diff options
author | Viktor Dukhovni <ietf-dane@dukhovni.org> | 2020-06-08 09:59:35 -0400 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2020-06-13 02:13:05 -0400 |
commit | 87d504f475471c61305b29578da2656f9ff9653e (patch) | |
tree | 03509c5d1fab9a61299c962a7e1571b5b97e5fb0 | |
parent | 429539025450757e30124fa9ee33206deeb951a2 (diff) | |
download | haskell-87d504f475471c61305b29578da2656f9ff9653e.tar.gz |
Add introductory prose for Data.Traversable
-rw-r--r-- | libraries/base/Data/Traversable.hs | 511 |
1 files changed, 419 insertions, 92 deletions
diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs index 0b6e775dd1..257af1d89d 100644 --- a/libraries/base/Data/Traversable.hs +++ b/libraries/base/Data/Traversable.hs @@ -18,24 +18,6 @@ -- -- Class of data structures that can be traversed from left to right, -- performing an action on each element. --- --- See also --- --- * \"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\", --- by Jeremy Gibbons and Bruno Oliveira, --- 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>. --- ----------------------------------------------------------------------------- module Data.Traversable ( @@ -49,6 +31,32 @@ module Data.Traversable ( -- * General definitions for superclass methods fmapDefault, foldMapDefault, + + -- * Overview + -- $overview + + -- ** The 'traverse' and 'mapM' methods + -- $traverse + + -- ** Validation use-case + -- $validation + + -- ** The 'sequenceA' and 'sequence' methods + -- $sequence + + -- ** Sample instance + -- $sample_instance + + -- ** Construction + -- + -- $construction + + -- * Laws + -- + -- $laws + + -- * See also + -- $also ) where -- It is convenient to use 'Const' here but this means we must @@ -56,7 +64,7 @@ module Data.Traversable ( import Control.Applicative ( Const(..), ZipList(..) ) import Data.Coerce import Data.Either ( Either(..) ) -import Data.Foldable ( Foldable ) +import Data.Foldable import Data.Functor import Data.Functor.Identity ( Identity(..) ) import Data.Functor.Utils ( StateL(..), StateR(..) ) @@ -74,79 +82,6 @@ import qualified GHC.List as List ( foldr ) -- | Functors representing data structures that can be traversed from -- left to right. -- --- 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' ('Data.Functor.Compose.Compose' . 'fmap' g . f) --- = 'Data.Functor.Compose.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' 'Data.Functor.Compose.Compose' --- = 'Data.Functor.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 (f '<*>' x) = t f '<*>' t x --- @ --- --- and the identity functor 'Identity' and composition functors --- 'Data.Functor.Compose.Compose' are from "Data.Functor.Identity" and --- "Data.Functor.Compose". --- --- A result of the naturality law is a purity law for 'traverse' --- --- @'traverse' 'pure' = 'pure'@ --- --- (The naturality law is implied by parametricity and thus so is the --- purity law [1, p15].) --- --- Instances are similar to 'Functor', e.g. given a data type --- --- > data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) --- --- a suitable instance would be --- --- > instance Traversable Tree where --- > traverse f Empty = pure Empty --- > traverse f (Leaf x) = Leaf <$> f x --- > traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r --- --- This is suitable even for abstract types, as the laws for '<*>' --- imply a form of associativity. --- --- The superclass instances should satisfy the following: --- --- * In the 'Functor' instance, 'fmap' should be equivalent to traversal --- with the identity applicative functor ('fmapDefault'). --- --- * In the 'Foldable' instance, 'Data.Foldable.foldMap' should be --- equivalent to traversal with a constant applicative functor --- ('foldMapDefault'). --- --- References: --- [1] The Essence of the Iterator Pattern, Jeremy Gibbons and Bruno C. d. S. Oliveira class (Functor t, Foldable t) => Traversable t where {-# MINIMAL traverse | sequenceA #-} @@ -411,3 +346,395 @@ foldMapDefault :: forall t m a . (Traversable t, Monoid m) {-# INLINE foldMapDefault #-} -- See Note [Function coercion] in Data.Functor.Utils. foldMapDefault = coerce (traverse :: (a -> Const m ()) -> t a -> Const m (t ())) + +------------------ + +-- $overview +-- @Traversable@ functors can be thought of as polymorphic containers that +-- support mapping of applicative (or monadic) effects over the container +-- (element-wise) to create a new container of __the same shape__, with the +-- effects sequenced in a natural order for the container type in question. +-- +-- The 'Functor' base class means that the container cannot impose any +-- constraints on the element type, so containers that require elements to +-- be comparable, or hashable, etc., cannot be instances of the @Traversable@ +-- class. + +------------------ + +-- $traverse +-- For an 'Applicative' functor __@f@__ and a Traversable functor __@t@__, the +-- type signatures of 'traverse' and 'fmap' are rather similar: +-- +-- > fmap :: (a -> f b) -> t a -> t (f b) +-- > traverse :: (a -> f b) -> t a -> f (t b) +-- +-- with one crucial difference: 'fmap' produces a container of effects, while +-- traverse produces an aggregate container-valued effect. For example, when +-- __@f@__ is the __@IO@__ monad, and __@t@__ is the List functor, while 'fmap' +-- returns a list of pending IO actions 'traverse' returns an IO action that +-- evaluates to a list of the return values of the individual actions performed +-- left-to-right. +-- +-- More concretely, if @nameAndLineCount@ counts the number of lines in a file, +-- returning a pair with input filename and the line count, then traversal +-- over a list of file names produces an IO action that evaluates to a list +-- of __@(fileName, lineCount)@__ pairs: +-- +-- >>> nameAndLineCount :: FilePath -> IO (FilePath, Int) +-- >>> nameAndLineCount fn = ... +-- >>> traverse nameAndLineCount ["/etc/passwd","/etc/hosts"] +-- [("/etc/passwd",56),("/etc/hosts",32)] +-- +-- The specialisation of 'traverse' to the case when __@f@__ is a monad is +-- called 'mapM'. The two are otherwise generally identical: +-- +-- > traverse :: (Applicative f, Traversable t) => (a -> f b) -> t a -> f (t b) +-- > mapM :: (Monad m, Traversable t) => (a -> m b) -> t a -> m (t b) +-- +-- The behaviour of 'traverse' and 'mapM' can be at first surprising when the +-- applicative functor __@f@__ is __@[]@__ (i.e. the List monad). The List +-- monad is said to be /non-deterministic/, by which is meant that applying a +-- list of __@n@__ functions __@[a -> b]@__ to a list of __@k@__ values +-- __@[a]@__ produces a list of __@n*k@__ values of each function applied to +-- each input value. +-- +-- As a result, traversal with a function __@f :: a -> [b]@__, over an input +-- container __@t a@__, yields a list __@[t b]@__, whose length is the product +-- of the lengths of the lists that the function returns for each element of +-- the input container! The individual elements __@a@__ of the container are +-- replaced by each element of __@f a@__ in turn: +-- +-- >>> mapM (\n -> [0..n]) $ Just 2 +-- [Just 0, Just 1, Just 2] +-- >>> mapM (\n -> [0..n]) [0..2] +-- [[0,0,0],[0,0,1],[0,0,2],[0,1,0],[0,1,1],[0,1,2]] +-- +-- If any element of the container is mapped to an empty list, then the +-- aggregate result is empty (no value is available to fill one of the +-- slots of the output container). +-- +-- >>> traverse (const []) $ Just 0 +-- [] +-- +-- When however the traversed container is empty, the result is always a +-- singleton of the empty container, the function is never evaluated +-- as there are no input values for it to be applied to. +-- +-- >>> traverse (const []) Nothing +-- [Nothing] +-- +-- The result of 'traverse' is all-or-nothing, either containers of exactly the +-- same shape as the input or a failure ('Nothing', 'Left', empty list, etc.). +-- The 'traverse' function does not perform selective filtering as with e.g. +-- 'Data.Maybe.mapMaybe': +-- +-- >>> let incOdd n = if odd n then Just $ n + 1 else Nothing +-- >>> traverse incOdd [1, 2, 3] +-- Nothing +-- >>> mapMaybe incOdd [1, 2, 3] +-- [2,4] + +------------------ + +-- $validation +-- A hypothetical application of the above is to validate a structure: +-- +-- >>> validate :: Int -> Either (String, Int) Int +-- >>> validate i = if odd i then Left ("That's odd", i) else Right i +-- >>> traverse validate [2,4,6,8,10] +-- Right [2,4,6,8,10] +-- >>> traverse validate [2,4,6,8,9] +-- Left ("That's odd",9) +-- +-- >>> -- Since 'Nothing' is an empty structure, none of its elements are odd. +-- >>> traverse validate Nothing +-- Right Nothing +-- >>> traverse validate (Just 42) +-- Right (Just 42) +-- >>> traverse validate (Just 17) +-- Left ("That's odd",17) +-- +-- However, this is not terribly efficient, because we pay the cost of +-- reconstructing the entire structure as a side effect of validation. +-- It is generally cheaper to just check all the elements and then use +-- the original structure if it is valid. This can be done via the +-- methods of the 'Foldable' superclass, which perform only the +-- side effects without generating a new structure: +-- +-- >>> traverse_ validate [2,4,6,8,10] +-- Right () +-- >>> traverse_ validate [2,4,6,8,9] +-- Left ("That's odd",9) +-- +-- The @Foldable@ instance should be defined in a manner that avoids +-- construction of an unnecesary copy of the container. +-- +-- Perhaps the most widely used @Foldable@ methods are 'mapM_' and its flipped +-- version 'forM_'. Often, to sequence IO actions (that return no useful +-- results) over all the elements of a @Traversable@ container. One special +-- case is a 'Maybe' container that optionally holds a value. Given: +-- +-- > action :: a -> IO () +-- > mvalue :: Maybe a +-- +-- if you want to evaluate the __@action@__ in the @Just@ case, and do +-- nothing otherwise, you can write the more concise and more general: +-- +-- > mapM_ action mvalue +-- +-- rather than +-- +-- > maybe (return ()) action mvalue +-- +-- The 'mapM_' form works verbatim if the type of __@mvalue@__ is later +-- refactored from __@Maybe a@__ to __@Either e a@__ (assuming it remains +-- OK to silently do nothing in the error case). +-- +-- There's even a generic way to handle empty values ('Nothing', 'Left', etc.): +-- +-- > case traverse_ (const Nothing) mvalue of +-- > Nothing -> mapM_ action mvalue -- mvalue is non-empty +-- > Just () -> ... handle empty mvalue ... + +------------------ + +-- $sequence +-- The 'sequenceA' and 'sequence' methods are useful when what you have is a +-- container of applicative or, respectively, monadic actions, and you want to +-- evaluate them left-to-right to obtain a container of the computed values. +-- +-- > sequenceA :: (Applicative f, Traversable t) => t (f a) -> f (t a) +-- > sequence :: (Monad m, Traversable t) => t (m a) -> m (t a) +-- > sequenceA = traverse id +-- > sequence = mapM id +-- +-- When the monad __@m@__ is 'System.IO.IO', applying 'sequence' to a list of +-- IO actions, performs each in turn, returning a list of the results: +-- +-- > sequence [putStr "Hello ", putStrLn "World!"] +-- > = (\a b -> [a,b]) <$> putStr "Hello " <*> putStrLn "World!" +-- > = do u1 <- putStr "Hello " +-- > u2 <- putStrLn "World!" +-- > return (u1, u2) +-- +-- For 'sequenceA', the /non-deterministic/ behaviour of @List@ is most easily +-- seen in the case of a list of lists (of elements of some common fixed type). +-- The result is a cross-product of all the sublists: +-- +-- >>> sequenceA [[0, 1, 2], [30, 40], [500]] +-- [[0,30,500],[0,40,500],[1,30,500],[1,40,500],[2,30,500],[2,40,500]] +-- +-- When the monad __@m@__ is 'Maybe' or 'Either', the effect in question is to +-- short-circuit the computation on encountering 'Nothing' or 'Left'. +-- +-- >>> sequence [Just 1,Just 2,Just 3] +-- Just [1,2,3] +-- >>> sequence [Just 1,Nothing,Just 3] +-- Nothing +-- >>> sequence [Right 1,Right 2,Right 3] +-- Right [1,2,3] +-- >>> sequence [Right 1,Left "sorry",Right 3] +-- Left "sorry" +-- +-- The result of 'sequence' is all-or-nothing, either containers of exactly the +-- same shape as the input or a failure ('Nothing', 'Left', empty list, etc.). +-- The 'sequence' function does not perform selective filtering as with e.g. +-- 'Data.Maybe.catMaybes' or 'Data.Either.rights': +-- +-- >>> catMaybes [Just 1,Nothing,Just 3] +-- [1,3] +-- >>> rights [Right 1,Left "sorry",Right 3] +-- [1,3] + +------------------ + +-- $sample_instance +-- +-- Instances are similar to 'Functor', e.g. given a data type +-- +-- > data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) +-- +-- a suitable instance would be +-- +-- > instance Traversable Tree where +-- > traverse f Empty = pure Empty +-- > traverse f (Leaf x) = Leaf <$> f x +-- > traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r +-- +-- This definition works for any applicative functor in the co-domain of @f@, +-- as the laws for '<*>' imply a form of associativity. + +------------------ + +-- $construction +-- +-- How do @Traversable@ functors manage to construct a new container of the +-- same shape by sequencing effects over their elements? Well, left-to-right +-- traversal with sequencing of effects suggests induction from a base case, so +-- the first question is what is the base case? A @Traversable@ container with +-- elements of type __@a@__ generally has some minimal form that is either +-- "empty" or has just a single element (think "Data.List" vs. +-- "Data.List.Nonempty"). +-- +-- * If the base case is empty (no associated first value of __@a@__) then +-- traversal just reproduces the empty structure with no side effects, +-- so we have: +-- +-- > traverse _ empty = pure empty +-- +-- With the List monad, "empty" is __@[]@__, while with 'Maybe' it is +-- 'Nothing'. With __@Either e a@__ we have an /empty/ case for each +-- value of __@e@__. +-- +-- * If the base case is a __@singleton a@__, then 'traverse' can take that +-- __@a@__, apply __@f :: a -> F b@__ getting an __@F b@__, then +-- __@fmap singleton@__ over that, getting __@F (singleton b)@__: +-- +-- > traverse f (singleton a) = singleton <$> f a +-- +-- Since 'Maybe' and 'Either' are either empty or singletons, we have +-- +-- > traverse _ Nothing = pure Nothing +-- > traverse f (Just a) = Just <$> f a +-- +-- > traverse _ (Left e) = pure (Left e) +-- > traverse f (Right a) = Right <$> f a +-- +-- Similarly, for List, we have: +-- +-- > traverse f [] = pure [] +-- > traverse f [a] = fmap (:[]) (f a) = (:) <$> f a <*> pure [] +-- +-- What remains to be done is an inductive step beyond the empty and singleton +-- cases. For a concrete @Traversable@ functor @T@ we need to be able to +-- extend our structure incrementally by filling in holes. We can view a +-- partially built structure __@t0 :: T a@__ as a function +-- __@append :: a -> T a@__ that takes one more element __@a@__ to insert into +-- the container to the right of the existing elements to produce a larger +-- structure. Conversely, we can view an element @a@ as a function +-- __@prepend :: T a -> T a@__ of a partially built structure that inserts the +-- element to the left of the existing elements. +-- +-- Assuming that 'traverse' has already been defined on the partially built +-- structure: +-- +-- > f0 = traverse f t0 :: F (T b) +-- +-- we aim to define __@traverse f (append t0 a)@__ and/or +-- __@traverse f (prepend a t0)@__. +-- +-- We can lift @append@ and apply it to @f0@ to get: +-- +-- > append <$> f0 :: F (b -> T b) +-- +-- and from the /next/ element __@a@__ we can obtain __@f a :: F b@__, and +-- this is where we'll make use of the applicative instance of @F@. Adding +-- one more element on the right is then: +-- +-- > traverse f (append t0 a) = append <$> traverse f t0 <*> f a +-- +-- while prepending an element on the left is: +-- +-- > traverse f (prepend a t0) = prepend <$> f a <*> traverse f t0 +-- +-- The (binary) @Tree@ instance example makes use of both, after defining the +-- @Empty@ base case and the singleton @Leaf@ node case, non-empty internal +-- nodes introduce both a prepended child node on the left and an appended +-- child node on the right: +-- +-- > traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r +-- +-- The above definitions sequence the 'Applicative' effects of __@F@__ in the +-- expected order while producing results of the expected shape __@T@__. +-- +-- For lists we get the natural order of effects by using +-- __@(prepend \<$\> f a)@__ as the operator and __@(traverse f as)@__ as the +-- operand (the actual definition is written as an equivalent right fold +-- in order to enable /fusion/ rules): +-- +-- > traverse f [] = pure [] +-- > traverse f (a:as) = (:) <$> f a <*> traverse f as +-- +-- The origin of the combinatorial product when __@F@__ is __@[]@__ should now +-- be apparent, the /non-deterministic/ definition of @\<*\>@ for @List@ makes +-- multiple independent choices for each element of the structure. + +------------------ + +-- $laws +-- 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' ('Data.Functor.Compose.Compose' . 'fmap' g . f) +-- = 'Data.Functor.Compose.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' 'Data.Functor.Compose.Compose' +-- = 'Data.Functor.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 (f '<*>' x) = t f '<*>' t x +-- @ +-- +-- and the identity functor 'Identity' and composition functors +-- 'Data.Functor.Compose.Compose' are from "Data.Functor.Identity" and +-- "Data.Functor.Compose". +-- +-- A result of the naturality law is a purity law for 'traverse' +-- +-- @'traverse' 'pure' = 'pure'@ +-- +-- (The naturality law is implied by parametricity and thus so is the +-- purity law [1, p15].) +-- +-- The superclass instances should satisfy the following: +-- +-- * In the 'Functor' instance, 'fmap' should be equivalent to traversal +-- with the identity applicative functor ('fmapDefault'). +-- +-- * In the 'Foldable' instance, 'Data.Foldable.foldMap' should be +-- equivalent to traversal with a constant applicative functor +-- ('foldMapDefault'). + +------------------ + +-- $also +-- +-- * [1] \"The Essence of the Iterator Pattern\", +-- by Jeremy Gibbons and Bruno Oliveira, +-- in /Mathematically-Structured Functional Programming/, 2006, online at +-- <http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/#iterator>. +-- +-- * \"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>. +-- +-- * \"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>. |