Difference between revisions of "Function decoration pattern"

From HaskellWiki
Jump to navigation Jump to search
(New page: Category:Idioms ==Motivation== You want to add extra properties to a function type, but you don't want the users to have to tediously project out the decorated type when they don't c...)
 
Line 75: Line 75:
   
 
Now if we produce values of type <hask>IsIsomorphic a b</hask> rather than <hask>Iso a b</hask> we can just treat them like functions. Note that this should be pursued aggresively. For example, traditionally we'd have two functions <hask>from :: Iso a b -> b -> a</hask> and <hask>op :: Iso a b -> Iso b a</hask> but by using <hask>from :: Iso a b -> IsIsomorphic b a</hask> we get both at once. This can be enforced by making <hask>Iso</hask> abstract.
 
Now if we produce values of type <hask>IsIsomorphic a b</hask> rather than <hask>Iso a b</hask> we can just treat them like functions. Note that this should be pursued aggresively. For example, traditionally we'd have two functions <hask>from :: Iso a b -> b -> a</hask> and <hask>op :: Iso a b -> Iso b a</hask> but by using <hask>from :: Iso a b -> IsIsomorphic b a</hask> we get both at once. This can be enforced by making <hask>Iso</hask> abstract.
  +
  +
Another example would be allowing arrays to used as functions but still being able to get at the bounds when you needed them.
   
 
==Notes==
 
==Notes==

Revision as of 20:53, 20 January 2013


Motivation

You want to add extra properties to a function type, but you don't want the users to have to tediously project out the decorated type when they don't care about the decorations.

This can be generalized to arbitrary values instead of just functions.

Approach

Use type classes to drive the projection by the how the value is used.

{-# LANGUAGE MultiParamTypeClasses, Rank2Types, FlexibleContexts, FlexibleInstances #-}

-- This implementation is somewhat general, but it is not intended
-- that all examples can be cast in exactly this way.
data Decorate d a b = Decorated (a -> b) (d a b)

class Decorated d a b dec where
    decorated :: (a -> b) -> d a b -> dec a b 
    -- The above is a Scott-encoding of the below which is equivalent.
    -- The Scott-encoded version is often more convenient and efficient.`
    -- decorated :: Decorate d a b -> dec a b

instance Decorated d a b (Decorate d) where
    decorated = Decorated

instance Decorated d a b (->) where
    decorated f _ = f

type IsDecorated d a b = forall dec. Decorated d a b dec => dec a b 

-- Not a very realistic example.
type UnitTested = Decorate (,)
type IsUnitTested a b = IsDecorated (,) a b

makeTested :: (a -> b) -> a -> b -> IsUnitTested a b
makeTested f a b = decorated f (a, b)

test :: Eq b => UnitTested a b -> Bool
test (Decorated f (a, b)) = f a == b

testedSquare :: Num a => IsUnitTested a a
testedSquare = makeTested (\x -> x * x) 3 9

main = do
    print (map testedSquare [1,2,3])
    putStrLn (if test testedSquare then "Passed" else "Failed")


Examples

The archetypical example is the type of isomorphisms e.g. as used in the lens library.

An isomorphism is a function equipped with an inverse. Traditionally, this would be represented by a data type such as

data Iso a b = Iso { _to :: a -> b, _from :: b -> a }

This would require explicitly projecting out the forward function using _to, which makes the code noisy and tedious to write. This can be eliminated by writing:

class Isomorphic a b iso where
    iso :: (a -> b) -> (b -> a) -> iso a b

instance Isomorphic a b Iso where
    iso = Iso

instance Isomorphic a b (->) where
    iso to _ = to

type IsIsomorphic a b = forall iso. Isomorphic a b iso => iso a b

Now if we produce values of type IsIsomorphic a b rather than Iso a b we can just treat them like functions. Note that this should be pursued aggresively. For example, traditionally we'd have two functions from :: Iso a b -> b -> a and op :: Iso a b -> Iso b a but by using from :: Iso a b -> IsIsomorphic b a we get both at once. This can be enforced by making Iso abstract.

Another example would be allowing arrays to used as functions but still being able to get at the bounds when you needed them.

Notes

This is closely related to the Yoneda lemma and representability. Essentially we are identifying the value x with ($ x). The instances of the type classes just choose how we want to observe the x via ($ x) observation. makeTested makes this pretty explicit especially if the direct (rather than Scott-encoded) representation is used.