summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorMichael Orlitzky <michael@orlitzky.com>2014-11-06 08:29:26 +0100
committerHerbert Valerio Riedel <hvr@gnu.org>2014-11-06 08:54:27 +0100
commitd14312fcb4c7d3c2a35e086acdac6127ff1a4c60 (patch)
tree9cb761536228b2018b2c854a8d551f55e38ac8aa
parent081ef2fb351831081bf6851fd3907679b1b98405 (diff)
downloadhaskell-d14312fcb4c7d3c2a35e086acdac6127ff1a4c60.tar.gz
Add doctest examples for Data.Either
Add doctest examples for every data type and function in `Data.Either` Differential Revision: https://phabricator.haskell.org/D443
-rw-r--r--libraries/base/Data/Either.hs181
1 files changed, 175 insertions, 6 deletions
diff --git a/libraries/base/Data/Either.hs b/libraries/base/Data/Either.hs
index efa9328f3e..bd85b8fcdb 100644
--- a/libraries/base/Data/Either.hs
+++ b/libraries/base/Data/Either.hs
@@ -34,6 +34,10 @@ import GHC.Read
import Data.Typeable
import Data.Type.Equality
+-- $setup
+-- Allow the use of some Prelude functions in doctests.
+-- >>> import Prelude ( (+), (*), length, putStrLn )
+
{-
-- just for testing
import Test.QuickCheck
@@ -48,6 +52,75 @@ The 'Either' type is sometimes used to represent a value which is
either correct or an error; by convention, the 'Left' constructor is
used to hold an error value and the 'Right' constructor is used to
hold a correct value (mnemonic: \"right\" also means \"correct\").
+
+==== __Examples__
+
+The type @'Either' 'String' 'Int'@ is the type of values which can be either
+a 'String' or an 'Int'. The 'Left' constructor can be used only on
+'String's, and the 'Right' constructor can be used only on 'Int's:
+
+>>> let s = Left "foo" :: Either String Int
+>>> s
+Left "foo"
+>>> let n = Right 3 :: Either String Int
+>>> n
+Right 3
+>>> :type s
+s :: Either String Int
+>>> :type n
+n :: Either String Int
+
+The 'fmap' from our 'Functor' instance will ignore 'Left' values, but
+will apply the supplied function to values contained in a 'Right':
+
+>>> let s = Left "foo" :: Either String Int
+>>> let n = Right 3 :: Either String Int
+>>> fmap (*2) s
+Left "foo"
+>>> fmap (*2) n
+Right 6
+
+The 'Monad' instance for 'Either' allows us to chain together multiple
+actions which may fail, and fail overall if any of the individual
+steps failed. First we'll write a function that can either parse an
+'Int' from a 'Char', or fail.
+
+>>> import Data.Char ( digitToInt, isDigit )
+>>> :{
+ let parseEither :: Char -> Either String Int
+ parseEither c
+ | isDigit c = Right (digitToInt c)
+ | otherwise = Left "parse error"
+>>> :}
+
+The following should work, since both @\'1\'@ and @\'2\'@ can be
+parsed as 'Int's.
+
+>>> :{
+ let parseMultiple :: Either String Int
+ parseMultiple = do
+ x <- parseEither '1'
+ y <- parseEither '2'
+ return (x + y)
+>>> :}
+
+>>> parseMultiple
+Right 3
+
+But the following should fail overall, since the first operation where
+we attempt to parse @\'m\'@ as an 'Int' will fail:
+
+>>> :{
+ let parseMultiple :: Either String Int
+ parseMultiple = do
+ x <- parseEither 'm'
+ y <- parseEither '2'
+ return (x + y)
+>>> :}
+
+>>> parseMultiple
+Left "parse error"
+
-}
data Either a b = Left a | Right b
deriving (Eq, Ord, Read, Show, Typeable)
@@ -69,27 +142,74 @@ instance Monad (Either e) where
-- | Case analysis for the 'Either' type.
-- If the value is @'Left' a@, apply the first function to @a@;
-- if it is @'Right' b@, apply the second function to @b@.
+--
+-- ==== __Examples__
+--
+-- We create two values of type @'Either' 'String' 'Int'@, one using the
+-- 'Left' constructor and another using the 'Right' constructor. Then
+-- we apply \"either\" the 'length' function (if we have a 'String')
+-- or the \"times-two\" function (if we have an 'Int'):
+--
+-- >>> let s = Left "foo" :: Either String Int
+-- >>> let n = Right 3 :: Either String Int
+-- >>> either length (*2) s
+-- 3
+-- >>> either length (*2) n
+-- 6
+--
either :: (a -> c) -> (b -> c) -> Either a b -> c
either f _ (Left x) = f x
either _ g (Right y) = g y
--- | Extracts from a list of 'Either' all the 'Left' elements
--- All the 'Left' elements are extracted in order.
+-- | Extracts from a list of 'Either' all the 'Left' elements.
+-- All the 'Left' elements are extracted in order.
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
+-- >>> lefts list
+-- ["foo","bar","baz"]
+--
lefts :: [Either a b] -> [a]
lefts x = [a | Left a <- x]
--- | Extracts from a list of 'Either' all the 'Right' elements
+-- | Extracts from a list of 'Either' all the 'Right' elements.
-- All the 'Right' elements are extracted in order.
-
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
+-- >>> rights list
+-- [3,7]
+--
rights :: [Either a b] -> [b]
rights x = [a | Right a <- x]
--- | Partitions a list of 'Either' into two lists
+-- | Partitions a list of 'Either' into two lists.
-- All the 'Left' elements are extracted, in order, to the first
-- component of the output. Similarly the 'Right' elements are extracted
-- to the second component of the output.
-
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
+-- >>> partitionEithers list
+-- (["foo","bar","baz"],[3,7])
+--
+-- The pair returned by @'partitionEithers' x@ should be the same
+-- pair as @('lefts' x, 'rights' x)@:
+--
+-- >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
+-- >>> partitionEithers list == (lefts list, rights list)
+-- True
+--
partitionEithers :: [Either a b] -> ([a],[b])
partitionEithers = foldr (either left right) ([],[])
where
@@ -99,6 +219,31 @@ partitionEithers = foldr (either left right) ([],[])
-- | Return `True` if the given value is a `Left`-value, `False` otherwise.
--
-- /Since: 4.7.0.0/
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> isLeft (Left "foo")
+-- True
+-- >>> isLeft (Right 3)
+-- False
+--
+-- Assuming a 'Left' value signifies some sort of error, we can use
+-- 'isLeft' to write a very simple error-reporting function that does
+-- absolutely nothing in the case of success, and outputs \"ERROR\" if
+-- any error occurred.
+--
+-- This example shows how 'isLeft' might be used to avoid pattern
+-- matching when one does not care about the value contained in the
+-- constructor:
+--
+-- >>> import Control.Monad ( when )
+-- >>> let report e = when (isLeft e) $ putStrLn "ERROR"
+-- >>> report (Right 1)
+-- >>> report (Left "parse error")
+-- ERROR
+--
isLeft :: Either a b -> Bool
isLeft (Left _) = True
isLeft (Right _) = False
@@ -106,6 +251,30 @@ isLeft (Right _) = False
-- | Return `True` if the given value is a `Right`-value, `False` otherwise.
--
-- /Since: 4.7.0.0/
+--
+-- ==== __Examples__
+--
+-- Basic usage:
+--
+-- >>> isRight (Left "foo")
+-- False
+-- >>> isRight (Right 3)
+-- True
+--
+-- Assuming a 'Left' value signifies some sort of error, we can use
+-- 'isRight' to write a very simple reporting function that only
+-- outputs \"SUCCESS\" when a computation has succeeded.
+--
+-- This example shows how 'isRight' might be used to avoid pattern
+-- matching when one does not care about the value contained in the
+-- constructor:
+--
+-- >>> import Control.Monad ( when )
+-- >>> let report e = when (isRight e) $ putStrLn "SUCCESS"
+-- >>> report (Left "parse error")
+-- >>> report (Right 1)
+-- SUCCESS
+--
isRight :: Either a b -> Bool
isRight (Left _) = False
isRight (Right _) = True