Copyright | (c) Tom Harding 2019 |
---|---|
License | MIT |
Maintainer | tom.harding@habito.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- module Data.Generic.HKD.Types
- module Data.Generic.HKD.Named
- module Data.Generic.HKD.Labels
- module Data.Generic.HKD.Construction
- module Data.Generic.HKD.Build
- class FunctorB b => ApplicativeB (b :: (k -> Type) -> Type) where
- class FunctorB b => ConstraintsB (b :: (k -> Type) -> Type) where
- type AllB (c :: k -> Constraint) (b :: (k -> Type) -> Type)
- baddDicts :: forall (c :: k -> Constraint) (f :: k -> Type). AllB c b => b f -> b (Product (Dict c) f)
- class FunctorB (b :: (k -> Type) -> Type) where
- bmap :: (forall (a :: k). f a -> g a) -> b f -> b g
- class FunctorB b => TraversableB (b :: (k -> Type) -> Type) where
- btraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> b f -> e (b g)
- position :: forall index f structure inner. HasPosition' index (HKD structure f) (f inner) => Lens' (HKD structure f) (f inner)
- field :: forall field f structure inner. HasField' field (HKD structure f) (f inner) => Lens' (HKD structure f) (f inner)
Documentation
module Data.Generic.HKD.Types
module Data.Generic.HKD.Named
module Data.Generic.HKD.Labels
module Data.Generic.HKD.Build
class FunctorB b => ApplicativeB (b :: (k -> Type) -> Type) where #
A FunctorB
with application, providing operations to:
It should satisfy the following laws:
- Naturality of
bprod
bmap
((Pair
a b) ->Pair
(f a) (g b)) (u `bprod
` v) =bmap
f u `bprod
`bmap
g v
- Left and right identity
bmap
((Pair
_ b) -> b) (bpure
e `bprod
` v) = vbmap
((Pair
a _) -> a) (u `bprod
`bpure
e) = u
- Associativity
bmap
((Pair
a (Pair
b c)) ->Pair
(Pair
a b) c) (u `bprod
` (v `bprod
` w)) = (u `bprod
` v) `bprod
` w
It is to FunctorB
in the same way as Applicative
relates to Functor
. For a presentation of Applicative
as
a monoidal functor, see Section 7 of
Applicative Programming with Effects.
There is a default implementation of bprod
and bpure
based on Generic
.
Intuitively, it works on types where the value of bpure
is uniquely defined.
This corresponds rougly to record types (in the presence of sums, there would
be several candidates for bpure
), where every field is either a Monoid
or
covered by the argument f
.
Nothing
bpure :: (forall (a :: k). f a) -> b f #
bprod :: forall (f :: k -> Type) (g :: k -> Type). b f -> b g -> b (Product f g) #
Instances
(FunctorB (HKD structure), GApplicativeB (Rep structure)) => ApplicativeB (HKD structure :: (Type -> Type) -> Type) Source # | |
ApplicativeB (Unit :: (k -> Type) -> Type) | |
ApplicativeB (Proxy :: (k -> Type) -> Type) | |
ApplicativeB b => ApplicativeB (Barbie b :: (k -> Type) -> Type) | |
Monoid a => ApplicativeB (Constant a :: (k -> Type) -> Type) | |
Monoid a => ApplicativeB (Const a :: (k -> Type) -> Type) | |
(ApplicativeB a, ApplicativeB b) => ApplicativeB (Product a b :: (k -> Type) -> Type) | |
class FunctorB b => ConstraintsB (b :: (k -> Type) -> Type) where #
Instances of this class provide means to talk about constraints,
both at compile-time, using AllB
, and at run-time, in the form
of Dict
, via baddDicts
.
A manual definition would look like this:
data T f = A (fInt
) (fString
) | B (fBool
) (fInt
) instanceConstraintsB
T where typeAllB
c T = (cInt
, cString
, cBool
)baddDicts
t = case t of A x y -> A (Pair
Dict
x) (Pair
Dict
y) B z w -> B (Pair
Dict
z) (Pair
Dict
w)
Now, when we given a T f
, if we need to use the Show
instance of
their fields, we can use:
baddDicts
:: AllB Show b => b f -> b (Dict
Show
`Product
` f)
There is a default implementation of ConstraintsB
for
Generic
types, so in practice one will simply do:
derive instanceGeneric
(T f) instanceConstraintsB
T
Nothing
type AllB (c :: k -> Constraint) (b :: (k -> Type) -> Type) #
baddDicts :: forall (c :: k -> Constraint) (f :: k -> Type). AllB c b => b f -> b (Product (Dict c) f) #
Instances
(FunctorB (HKD structure), GConstraintsB (Rep structure), GAllBC (Rep structure)) => ConstraintsB (HKD structure :: (Type -> Type) -> Type) Source # | |
ConstraintsB (Void :: (k -> Type) -> Type) | |
ConstraintsB (Unit :: (k -> Type) -> Type) | |
ConstraintsB (Proxy :: (k -> Type) -> Type) | |
ConstraintsB b => ConstraintsB (Barbie b :: (k -> Type) -> Type) | |
ConstraintsB (Const a :: (k -> Type) -> Type) | |
(ConstraintsB a, ConstraintsB b) => ConstraintsB (Sum a b :: (k -> Type) -> Type) | |
(ConstraintsB a, ConstraintsB b) => ConstraintsB (Product a b :: (k -> Type) -> Type) | |
(Functor f, ConstraintsB b) => ConstraintsB (Compose f b :: (k -> Type) -> Type) | |
class FunctorB (b :: (k -> Type) -> Type) where #
Barbie-types that can be mapped over. Instances of FunctorB
should
satisfy the following laws:
bmap
id
=id
bmap
f .bmap
g =bmap
(f . g)
There is a default bmap
implementation for Generic
types, so
instances can derived automatically.
Nothing
Instances
GFunctorB (Rep structure) => FunctorB (HKD structure :: (Type -> Type) -> Type) Source # | |
Defined in Data.Generic.HKD.Types | |
FunctorB (Void :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.Trivial | |
FunctorB (Unit :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.Trivial | |
FunctorB (Proxy :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.FunctorB | |
FunctorB b => FunctorB (Barbie b :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.Wrappers | |
FunctorB (Constant x :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.FunctorB | |
FunctorB (Const x :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.FunctorB | |
(FunctorB a, FunctorB b) => FunctorB (Sum a b :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.FunctorB | |
(FunctorB a, FunctorB b) => FunctorB (Product a b :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.FunctorB | |
(Functor f, FunctorB b) => FunctorB (Compose f b :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.FunctorB |
class FunctorB b => TraversableB (b :: (k -> Type) -> Type) where #
Barbie-types that can be traversed from left to right. Instances should satisfy the following laws:
t .btraverse
f =btraverse
(t . f) -- naturalitybtraverse
Identity
=Identity
-- identitybtraverse
(Compose
.fmap
g . f) =Compose
.fmap
(btraverse
g) .btraverse
f -- composition
There is a default btraverse
implementation for Generic
types, so
instances can derived automatically.
Nothing
btraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> b f -> e (b g) #
Instances
(FunctorB (HKD structure), GTraversableB (Rep structure)) => TraversableB (HKD structure :: (Type -> Type) -> Type) Source # | |
Defined in Data.Generic.HKD.Types btraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> HKD structure f -> e (HKD structure g) # | |
TraversableB (Void :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.Trivial btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Void f -> e (Void g) # | |
TraversableB (Unit :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.Trivial btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Unit f -> e (Unit g) # | |
TraversableB (Proxy :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.TraversableB btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Proxy f -> e (Proxy g) # | |
TraversableB b => TraversableB (Barbie b :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.Wrappers btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Barbie b f -> e (Barbie b g) # | |
TraversableB (Constant a :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.TraversableB btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Constant a f -> e (Constant a g) # | |
TraversableB (Const a :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.TraversableB btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Const a f -> e (Const a g) # | |
(TraversableB a, TraversableB b) => TraversableB (Sum a b :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.TraversableB btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Sum a b f -> e (Sum a b g) # | |
(TraversableB a, TraversableB b) => TraversableB (Product a b :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.TraversableB btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Product a b f -> e (Product a b g) # | |
(Traversable f, TraversableB b) => TraversableB (Compose f b :: (k -> Type) -> Type) | |
Defined in Barbies.Internal.TraversableB btraverse :: Applicative e => (forall (a :: k0). f0 a -> e (g a)) -> Compose f b f0 -> e (Compose f b g) # |
position :: forall index f structure inner. HasPosition' index (HKD structure f) (f inner) => Lens' (HKD structure f) (f inner) Source #
Product types without named fields can't be addressed by field name (for very obvious reason), so we instead need to address them with their "position" index. This is a one-indexed type-applied natural:
>>>
import Control.Lens ((^.))
>>>
:t mempty @(HKD (Int, String) []) ^. position @1
mempty @(HKD (Int, String) []) ^. position @1 :: [Int]
As we're using the wonderful generic-lens
library under the hood, we also
get some beautiful error messages when things go awry:
>>>
import Data.Generic.HKD.Construction
>>>
deconstruct ("Hello", True) ^. position @4
... ... error: ... The type HKD ... ([Char], Bool) f does not contain a field at position 4 ...
field :: forall field f structure inner. HasField' field (HKD structure f) (f inner) => Lens' (HKD structure f) (f inner) Source #
When we work with records, all the fields are named, and we can refer to
them using these names. This class provides a lens from our HKD structure to
any f
-wrapped field.
>>>
:set -XDataKinds -XDeriveGeneric -XTypeApplications
>>>
import Control.Lens ((&), (.~))
>>>
import Data.Monoid (Last)
>>>
import GHC.Generics
>>>
data User = User { name :: String, age :: Int } deriving (Generic, Show)
>>>
type Partial a = HKD a Last
We can create an empty partial User
and set its name to "Tom" (which, in
this case, is pure "Tom" :: Last String
):
>>>
mempty @(Partial User) & field @"name" .~ pure "Tom"
User {name = Last {getLast = Just "Tom"}, age = Last {getLast = Nothing}}
Thanks to some generic-lens
magic, we also get some pretty magical type
errors! If we create a (complete) partial user:
>>>
import Data.Generic.HKD.Construction (deconstruct)
>>>
total = deconstruct @Last (User "Tom" 25)
... and then try to access a field that isn't there, we get a friendly message to point us in the right direction:
>>>
total & field @"oops" .~ pure ()
... ... error: ... The type HKD User Last does not contain a field named 'oops'. ...