Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/78960877ca29b78dd3d3b38f4f4b70eb9494b830

>---------------------------------------------------------------

commit 78960877ca29b78dd3d3b38f4f4b70eb9494b830
Author: Ross Paterson <[email protected]>
Date:   Tue Oct 30 01:22:17 2012 +0000

    add Traversable laws

>---------------------------------------------------------------

 Data/Traversable.hs |   74 ++++++++++++++++++++++++++++++++++++++++++++++++---
 1 files changed, 70 insertions(+), 4 deletions(-)

diff --git a/Data/Traversable.hs b/Data/Traversable.hs
index 75356ec..2ae49c6 100644
--- a/Data/Traversable.hs
+++ b/Data/Traversable.hs
@@ -16,15 +16,21 @@
 --
 -- See also
 --
---  * /Applicative Programming with Effects/,
---    by Conor McBride and Ross Paterson, online at
+--  * \"Applicative Programming with Effects\",
+--    by Conor McBride and Ross Paterson,
+--    /Journal of Functional Programming/ 18:1 (2008) 1-13, online at
 --    <http://www.soi.city.ac.uk/~ross/papers/Applicative.html>.
 --
---  * /The Essence of the Iterator Pattern/,
+--  * \"The Essence of the Iterator Pattern\",
 --    by Jeremy Gibbons and Bruno Oliveira,
---    in /Mathematically-Structured Functional Programming/, 2006, and online 
at
+--    in /Mathematically-Structured Functional Programming/, 2006, online at
 --    
<http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/#iterator>.
 --
+--  * \"An Investigation of the Laws of Traversals\",
+--    by Mauro Jaskelioff and Ondrej Rypacek,
+--    in /Mathematically-Structured Functional Programming/, 2012, online at
+--    <http://arxiv.org/pdf/1202.2919>.
+--
 -- Note that the functions 'mapM' and 'sequence' generalize "Prelude"
 -- functions of the same names from lists to any 'Traversable' functor.
 -- To avoid ambiguity, either import the "Prelude" hiding these names
@@ -33,11 +39,14 @@
 -----------------------------------------------------------------------------
 
 module Data.Traversable (
+    -- * The 'Traversable' class
     Traversable(..),
+    -- * Utility functions
     for,
     forM,
     mapAccumL,
     mapAccumR,
+    -- * General definitions for superclass methods
     fmapDefault,
     foldMapDefault,
     ) where
@@ -61,6 +70,63 @@ import Array
 --
 -- Minimal complete definition: 'traverse' or 'sequenceA'.
 --
+-- A definition of 'traverse' must satisfy the following laws:
+--
+-- [/naturality/]
+--   @t . 'traverse' f = 'traverse' (t . f)@
+--   for every applicative transformation @t@
+--
+-- [/identity/]
+--   @'traverse' Identity = Identity@
+--
+-- [/composition/]
+--   @'traverse' (Compose . 'fmap' g . f) = Compose . 'fmap' ('traverse' g) . 
'traverse' f@
+--
+-- A definition of 'sequenceA' must satisfy the following laws:
+--
+-- [/naturality/]
+--   @t . 'sequenceA' = 'sequenceA' . 'fmap' t@
+--   for every applicative transformation @t@
+--
+-- [/identity/]
+--   @'sequenceA' . 'fmap' Identity = Identity@
+--
+-- [/composition/]
+--   @'sequenceA' . 'fmap' Compose = Compose . 'fmap' 'sequenceA' . 
'sequenceA'@
+--
+-- where an /applicative transformation/ is a function
+--
+-- @t :: (Applicative f, Applicative g) => f a -> g a@
+--
+-- preserving the 'Applicative' operations, i.e.
+--
+--  * @t ('pure' x) = 'pure' x@
+--
+--  * @t (x '<*>' y) = t x '<*>' t y@
+--
+-- and the identity functor @Identity@ and composition of functors @Compose@
+-- are defined as
+--
+-- >   newtype Identity a = Identity a
+-- >
+-- >   instance Functor Identity where
+-- >     fmap f (Identity x) = Identity (f x)
+-- >
+-- >   instance Applicative Indentity where
+-- >     pure x = Identity x
+-- >     Identity f <*> Identity x = Identity (f x)
+-- >
+-- >   newtype Compose f g a = Compose (f (g a))
+-- >
+-- >   instance (Functor f, Functor g) => Functor (Compose f g) where
+-- >     fmap f (Compose x) = Compose (fmap (fmap f) x)
+-- >
+-- >   instance (Applicative f, Applicative g) => Applicative (Compose f g) 
where
+-- >     pure x = Compose (pure (pure x))
+-- >     Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
+--
+-- (The naturality law is implied by parametricity.)
+--
 -- Instances are similar to 'Functor', e.g. given a data type
 --
 -- > data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to