base-4.8.1.0: Basic libraries

Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Functor

Description

Functors: uniform action over a parameterized type, generalizing the map function on lists.

Synopsis

Documentation

class Functor f where Source

The Functor class is used for types that can be mapped over. Instances of Functor should satisfy the following laws:

fmap id  ==  id
fmap (f . g)  ==  fmap f . fmap g

The instances of Functor for lists, Maybe and IO satisfy these laws.

Minimal complete definition

fmap

Methods

fmap :: (a -> b) -> f a -> f b Source

(<$) :: a -> f b -> f a infixl 4 Source

Replace all locations in the input with the same value. The default definition is fmap . const, but this may be overridden with a more efficient version.

Instances

Functor [] Source 

Methods

fmap :: (a -> b) -> [a] -> [b] Source

(<$) :: a -> [b] -> [a] Source

Functor IO Source 

Methods

fmap :: (a -> b) -> IO a -> IO b Source

(<$) :: a -> IO b -> IO a Source

Functor Maybe Source 

Methods

fmap :: (a -> b) -> Maybe a -> Maybe b Source

(<$) :: a -> Maybe b -> Maybe a Source

Functor ReadP Source 

Methods

fmap :: (a -> b) -> ReadP a -> ReadP b Source

(<$) :: a -> ReadP b -> ReadP a Source

Functor ReadPrec Source 

Methods

fmap :: (a -> b) -> ReadPrec a -> ReadPrec b Source

(<$) :: a -> ReadPrec b -> ReadPrec a Source

Functor Last Source 

Methods

fmap :: (a -> b) -> Last a -> Last b Source

(<$) :: a -> Last b -> Last a Source

Functor First Source 

Methods

fmap :: (a -> b) -> First a -> First b Source

(<$) :: a -> First b -> First a Source

Functor STM Source 

Methods

fmap :: (a -> b) -> STM a -> STM b Source

(<$) :: a -> STM b -> STM a Source

Functor Handler Source 

Methods

fmap :: (a -> b) -> Handler a -> Handler b Source

(<$) :: a -> Handler b -> Handler a Source

Functor ZipList Source 

Methods

fmap :: (a -> b) -> ZipList a -> ZipList b Source

(<$) :: a -> ZipList b -> ZipList a Source

Functor Identity Source 

Methods

fmap :: (a -> b) -> Identity a -> Identity b Source

(<$) :: a -> Identity b -> Identity a Source

Functor ArgDescr Source 

Methods

fmap :: (a -> b) -> ArgDescr a -> ArgDescr b Source

(<$) :: a -> ArgDescr b -> ArgDescr a Source

Functor OptDescr Source 

Methods

fmap :: (a -> b) -> OptDescr a -> OptDescr b Source

(<$) :: a -> OptDescr b -> OptDescr a Source

Functor ArgOrder Source 

Methods

fmap :: (a -> b) -> ArgOrder a -> ArgOrder b Source

(<$) :: a -> ArgOrder b -> ArgOrder a Source

Functor ((->) r) Source 

Methods

fmap :: (a -> b) -> (->) r a -> (->) r b Source

(<$) :: a -> (->) r b -> (->) r a Source

Functor (Either a) Source 

Methods

fmap :: (b -> c) -> Either a b -> Either a c Source

(<$) :: b -> Either a c -> Either a b Source

Functor ((,) a) Source 

Methods

fmap :: (b -> c) -> (a, b) -> (a, c) Source

(<$) :: b -> (a, c) -> (a, b) Source

Functor (ST s) Source 

Methods

fmap :: (a -> b) -> ST s a -> ST s b Source

(<$) :: a -> ST s b -> ST s a Source

Functor (Proxy *) Source 

Methods

fmap :: (a -> b) -> Proxy * a -> Proxy * b Source

(<$) :: a -> Proxy * b -> Proxy * a Source

Arrow a => Functor (ArrowMonad a) Source 

Methods

fmap :: (b -> c) -> ArrowMonad a b -> ArrowMonad a c Source

(<$) :: b -> ArrowMonad a c -> ArrowMonad a b Source

Monad m => Functor (WrappedMonad m) Source 

Methods

fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b Source

(<$) :: a -> WrappedMonad m b -> WrappedMonad m a Source

Functor (Const m) Source 

Methods

fmap :: (a -> b) -> Const m a -> Const m b Source

(<$) :: a -> Const m b -> Const m a Source

Functor (ST s) Source 

Methods

fmap :: (a -> b) -> ST s a -> ST s b Source

(<$) :: a -> ST s b -> ST s a Source

Functor f => Functor (Alt * f) Source 

Methods

fmap :: (a -> b) -> Alt * f a -> Alt * f b Source

(<$) :: a -> Alt * f b -> Alt * f a Source

Arrow a => Functor (WrappedArrow a b) Source 

Methods

fmap :: (c -> d) -> WrappedArrow a b c -> WrappedArrow a b d Source

(<$) :: c -> WrappedArrow a b d -> WrappedArrow a b c Source

($>) :: Functor f => f a -> b -> f b infixl 4 Source

Flipped version of <$.

Examples

Replace the contents of a Maybe Int with a constant String:

>>> Nothing $> "foo"
Nothing
>>> Just 90210 $> "foo"
Just "foo"

Replace the contents of an Either Int Int with a constant String, resulting in an Either Int String:

>>> Left 8675309 $> "foo"
Left 8675309
>>> Right 8675309 $> "foo"
Right "foo"

Replace each element of a list with a constant String:

>>> [1,2,3] $> "foo"
["foo","foo","foo"]

Replace the second element of a pair with a constant String:

>>> (1,2) $> "foo"
(1,"foo")

Since: 4.7.0.0

(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 Source

An infix synonym for fmap.

Examples

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an Either Int String using show:

>>> show <$> Left 17
Left 17
>>> show <$> Right 17
Right "17"

Double each element of a list:

>>> (*2) <$> [1,2,3]
[2,4,6]

Apply even to the second element of a pair:

>>> even <$> (2,2)
(2,True)

void :: Functor f => f a -> f () Source

void value discards or ignores the result of evaluation, such as the return value of an IO action.

Examples

Replace the contents of a Maybe Int with unit:

>>> void Nothing
Nothing
>>> void (Just 3)
Just ()

Replace the contents of an Either Int Int with unit, resulting in an Either Int '()':

>>> void (Left 8675309)
Left 8675309
>>> void (Right 8675309)
Right ()

Replace every element of a list with unit:

>>> void [1,2,3]
[(),(),()]

Replace the second element of a pair with unit:

>>> void (1,2)
(1,())

Discard the result of an IO action:

>>> mapM print [1,2]
1
2
[(),()]
>>> void $ mapM print [1,2]
1
2