| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Vinyl.Functor
Synopsis
- newtype Identity a = Identity {- getIdentity :: a
 
- data Thunk a = Thunk {- getThunk :: a
 
- newtype Lift (op :: l -> l' -> *) (f :: k -> l) (g :: k -> l') (x :: k) = Lift {- getLift :: op (f x) (g x)
 
- data ElField (field :: (Symbol, Type)) where- Field :: KnownSymbol s => !t -> ElField '(s, t)
 
- newtype Compose (f :: l -> *) (g :: k -> l) (x :: k) = Compose {- getCompose :: f (g x)
 
- onCompose :: (f (g a) -> h (k a)) -> (f :. g) a -> (h :. k) a
- type (:.) f g = Compose f g
- newtype Const (a :: *) (b :: k) = Const {- getConst :: a
 
Introduction
This module provides functors and functor compositions
    that can be used as the interpretation function for a
    Rec. For a more full discussion of this, scroll down
    to the bottom.
This is identical to the Identity from Data.Functor.Identity
 in "base" except for its Show instance.
Constructors
| Identity | |
| Fields 
 | |
Instances
Used this instead of Identity to make a record
   lazy in its fields.
Instances
| Monad Thunk Source # | |
| Functor Thunk Source # | |
| Applicative Thunk Source # | |
| Foldable Thunk Source # | |
| Defined in Data.Vinyl.Functor Methods fold :: Monoid m => Thunk m -> m # foldMap :: Monoid m => (a -> m) -> Thunk a -> m # foldr :: (a -> b -> b) -> b -> Thunk a -> b # foldr' :: (a -> b -> b) -> b -> Thunk a -> b # foldl :: (b -> a -> b) -> b -> Thunk a -> b # foldl' :: (b -> a -> b) -> b -> Thunk a -> b # foldr1 :: (a -> a -> a) -> Thunk a -> a # foldl1 :: (a -> a -> a) -> Thunk a -> a # elem :: Eq a => a -> Thunk a -> Bool # maximum :: Ord a => Thunk a -> a # minimum :: Ord a => Thunk a -> a # | |
| Traversable Thunk Source # | |
| Show a => Show (Thunk a) Source # | |
newtype Lift (op :: l -> l' -> *) (f :: k -> l) (g :: k -> l') (x :: k) Source #
Instances
| (IsoHKD f a, IsoHKD g a) => IsoHKD (Lift ((->) :: Type -> Type -> Type) f g :: k -> Type) (a :: k) Source # | Work with values of type  | 
| (Functor f, Functor g) => Functor (Lift Either f g) Source # | |
| (Functor f, Functor g) => Functor (Lift (,) f g) Source # | |
| (Applicative f, Applicative g) => Applicative (Lift (,) f g) Source # | |
| Defined in Data.Vinyl.Functor | |
| type HKD (Lift ((->) :: Type -> Type -> Type) f g :: k -> Type) (a :: k) Source # | |
data ElField (field :: (Symbol, Type)) where Source #
A value with a phantom Symbol label. It is not a
 Haskell Functor, but it is used in many of the same places a
 Functor is used in vinyl.
Constructors
| Field :: KnownSymbol s => !t -> ElField '(s, t) | 
Instances
newtype Compose (f :: l -> *) (g :: k -> l) (x :: k) Source #
Constructors
| Compose | |
| Fields 
 | |
Instances
| (IsoHKD f (HKD g a), IsoHKD g a, Functor f) => IsoHKD (Compose f g :: k -> Type) (a :: k) Source # | Work with values of type  | 
| (Functor f, Functor g) => Functor (Compose f g) Source # | |
| (Applicative f, Applicative g) => Applicative (Compose f g) Source # | |
| Defined in Data.Vinyl.Functor | |
| (Foldable f, Foldable g) => Foldable (Compose f g) Source # | |
| Defined in Data.Vinyl.Functor Methods fold :: Monoid m => Compose f g m -> m # foldMap :: Monoid m => (a -> m) -> Compose f g a -> m # foldr :: (a -> b -> b) -> b -> Compose f g a -> b # foldr' :: (a -> b -> b) -> b -> Compose f g a -> b # foldl :: (b -> a -> b) -> b -> Compose f g a -> b # foldl' :: (b -> a -> b) -> b -> Compose f g a -> b # foldr1 :: (a -> a -> a) -> Compose f g a -> a # foldl1 :: (a -> a -> a) -> Compose f g a -> a # toList :: Compose f g a -> [a] # null :: Compose f g a -> Bool # length :: Compose f g a -> Int # elem :: Eq a => a -> Compose f g a -> Bool # maximum :: Ord a => Compose f g a -> a # minimum :: Ord a => Compose f g a -> a # | |
| (Traversable f, Traversable g) => Traversable (Compose f g) Source # | |
| Defined in Data.Vinyl.Functor | |
| Show (f (g a)) => Show (Compose f g a) Source # | |
| Generic (Compose f g x) Source # | |
| Semigroup (f (g a)) => Semigroup (Compose f g a) Source # | |
| Monoid (f (g a)) => Monoid (Compose f g a) Source # | |
| Storable (f (g x)) => Storable (Compose f g x) Source # | |
| Defined in Data.Vinyl.Functor Methods sizeOf :: Compose f g x -> Int # alignment :: Compose f g x -> Int # peekElemOff :: Ptr (Compose f g x) -> Int -> IO (Compose f g x) # pokeElemOff :: Ptr (Compose f g x) -> Int -> Compose f g x -> IO () # peekByteOff :: Ptr b -> Int -> IO (Compose f g x) # pokeByteOff :: Ptr b -> Int -> Compose f g x -> IO () # | |
| type HKD (Compose f g :: k -> Type) (a :: k) Source # | |
| type Rep (Compose f g x) Source # | |
| Defined in Data.Vinyl.Functor | |
newtype Const (a :: *) (b :: k) Source #
Instances
| Functor (Const a :: Type -> Type) Source # | |
| Foldable (Const a :: Type -> Type) Source # | |
| Defined in Data.Vinyl.Functor Methods fold :: Monoid m => Const a m -> m # foldMap :: Monoid m => (a0 -> m) -> Const a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Const a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Const a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Const a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Const a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Const a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Const a a0 -> a0 # toList :: Const a a0 -> [a0] # elem :: Eq a0 => a0 -> Const a a0 -> Bool # maximum :: Ord a0 => Const a a0 -> a0 # minimum :: Ord a0 => Const a a0 -> a0 # | |
| Traversable (Const a :: Type -> Type) Source # | |
| Eq a => Eq (Const a b) Source # | |
| Show a => Show (Const a b) Source # | |
| Generic (Const a b) Source # | |
| Storable a => Storable (Const a b) Source # | |
| Defined in Data.Vinyl.Functor | |
| type Rep (Const a b) Source # | |
| Defined in Data.Vinyl.Functor | |
Discussion
Example
The data types in this module are used to build interpretation
    fuctions for a Rec. To build a Rec that is simply a heterogeneous
    list, use Identity:
>>>:{let myRec1 :: Rec Identity '[Int,Bool,Char] myRec1 = Identity 4 :& Identity True :& Identity 'c' :& RNil :}
For a record in which the fields are optional, you could alternatively write:
>>>:{let myRec2 :: Rec Maybe '[Int,Bool,Char] myRec2 = Just 4 :& Nothing :& Nothing :& RNil :}
And we can gather all of the effects with rtraverse:
>>>let r2 = rtraverse (fmap Identity) myRec2>>>:t r2r2 :: Maybe (Rec Identity '[Int, Bool, Char])>>>r2Nothing
If the fields only exist once an environment is provided, you can build the record as follows:
>>>:{let myRec3 :: Rec ((->) Int) '[Int,Bool,Char] myRec3 = (+5) :& (const True) :& (head . show) :& RNil :}
And again, we can collect these effects with "rtraverse":
>>>(rtraverse (fmap Identity) myRec3) 8{13, True, '8'}
If you want the composition of these two effects, you can use Compose:
>>>import Data.Char (chr)>>>:{let safeDiv a b = if b == 0 then Nothing else Just (div a b) safeChr i = if i >= 32 && i <= 126 then Just (chr i) else Nothing myRec4 :: Rec (Compose ((->) Int) Maybe) '[Int,Char] myRec4 = (Compose $ safeDiv 42) :& (Compose safeChr) :& RNil :}
Ecosystem
Of the five data types provided by this modules, three can be found in others places: Identity, Compose, and Const. They are included with "vinyl" to help keep the dependency list small. The differences will be discussed here.
The Data.Functor.Identity module was originally provided
    by "transformers". When GHC 7.10 was released, it was moved
    into "base-4.8". The Identity data type provided by that
    module is well recognized across the haskell ecosystem
    and has typeclass instances for lots of common typeclasses.
    The significant difference between it and the copy of
    it provided here is that this one has a different Show
    instance. This is illustrated below:
>>>Identity "hello""hello"
But, when using Identity from "base":
>>>import qualified Data.Functor.Identity as Base>>>Base.Identity "hello"Identity "hello"
This Show instance makes records look nicer in GHCi.
    Feel free to use Data.Functor.Identity if you do not
    need the prettier output or if you need the many additional
    typeclass instances that are provided for the standard
    Identity.
The story with Compose and Const is much more simple.
    These also exist in "transformers", although Const
    is named Constant there. Prior to the release of
    "transformers-0.5", they were not polykinded, making
    them unusable for certain universes. However, in
    "transformers-0.5" and forward, they have been made
    polykinded. This means that they are just as usable with Rec
    as the vinyl equivalents but with many more typeclass
    instances such as Ord and Show.