Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
The data functor hierarchy
This module defines the data functor library. Unlike in the case of non-linear, unrestricted, functors, there is a split between data functors, which represent containers, and control functors which represent effects. Please read this blog post. For more details, see Control.Functor.Linear.
- Linear data functors should be thought of as containers of data.
- Linear data applicative functors should be thought of as containers that can be zipped.
- Linear data traversable functors should be thought of as containers which store a finite number of values.
This module also defines genericTraverse
for types implementing
Generic1
.
Synopsis
- class Functor f where
- fmap :: (a %1 -> b) -> f a %1 -> f b
- (<$>) :: Functor f => (a %1 -> b) -> f a %1 -> f b
- (<$) :: (Functor f, Consumable b) => a -> f b %1 -> f a
- void :: (Functor f, Consumable a) => f a %1 -> f ()
- class Functor f => Applicative f where
- newtype Const a (b :: k) = Const {
- getConst :: a
- class Functor t => Traversable t where
- traverse :: Applicative f => (a %1 -> f b) -> t a %1 -> f (t b)
- sequence :: Applicative f => t (f a) %1 -> f (t a)
- genericTraverse :: (Generic1 t, GTraversable (Rep1 t), Applicative f) => (a %1 -> f b) -> t a %1 -> f (t b)
- class GTraversable t
- mapM :: (Traversable t, Monad m) => (a %1 -> m b) -> t a %1 -> m (t b)
- sequenceA :: (Traversable t, Applicative f) => t (f a) %1 -> f (t a)
- for :: (Traversable t, Applicative f) => t a %1 -> (a %1 -> f b) -> f (t b)
- forM :: (Traversable t, Monad m) => t a %1 -> (a %1 -> m b) -> m (t b)
- mapAccumL :: Traversable t => (a %1 -> b %1 -> (a, c)) -> a %1 -> t b %1 -> (a, t c)
- mapAccumR :: Traversable t => (a %1 -> b %1 -> (a, c)) -> a %1 -> t b %1 -> (a, t c)
Data Functor Hierarchy
class Functor f where Source #
Linear Data Functors should be thought of as containers holding values of
type a
over which you are able to apply a linear function of type a %1->
b
on each value of type a
in the functor and consume a given functor
of type f a
.
Instances
(<$) :: (Functor f, Consumable b) => a -> f b %1 -> f a infixl 4 Source #
Replace all occurances of b
with the given a
and consume the functor f b
.
void :: (Functor f, Consumable a) => f a %1 -> f () Source #
Discard a consumable value stored in a data functor.
class Functor f => Applicative f where Source #
Data Applicative
-s can be seen as containers which can be zipped
together. A prime example of data Applicative
are vectors of known length
(ZipList
s would be, if it were not for the fact that zipping them together
drops values, which we are not allowed to do in a linear container).
In fact, an applicative functor is precisely a functor equipped with (pure
and) liftA2 :: (a %1-> b %1-> c) -> f a %1-> f b %1-> f c
. In the case where
f = []
, the signature of liftA2
would specialise to that of zipWith
.
Intuitively, the type of liftA2
means that Applicative
s can be seen as
containers whose "number" of elements is known at compile-time. This
includes vectors of known length but excludes Maybe
, since this may
contain either zero or one value. Similarly, ((->) r)
forms a Data
Applicative
, since this is a (possibly infinitary) container indexed by
r
, while lists do not, since they may contain any number of elements.
Remarks for the mathematically inclined
An Applicative
is, as in the restricted case, a lax monoidal endofunctor of
the category of linear types. That is, it is equipped with
- a (linear) function
() %1-> f ()
- a (linear) natural transformation
(f a, f b) %1-> f (a, b)
It is a simple exercise to verify that these are equivalent to the definition
of Applicative
. Hence that the choice of linearity of the various arrow is
indeed natural.
(<*>) :: f (a %1 -> b) %1 -> f a %1 -> f b infixl 4 Source #
liftA2 :: (a %1 -> b %1 -> c) -> f a %1 -> f b %1 -> f c Source #
Instances
The Const
functor.
Instances
Strong Either Void (CoKleisli (Const x :: Type -> Type)) Source # | |
Generic1 (Const a :: k -> Type) | |
Bifunctor (Const :: Type -> Type -> Type) | Since: base-4.8.0.0 |
Eq2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Ord2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Const a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Const a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Const a b] # | |
Show2 (Const :: Type -> TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Hashable2 (Const :: Type -> Type -> Type) | |
Defined in Data.Hashable.Class | |
Foldable (Const m :: TYPE LiftedRep -> Type) | Since: base-4.7.0.0 |
Defined in Data.Functor.Const fold :: Monoid m0 => Const m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 # foldMap' :: Monoid m0 => (a -> m0) -> Const m a -> m0 # foldr :: (a -> b -> b) -> b -> Const m a -> b # foldr' :: (a -> b -> b) -> b -> Const m a -> b # foldl :: (b -> a -> b) -> b -> Const m a -> b # foldl' :: (b -> a -> b) -> b -> Const m a -> b # foldr1 :: (a -> a -> a) -> Const m a -> a # foldl1 :: (a -> a -> a) -> Const m a -> a # elem :: Eq a => a -> Const m a -> Bool # maximum :: Ord a => Const m a -> a # minimum :: Ord a => Const m a -> a # | |
Eq a => Eq1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Ord a => Ord1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read a => Read1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show a => Show1 (Const a :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Traversable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
Functor (Const m :: Type -> Type) | Since: base-2.1 |
Hashable a => Hashable1 (Const a :: Type -> Type) | |
Defined in Data.Hashable.Class | |
Monoid x => Applicative (Const x :: Type -> Type) Source # | |
Functor (Const x :: Type -> Type) Source # | |
Traversable (Const a :: Type -> Type) Source # | |
Defined in Data.Functor.Linear.Internal.Traversable | |
IsString a => IsString (Const a b) | Since: base-4.9.0.0 |
Defined in Data.String fromString :: String -> Const a b # | |
Storable a => Storable (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Const a b) | Since: base-4.9.0.0 |
Bits a => Bits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const (.&.) :: Const a b -> Const a b -> Const a b # (.|.) :: Const a b -> Const a b -> Const a b # xor :: Const a b -> Const a b -> Const a b # complement :: Const a b -> Const a b # shift :: Const a b -> Int -> Const a b # rotate :: Const a b -> Int -> Const a b # setBit :: Const a b -> Int -> Const a b # clearBit :: Const a b -> Int -> Const a b # complementBit :: Const a b -> Int -> Const a b # testBit :: Const a b -> Int -> Bool # bitSizeMaybe :: Const a b -> Maybe Int # isSigned :: Const a b -> Bool # shiftL :: Const a b -> Int -> Const a b # unsafeShiftL :: Const a b -> Int -> Const a b # shiftR :: Const a b -> Int -> Const a b # unsafeShiftR :: Const a b -> Int -> Const a b # rotateL :: Const a b -> Int -> Const a b # | |
FiniteBits a => FiniteBits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const finiteBitSize :: Const a b -> Int # countLeadingZeros :: Const a b -> Int # countTrailingZeros :: Const a b -> Int # | |
Bounded a => Bounded (Const a b) | Since: base-4.9.0.0 |
Enum a => Enum (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const succ :: Const a b -> Const a b # pred :: Const a b -> Const a b # fromEnum :: Const a b -> Int # enumFrom :: Const a b -> [Const a b] # enumFromThen :: Const a b -> Const a b -> [Const a b] # enumFromTo :: Const a b -> Const a b -> [Const a b] # enumFromThenTo :: Const a b -> Const a b -> Const a b -> [Const a b] # | |
Floating a => Floating (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const exp :: Const a b -> Const a b # log :: Const a b -> Const a b # sqrt :: Const a b -> Const a b # (**) :: Const a b -> Const a b -> Const a b # logBase :: Const a b -> Const a b -> Const a b # sin :: Const a b -> Const a b # cos :: Const a b -> Const a b # tan :: Const a b -> Const a b # asin :: Const a b -> Const a b # acos :: Const a b -> Const a b # atan :: Const a b -> Const a b # sinh :: Const a b -> Const a b # cosh :: Const a b -> Const a b # tanh :: Const a b -> Const a b # asinh :: Const a b -> Const a b # acosh :: Const a b -> Const a b # atanh :: Const a b -> Const a b # log1p :: Const a b -> Const a b # expm1 :: Const a b -> Const a b # | |
RealFloat a => RealFloat (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const floatRadix :: Const a b -> Integer # floatDigits :: Const a b -> Int # floatRange :: Const a b -> (Int, Int) # decodeFloat :: Const a b -> (Integer, Int) # encodeFloat :: Integer -> Int -> Const a b # exponent :: Const a b -> Int # significand :: Const a b -> Const a b # scaleFloat :: Int -> Const a b -> Const a b # isInfinite :: Const a b -> Bool # isDenormalized :: Const a b -> Bool # isNegativeZero :: Const a b -> Bool # | |
Generic (Const a b) | |
Ix a => Ix (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const range :: (Const a b, Const a b) -> [Const a b] # index :: (Const a b, Const a b) -> Const a b -> Int # unsafeIndex :: (Const a b, Const a b) -> Const a b -> Int # inRange :: (Const a b, Const a b) -> Const a b -> Bool # rangeSize :: (Const a b, Const a b) -> Int # unsafeRangeSize :: (Const a b, Const a b) -> Int # | |
Num a => Num (Const a b) | Since: base-4.9.0.0 |
Read a => Read (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
Fractional a => Fractional (Const a b) | Since: base-4.9.0.0 |
Integral a => Integral (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Real a => Real (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const toRational :: Const a b -> Rational # | |
RealFrac a => RealFrac (Const a b) | Since: base-4.9.0.0 |
Show a => Show (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
Eq a => Eq (Const a b) | Since: base-4.9.0.0 |
Ord a => Ord (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Hashable a => Hashable (Const a b) | |
Defined in Data.Hashable.Class | |
Monoid a => Monoid (Const a b) Source # | |
Defined in Data.Monoid.Linear.Internal.Monoid | |
Semigroup a => Semigroup (Const a b) Source # | |
type Rep1 (Const a :: k -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
type Rep1 (Const a :: k -> Type) | |
Defined in Generics.Linear.Instances.Base | |
type Rep (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
type Rep (Const a b) | |
Defined in Generics.Linear.Instances.Base |
Linear traversable hierarchy
class Functor t => Traversable t where Source #
A linear data traversible is a functor of type t a
where you can apply a
linear effectful action of type a %1-> f b
on each value of type a
and
compose this to perform an action on the whole functor, resulting in a value
of type f (t b)
.
To learn more about Traversable
, see here:
- "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.
traverse :: Applicative f => (a %1 -> f b) -> t a %1 -> f (t b) Source #
sequence :: Applicative f => t (f a) %1 -> f (t a) Source #
Instances
genericTraverse :: (Generic1 t, GTraversable (Rep1 t), Applicative f) => (a %1 -> f b) -> t a %1 -> f (t b) Source #
Implementation of traverse
for types which derive
(linear) Generic1
.
### Performance note
At present, this function does not perform well for recursive types like lists; it will not specialize to either
### Example
data T $(deriveGeneric1 ''T) instance Traversable T where traverse = genericTraverse
Note that, contrary to many other classes in linear-base, we can't define
`Traversable T` using deriving via, because the
role
of t
, in the type of traverse
, is nominal.
class GTraversable t Source #
This type class derives the definition of genericTraverse
by induction on
the generic representation of a type.
gtraverse
Instances
mapM :: (Traversable t, Monad m) => (a %1 -> m b) -> t a %1 -> m (t b) Source #
sequenceA :: (Traversable t, Applicative f) => t (f a) %1 -> f (t a) Source #
for :: (Traversable t, Applicative f) => t a %1 -> (a %1 -> f b) -> f (t b) Source #
forM :: (Traversable t, Monad m) => t a %1 -> (a %1 -> m b) -> m (t b) Source #
mapAccumL :: Traversable t => (a %1 -> b %1 -> (a, c)) -> a %1 -> t b %1 -> (a, t c) Source #
mapAccumR :: Traversable t => (a %1 -> b %1 -> (a, c)) -> a %1 -> t b %1 -> (a, t c) Source #