| Copyright | (c) 2016 Stephen Diehl (c) 2016-2018 Serokell (c) 2018-2023 Kowainik  | 
|---|---|
| License | MIT | 
| Maintainer | Kowainik <xrom.xkov@gmail.com> | 
| Stability | Stable | 
| Portability | Portable | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
Relude.Functor.Reexport
Synopsis
- (<$>) :: Functor f => (a -> b) -> f a -> f b
 - class Functor (f :: Type -> Type) where
 - ($>) :: Functor f => f a -> b -> f b
 - void :: Functor f => f a -> f ()
 - module Data.Functor.Compose
 - module Data.Functor.Identity
 - module Data.Functor.Contravariant
 - module Data.Bifunctor
 
Reexport Functor
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #
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
Convert from a  to a Maybe Int using Maybe
 Stringshow:
>>>show <$> NothingNothing>>>show <$> Just 3Just "3"
Convert from an  to an
 Either Int IntEither IntString using show:
>>>show <$> Left 17Left 17>>>show <$> Right 17Right "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)
class Functor (f :: Type -> Type) where #
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:
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 https://www.schoolofhaskell.com/user/edwardk/snippets/fmap or
https://github.com/quchen/articles/blob/master/second_functor_law.md
for an explanation.
Minimal complete definition
Methods
fmap :: (a -> b) -> f a -> f b #
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  instance that allows
 both the last and the penultimate parameters to be mapped over.Bifunctor
Examples
Convert from a  to a Maybe IntMaybe String
 using show:
>>>fmap show NothingNothing>>>fmap show (Just 3)Just "3"
Convert from an  to an
 Either Int IntEither 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)
Instances
| Functor ZipList | Since: base-2.1  | 
| Functor Handler | Since: base-4.6.0.0  | 
| Functor Complex | Since: base-4.9.0.0  | 
| Functor Identity | Since: base-4.8.0.0  | 
| Functor First | Since: base-4.8.0.0  | 
| Functor Last | Since: base-4.8.0.0  | 
| Functor Down | Since: base-4.11.0.0  | 
| Functor First | Since: base-4.9.0.0  | 
| Functor Last | Since: base-4.9.0.0  | 
| Functor Max | Since: base-4.9.0.0  | 
| Functor Min | Since: base-4.9.0.0  | 
| Functor Dual | Since: base-4.8.0.0  | 
| Functor Product | Since: base-4.8.0.0  | 
| Functor Sum | Since: base-4.8.0.0  | 
| Functor NonEmpty | Since: base-4.9.0.0  | 
| Functor STM | Since: base-4.3.0.0  | 
| Functor NoIO | Since: base-4.8.0.0  | 
| Functor Par1 | Since: base-4.9.0.0  | 
| Functor ArgDescr | Since: base-4.7.0.0  | 
| Functor ArgOrder | Since: base-4.7.0.0  | 
| Functor OptDescr | Since: base-4.7.0.0  | 
| Functor P | Since: base-4.8.0.0  | 
Defined in Text.ParserCombinators.ReadP  | |
| Functor ReadP | Since: base-2.1  | 
| Functor ReadPrec | Since: base-2.1  | 
| Functor Put | |
| Functor SCC | Since: containers-0.5.4  | 
| Functor IntMap | |
| Functor Digit | |
| Functor Elem | |
| Functor FingerTree | |
Defined in Data.Sequence.Internal Methods fmap :: (a -> b) -> FingerTree a -> FingerTree b # (<$) :: a -> FingerTree b -> FingerTree a #  | |
| Functor Node | |
| Functor Seq | |
| Functor ViewL | |
| Functor ViewR | |
| Functor Tree | |
| Functor IO | Since: base-2.1  | 
| Functor AnnotDetails | |
Defined in Text.PrettyPrint.Annotated.HughesPJ Methods fmap :: (a -> b) -> AnnotDetails a -> AnnotDetails b # (<$) :: a -> AnnotDetails b -> AnnotDetails a #  | |
| Functor Doc | |
| Functor Span | |
| Functor Q | |
| Functor TyVarBndr | |
| Functor Maybe | Since: base-2.1  | 
| Functor Solo | Since: base-4.15  | 
| Functor [] | Since: base-2.1  | 
| Monad m => Functor (WrappedMonad m) | Since: base-2.1  | 
Defined in Control.Applicative Methods fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b # (<$) :: a -> WrappedMonad m b -> WrappedMonad m a #  | |
| Arrow a => Functor (ArrowMonad a) | Since: base-4.6.0.0  | 
Defined in Control.Arrow Methods fmap :: (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b # (<$) :: a0 -> ArrowMonad a b -> ArrowMonad a a0 #  | |
| Functor (Either a) | Since: base-3.0  | 
| Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0  | 
| Functor (Arg a) | Since: base-4.9.0.0  | 
| Functor (Array i) | Since: base-2.1  | 
| Functor (U1 :: Type -> Type) | Since: base-4.9.0.0  | 
| Functor (V1 :: Type -> Type) | Since: base-4.9.0.0  | 
| Functor (ST s) | Since: base-2.1  | 
| Functor (SetM s) | |
Defined in Data.Graph  | |
| Functor (Map k) | |
| Functor (IParser t) | |
| Functor f => Functor (Lift f) | |
| Functor m => Functor (MaybeT m) | |
| Functor (HashMap k) | |
| Functor ((,) a) | Since: base-2.1  | 
| Arrow a => Functor (WrappedArrow a b) | Since: base-2.1  | 
Defined in Control.Applicative Methods fmap :: (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 # (<$) :: a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 #  | |
| Functor m => Functor (Kleisli m a) | Since: base-4.14.0.0  | 
| Functor (Const m :: Type -> Type) | Since: base-2.1  | 
| Functor f => Functor (Ap f) | Since: base-4.12.0.0  | 
| Functor f => Functor (Alt f) | Since: base-4.8.0.0  | 
| (Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) | Since: base-4.17.0.0  | 
Defined in GHC.Generics Methods fmap :: (a -> b) -> Generically1 f a -> Generically1 f b # (<$) :: a -> Generically1 f b -> Generically1 f a #  | |
| Functor f => Functor (Rec1 f) | Since: base-4.9.0.0  | 
| Functor (URec (Ptr ()) :: Type -> Type) | Since: base-4.9.0.0  | 
| Functor (URec Char :: Type -> Type) | Since: base-4.9.0.0  | 
| Functor (URec Double :: Type -> Type) | Since: base-4.9.0.0  | 
| Functor (URec Float :: Type -> Type) | Since: base-4.9.0.0  | 
| Functor (URec Int :: Type -> Type) | Since: base-4.9.0.0  | 
| Functor (URec Word :: Type -> Type) | Since: base-4.9.0.0  | 
| (Applicative f, Monad f) => Functor (WhenMissing f x) | Since: containers-0.5.9  | 
Defined in Data.IntMap.Internal Methods fmap :: (a -> b) -> WhenMissing f x a -> WhenMissing f x b # (<$) :: a -> WhenMissing f x b -> WhenMissing f x a #  | |
| Functor (t m) => Functor (LiftingAccum t m) | Since: mtl-2.3  | 
Defined in Control.Monad.Accum Methods fmap :: (a -> b) -> LiftingAccum t m a -> LiftingAccum t m b # (<$) :: a -> LiftingAccum t m b -> LiftingAccum t m a #  | |
| Functor (t m) => Functor (LiftingSelect t m) | Since: mtl-2.3  | 
Defined in Control.Monad.Select Methods fmap :: (a -> b) -> LiftingSelect t m a -> LiftingSelect t m b # (<$) :: a -> LiftingSelect t m b -> LiftingSelect t m a #  | |
| Functor f => Functor (Backwards f) | Derived instance.  | 
| Functor m => Functor (AccumT w m) | |
| Functor m => Functor (ExceptT e m) | |
| Functor m => Functor (IdentityT m) | |
| Functor m => Functor (ReaderT r m) | |
| Functor m => Functor (SelectT r m) | |
| Functor m => Functor (StateT s m) | |
| Functor m => Functor (StateT s m) | |
| Functor m => Functor (WriterT w m) | |
| Functor m => Functor (WriterT w m) | |
| Functor m => Functor (WriterT w m) | |
| Functor (Constant a :: Type -> Type) | |
| Functor f => Functor (Reverse f) | Derived instance.  | 
| Functor ((,,) a b) | Since: base-4.14.0.0  | 
| (Functor f, Functor g) => Functor (Product f g) | Since: base-4.9.0.0  | 
| (Functor f, Functor g) => Functor (Sum f g) | Since: base-4.9.0.0  | 
| (Functor f, Functor g) => Functor (f :*: g) | Since: base-4.9.0.0  | 
| (Functor f, Functor g) => Functor (f :+: g) | Since: base-4.9.0.0  | 
| Functor (K1 i c :: Type -> Type) | Since: base-4.9.0.0  | 
| Functor f => Functor (WhenMatched f x y) | Since: containers-0.5.9  | 
Defined in Data.IntMap.Internal Methods fmap :: (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b # (<$) :: a -> WhenMatched f x y b -> WhenMatched f x y a #  | |
| (Applicative f, Monad f) => Functor (WhenMissing f k x) | Since: containers-0.5.9  | 
Defined in Data.Map.Internal Methods fmap :: (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b # (<$) :: a -> WhenMissing f k x b -> WhenMissing f k x a #  | |
| Functor (ContT r m) | |
| Functor ((,,,) a b c) | Since: base-4.14.0.0  | 
| Functor ((->) r) | Since: base-2.1  | 
| (Functor f, Functor g) => Functor (Compose f g) | Since: base-4.9.0.0  | 
| (Functor f, Functor g) => Functor (f :.: g) | Since: base-4.9.0.0  | 
| Functor f => Functor (M1 i c f) | Since: base-4.9.0.0  | 
| Functor f => Functor (WhenMatched f k x y) | Since: containers-0.5.9  | 
Defined in Data.Map.Internal Methods fmap :: (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b # (<$) :: a -> WhenMatched f k x y b -> WhenMatched f k x y a #  | |
| Functor m => Functor (RWST r w s m) | |
| Functor m => Functor (RWST r w s m) | |
| Functor m => Functor (RWST r w s m) | |
| Functor ((,,,,) a b c d) | Since: base-4.18.0.0  | 
| Functor ((,,,,,) a b c d e) | Since: base-4.18.0.0  | 
| Functor ((,,,,,,) a b c d e f) | Since: base-4.18.0.0  | 
($>) :: Functor f => f a -> b -> f b infixl 4 #
Flipped version of <$.
Examples
Replace the contents of a  with a constant
 Maybe IntString:
>>>Nothing $> "foo"Nothing>>>Just 90210 $> "foo"Just "foo"
Replace the contents of an 
 with a constant Either Int IntString, 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: base-4.7.0.0
void :: Functor f => f a -> f () #
 discards or ignores the result of evaluation, such
 as the return value of an void valueIO action.
Examples
Replace the contents of a  with unit:Maybe Int
>>>void NothingNothing>>>void (Just 3)Just ()
Replace the contents of an 
 with unit, resulting in an Either Int Int: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
module Data.Functor.Compose
module Data.Functor.Identity
module Data.Functor.Contravariant
Reexport Bifunctor
module Data.Bifunctor