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 => ConstraintsB (b :: (k -> Type) -> Type) where
- type AllB (c :: k -> Constraint) (b :: (k -> Type) -> Type) :: Constraint
- baddDicts :: 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 (ConstraintsB b, ProductB b) => ProductBC (b :: (k -> Type) -> Type) where
- class FunctorB b => TraversableB (b :: (k -> Type) -> Type) where
- btraverse :: Applicative t => (forall (a :: k). f a -> t (g a)) -> b f -> t (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 => 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 if we given a T f
, we need to use the Show
instance of
their fields, we can use:
baddDicts
:: AllB Show b => b f -> b (Dict
Show
Product
b)
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) :: Constraint #
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 (Proxy :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Internal.Functor | |
FunctorB (Void :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Trivial | |
FunctorB (Unit :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Trivial | |
FunctorB (Const x :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Internal.Functor | |
FunctorB b => FunctorB (Barbie b :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Internal.Instances | |
(FunctorB a, FunctorB b) => FunctorB (Sum a b :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Internal.Functor | |
(FunctorB a, FunctorB b) => FunctorB (Product a b :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Internal.Functor | |
(Functor f, FunctorB b) => FunctorB (Compose f b :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Internal.Functor |
class (ConstraintsB b, ProductB b) => ProductBC (b :: (k -> Type) -> Type) where #
Every type b
that is an instance of both ProductB
and
ConstraintsB
can be made an instance of ProductBC
as well.
Intuitively, in addition to buniq
from ProductB
, one
can define buniqC
that takes into account constraints:
buniq
:: (forall a . f a) -> b fbuniqC
::AllB
c b => (forall a . c a => f a) -> b f
For technical reasons, buniqC
is not currently provided
as a method of this class and is instead defined in terms
bdicts
, which is similar to baddDicts
but can produce the
instance dictionaries out-of-the-blue. bdicts
could also be
defined in terms of buniqC
, so they are essentially equivalent.
bdicts
:: forall c b .AllB
c b => b (Dict
c)bdicts
=buniqC
(Dict
@c)
There is a default implementation for Generic
types, so
instances can derived automatically.
Nothing
Instances
(ProductB (HKD structure), ConstraintsB (HKD structure), GProductBC (Rep structure)) => ProductBC (HKD structure :: (Type -> Type) -> Type) Source # | |
ProductBC (Proxy :: (k -> Type) -> Type) | |
ProductBC (Unit :: (k -> Type) -> Type) | |
ProductBC b => ProductBC (Barbie b :: (k -> Type) -> Type) | |
(ProductBC a, ProductBC b) => ProductBC (Product a b :: (k -> Type) -> Type) | |
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 t => (forall (a :: k). f a -> t (g a)) -> b f -> t (b g) #
Instances
(FunctorB (HKD structure), GTraversableB (Rep structure)) => TraversableB (HKD structure :: (Type -> Type) -> Type) Source # | |
Defined in Data.Generic.HKD.Types btraverse :: Applicative t => (forall (a :: k). f a -> t (g a)) -> HKD structure f -> t (HKD structure g) # | |
TraversableB (Proxy :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Internal.Traversable btraverse :: Applicative t => (forall (a :: k0). f a -> t (g a)) -> Proxy f -> t (Proxy g) # | |
TraversableB (Void :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Trivial btraverse :: Applicative t => (forall (a :: k0). f a -> t (g a)) -> Void f -> t (Void g) # | |
TraversableB (Unit :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Trivial btraverse :: Applicative t => (forall (a :: k0). f a -> t (g a)) -> Unit f -> t (Unit g) # | |
TraversableB (Const a :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Internal.Traversable btraverse :: Applicative t => (forall (a0 :: k0). f a0 -> t (g a0)) -> Const a f -> t (Const a g) # | |
TraversableB b => TraversableB (Barbie b :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Internal.Instances btraverse :: Applicative t => (forall (a :: k0). f a -> t (g a)) -> Barbie b f -> t (Barbie b g) # | |
(TraversableB a, TraversableB b) => TraversableB (Sum a b :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Internal.Traversable btraverse :: Applicative t => (forall (a0 :: k0). f a0 -> t (g a0)) -> Sum a b f -> t (Sum a b g) # | |
(TraversableB a, TraversableB b) => TraversableB (Product a b :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Internal.Traversable btraverse :: Applicative t => (forall (a0 :: k0). f a0 -> t (g a0)) -> Product a b f -> t (Product a b g) # | |
(Traversable f, TraversableB b) => TraversableB (Compose f b :: (k -> Type) -> Type) | |
Defined in Data.Barbie.Internal.Traversable btraverse :: Applicative t => (forall (a :: k0). f0 a -> t (g a)) -> Compose f b f0 -> t (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'. ...