ghc-internal-9.1001.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

GHC.Internal.Data.Functor

Description

A type f is a Functor if it provides a function fmap which, given any types a and b, lets you apply any function of type (a -> b) to turn an f a into an f b, preserving the structure of f.

Examples

Expand
>>> fmap show (Just 1)  --  (a   -> b)      -> f a       -> f b
Just "1"                --  (Int -> String) -> Maybe Int -> Maybe String
>>> fmap show Nothing   --  (a   -> b)      -> f a       -> f b
Nothing                 --  (Int -> String) -> Maybe Int -> Maybe String
>>> fmap show [1,2,3]   --  (a   -> b)      -> f a       -> f b
["1","2","3"]           --  (Int -> String) -> [Int]     -> [String]
>>> fmap show []        --  (a   -> b)      -> f a       -> f b
[]                      --  (Int -> String) -> [Int]     -> [String]

The fmap function is also available as the infix operator <$>:

>>> fmap show (Just 1) --  (Int -> String) -> Maybe Int -> Maybe String
Just "1"
>>> show <$> (Just 1)  --  (Int -> String) -> Maybe Int -> Maybe String
Just "1"
Synopsis

Documentation

class Functor (f :: Type -> Type) where Source #

A type f is a Functor if it provides a function fmap which, given any types a and b lets you apply any function from (a -> b) to turn an f a into an f b, preserving the structure of f. Furthermore f needs to adhere to the following:

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

Note, that the second law follows from the free theorem of the type fmap and the first law, so you need only check that the former condition holds. See these articles by School of Haskell or David Luposchainsky for an explanation.

Minimal complete definition

fmap

Methods

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

fmap is used to apply a function of type (a -> b) to a value of type f a, where f is a functor, to produce a value of type f b. Note that for any type constructor with more than one parameter (e.g., Either), only the last type parameter can be modified with fmap (e.g., b in `Either a b`).

Some type constructors with two parameters or more have a Bifunctor instance that allows both the last and the penultimate parameters to be mapped over.

Examples

Expand

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

>>> fmap show Nothing
Nothing
>>> fmap show (Just 3)
Just "3"

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

>>> fmap show (Left 17)
Left 17
>>> fmap show (Right 17)
Right "17"

Double each element of a list:

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

Apply even to the second element of a pair:

>>> fmap even (2,2)
(2,True)

It may seem surprising that the function is only applied to the last element of the tuple compared to the list example above which applies it to every element in the list. To understand, remember that tuples are type constructors with multiple type parameters: a tuple of 3 elements (a,b,c) can also be written (,,) a b c and its Functor instance is defined for Functor ((,,) a b) (i.e., only the third parameter is free to be mapped over with fmap).

It explains why fmap can be used with tuples containing values of different types as in the following example:

>>> fmap even ("hello", 1.0, 4)
("hello",1.0,True)

(<$) :: 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.

Examples

Expand

Perform a computation with Maybe and replace the result with a constant value if it is Just:

>>> 'a' <$ Just 2
Just 'a'
>>> 'a' <$ Nothing
Nothing

Instances

Instances details
Functor NonEmpty Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b Source #

(<$) :: a -> NonEmpty b -> NonEmpty a Source #

Functor STM Source #

@since base-4.3.0.0

Instance details

Defined in GHC.Internal.Conc.Sync

Methods

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

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

Functor Handler Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Control.Exception

Methods

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

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

Functor Identity Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Methods

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

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

Functor First Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

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

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

Functor Last Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

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

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

Functor Down Source #

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

fmap :: (a -> b) -> Down a -> Down b Source #

(<$) :: a -> Down b -> Down a Source #

Functor Dual Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Dual a -> Dual b Source #

(<$) :: a -> Dual b -> Dual a Source #

Functor Product Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Product a -> Product b Source #

(<$) :: a -> Product b -> Product a Source #

Functor Sum Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Sum a -> Sum b Source #

(<$) :: a -> Sum b -> Sum a Source #

Functor ZipList Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Functor.ZipList

Methods

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

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

Functor NoIO Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.GHCi

Methods

fmap :: (a -> b) -> NoIO a -> NoIO b Source #

(<$) :: a -> NoIO b -> NoIO a Source #

Functor Par1 Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> Par1 a -> Par1 b Source #

(<$) :: a -> Par1 b -> Par1 a Source #

Functor ReadP Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Text.ParserCombinators.ReadP

Methods

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

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

Functor ReadPrec Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Text.ParserCombinators.ReadPrec

Methods

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

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

Functor IO Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

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

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

Functor Maybe Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

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

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

Functor Solo Source #

@since base-4.15

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a -> b) -> Solo a -> Solo b Source #

(<$) :: a -> Solo b -> Solo a Source #

Functor [] Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

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

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

Functor (Array i) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Arr

Methods

fmap :: (a -> b) -> Array i a -> Array i b Source #

(<$) :: a -> Array i b -> Array i a Source #

Arrow a => Functor (ArrowMonad a) Source #

@since base-4.6.0.0

Instance details

Defined in GHC.Internal.Control.Arrow

Methods

fmap :: (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b Source #

(<$) :: a0 -> ArrowMonad a b -> ArrowMonad a a0 Source #

Functor (ST s) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Control.Monad.ST.Lazy.Imp

Methods

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

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

Functor (Either a) Source #

@since base-3.0

Instance details

Defined in GHC.Internal.Data.Either

Methods

fmap :: (a0 -> b) -> Either a a0 -> Either a b Source #

(<$) :: a0 -> Either a b -> Either a a0 Source #

Functor (StateL s) Source #

@since base-4.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

fmap :: (a -> b) -> StateL s a -> StateL s b Source #

(<$) :: a -> StateL s b -> StateL s a Source #

Functor (StateR s) Source #

@since base-4.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

fmap :: (a -> b) -> StateR s a -> StateR s b Source #

(<$) :: a -> StateR s b -> StateR s a Source #

Functor (Proxy :: Type -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

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

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

Functor (U1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> U1 a -> U1 b Source #

(<$) :: a -> U1 b -> U1 a Source #

Functor (V1 :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> V1 a -> V1 b Source #

(<$) :: a -> V1 b -> V1 a Source #

Functor (ST s) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.ST

Methods

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

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

Functor ((,) a) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a0 -> b) -> (a, a0) -> (a, b) Source #

(<$) :: a0 -> (a, b) -> (a, a0) Source #

Functor m => Functor (Kleisli m a) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Control.Arrow

Methods

fmap :: (a0 -> b) -> Kleisli m a a0 -> Kleisli m a b Source #

(<$) :: a0 -> Kleisli m a b -> Kleisli m a a0 Source #

Functor (Const m :: Type -> Type) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

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

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

Monad m => Functor (StateT s m) Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Utils

Methods

fmap :: (a -> b) -> StateT s m a -> StateT s m b Source #

(<$) :: a -> StateT s m b -> StateT s m a Source #

Functor f => Functor (Ap f) Source #

@since base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

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

(<$) :: a -> Ap f b -> Ap f a Source #

Functor f => Functor (Alt f) Source #

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

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

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

(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) Source #

@since base-4.17.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

(<$) :: a -> Generically1 f b -> Generically1 f a Source #

Functor f => Functor (Rec1 f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

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

(<$) :: a -> Rec1 f b -> Rec1 f a Source #

Functor (URec (Ptr ()) :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b Source #

(<$) :: a -> URec (Ptr ()) b -> URec (Ptr ()) a Source #

Functor (URec Char :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Char a -> URec Char b Source #

(<$) :: a -> URec Char b -> URec Char a Source #

Functor (URec Double :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Double a -> URec Double b Source #

(<$) :: a -> URec Double b -> URec Double a Source #

Functor (URec Float :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Float a -> URec Float b Source #

(<$) :: a -> URec Float b -> URec Float a Source #

Functor (URec Int :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Int a -> URec Int b Source #

(<$) :: a -> URec Int b -> URec Int a Source #

Functor (URec Word :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b Source #

(<$) :: a -> URec Word b -> URec Word a Source #

Functor ((,,) a b) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a0 -> b0) -> (a, b, a0) -> (a, b, b0) Source #

(<$) :: a0 -> (a, b, b0) -> (a, b, a0) Source #

(Functor f, Functor g) => Functor (f :*: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> (f :*: g) a -> (f :*: g) b Source #

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

(Functor f, Functor g) => Functor (f :+: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> (f :+: g) a -> (f :+: g) b Source #

(<$) :: a -> (f :+: g) b -> (f :+: g) a Source #

Functor (K1 i c :: Type -> Type) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> K1 i c a -> K1 i c b Source #

(<$) :: a -> K1 i c b -> K1 i c a Source #

Functor ((,,,) a b c) Source #

@since base-4.14.0.0

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a0 -> b0) -> (a, b, c, a0) -> (a, b, c, b0) Source #

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

Functor ((->) r) Source #

@since base-2.01

Instance details

Defined in GHC.Internal.Base

Methods

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

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

(Functor f, Functor g) => Functor (f :.: g) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> (f :.: g) a -> (f :.: g) b Source #

(<$) :: a -> (f :.: g) b -> (f :.: g) a Source #

Functor f => Functor (M1 i c f) Source #

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> M1 i c f a -> M1 i c f b Source #

(<$) :: a -> M1 i c f b -> M1 i c f a Source #

Functor ((,,,,) a b c d) Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a0 -> b0) -> (a, b, c, d, a0) -> (a, b, c, d, b0) Source #

(<$) :: a0 -> (a, b, c, d, b0) -> (a, b, c, d, a0) Source #

Functor ((,,,,,) a b c d e) Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a0 -> b0) -> (a, b, c, d, e, a0) -> (a, b, c, d, e, b0) Source #

(<$) :: a0 -> (a, b, c, d, e, b0) -> (a, b, c, d, e, a0) Source #

Functor ((,,,,,,) a b c d e f) Source #

@since base-4.18.0.0

Instance details

Defined in GHC.Internal.Base

Methods

fmap :: (a0 -> b0) -> (a, b, c, d, e, f, a0) -> (a, b, c, d, e, f, b0) Source #

(<$) :: a0 -> (a, b, c, d, e, f, b0) -> (a, b, c, d, e, f, a0) Source #

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

Flipped version of <$.

@since base-4.7.0.0

Examples

Expand

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")

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

An infix synonym for fmap.

The name of this operator is an allusion to $. Note the similarities between their types:

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

Whereas $ is function application, <$> is function application lifted over a Functor.

Examples

Expand

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)

(<&>) :: Functor f => f a -> (a -> b) -> f b infixl 1 Source #

Flipped version of <$>.

(<&>) = flip fmap

@since base-4.11.0.0

Examples

Expand

Apply (+1) to a list, a Just and a Right:

>>> Just 2 <&> (+1)
Just 3
>>> [1,2,3] <&> (+1)
[2,3,4]
>>> Right 3 <&> (+1)
Right 4

unzip :: Functor f => f (a, b) -> (f a, f b) Source #

Generalization of Data.List.unzip.

Examples

Expand
>>> unzip (Just ("Hello", "World"))
(Just "Hello",Just "World")
>>> unzip [("I", "love"), ("really", "haskell")]
(["I","really"],["love","haskell"])

@since base-4.19.0.0

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

Expand

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