higgledy-0.4.1.1: Partial types as a type constructor.
Copyright(c) Tom Harding 2019
LicenseMIT
Maintainertom.harding@habito.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.Generic.HKD

Description

 
Synopsis

Documentation

class FunctorB b => ApplicativeB (b :: (k -> Type) -> Type) where #

A FunctorB with application, providing operations to:

  • embed an "empty" value (bpure)
  • align and combine values (bprod)

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) = v
bmap ((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.

Minimal complete definition

Nothing

Methods

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

Instances details
(FunctorB (HKD structure), GApplicativeB (Rep structure)) => ApplicativeB (HKD structure :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Generic.HKD.Types

Methods

bpure :: (forall (a :: k). f a) -> HKD structure f #

bprod :: forall (f :: k -> Type) (g :: k -> Type). HKD structure f -> HKD structure g -> HKD structure (Product f g) #

ApplicativeB (Unit :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.Trivial

Methods

bpure :: (forall (a :: k0). f a) -> Unit f #

bprod :: forall (f :: k0 -> Type) (g :: k0 -> Type). Unit f -> Unit g -> Unit (Product f g) #

ApplicativeB (Proxy :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.ApplicativeB

Methods

bpure :: (forall (a :: k0). f a) -> Proxy f #

bprod :: forall (f :: k0 -> Type) (g :: k0 -> Type). Proxy f -> Proxy g -> Proxy (Product f g) #

ApplicativeB b => ApplicativeB (Barbie b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.Wrappers

Methods

bpure :: (forall (a :: k0). f a) -> Barbie b f #

bprod :: forall (f :: k0 -> Type) (g :: k0 -> Type). Barbie b f -> Barbie b g -> Barbie b (Product f g) #

Monoid a => ApplicativeB (Constant a :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.ApplicativeB

Methods

bpure :: (forall (a0 :: k0). f a0) -> Constant a f #

bprod :: forall (f :: k0 -> Type) (g :: k0 -> Type). Constant a f -> Constant a g -> Constant a (Product f g) #

Monoid a => ApplicativeB (Const a :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.ApplicativeB

Methods

bpure :: (forall (a0 :: k0). f a0) -> Const a f #

bprod :: forall (f :: k0 -> Type) (g :: k0 -> Type). Const a f -> Const a g -> Const a (Product f g) #

(ApplicativeB a, ApplicativeB b) => ApplicativeB (Product a b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.ApplicativeB

Methods

bpure :: (forall (a0 :: k0). f a0) -> Product a b f #

bprod :: forall (f :: k0 -> Type) (g :: k0 -> Type). Product a b f -> Product a b g -> Product a b (Product f g) #

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 (f Int) (f String) | B (f Bool) (f Int)

instance ConstraintsB T where
  type AllB c T = (c Int, c String, c Bool)

  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 instance Generic (T f)
instance ConstraintsB T

Minimal complete definition

Nothing

Associated Types

type AllB (c :: k -> Constraint) (b :: (k -> Type) -> Type) #

AllB c b should contain a constraint c a for each a occurring under an f in b f. E.g.:

AllB Show Person ~ (Show String, Show Int)

For requiring constraints of the form c (f a), use AllBF.

type AllB (c :: k -> Constraint) (b :: (k -> Type) -> Type) = GAll 0 c (GAllRepB b)

Methods

baddDicts :: forall (c :: k -> Constraint) (f :: k -> Type). AllB c b => b f -> b (Product (Dict c) f) #

Instances

Instances details
(FunctorB (HKD structure), GConstraintsB (Rep structure), GAllBC (Rep structure)) => ConstraintsB (HKD structure :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Generic.HKD.Types

Associated Types

type AllB c (HKD structure) #

Methods

baddDicts :: forall (c :: k -> Constraint) (f :: k -> Type). AllB c (HKD structure) => HKD structure f -> HKD structure (Product (Dict c) f) #

ConstraintsB (Void :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type AllB c Void #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c Void => Void f -> Void (Product (Dict c) f) #

ConstraintsB (Unit :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type AllB c Unit #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c Unit => Unit f -> Unit (Product (Dict c) f) #

ConstraintsB (Proxy :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c Proxy #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c Proxy => Proxy f -> Proxy (Product (Dict c) f) #

ConstraintsB b => ConstraintsB (Barbie b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.Wrappers

Associated Types

type AllB c (Barbie b) #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c (Barbie b) => Barbie b f -> Barbie b (Product (Dict c) f) #

ConstraintsB (Const a :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c (Const a) #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c (Const a) => Const a f -> Const a (Product (Dict c) f) #

(ConstraintsB a, ConstraintsB b) => ConstraintsB (Sum a b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c (Sum a b) #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c (Sum a b) => Sum a b f -> Sum a b (Product (Dict c) f) #

(ConstraintsB a, ConstraintsB b) => ConstraintsB (Product a b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c (Product a b) #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f :: k0 -> Type). AllB c (Product a b) => Product a b f -> Product a b (Product (Dict c) f) #

(Functor f, ConstraintsB b) => ConstraintsB (Compose f b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c (Compose f b) #

Methods

baddDicts :: forall (c :: k0 -> Constraint) (f0 :: k0 -> Type). AllB c (Compose f b) => Compose f b f0 -> Compose f b (Product (Dict c) f0) #

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.

Minimal complete definition

Nothing

Methods

bmap :: (forall (a :: k). f a -> g a) -> b f -> b g #

Instances

Instances details
GFunctorB (Rep structure) => FunctorB (HKD structure :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Generic.HKD.Types

Methods

bmap :: (forall (a :: k). f a -> g a) -> HKD structure f -> HKD structure g #

FunctorB (Void :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.Trivial

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Void f -> Void g #

FunctorB (Unit :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.Trivial

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Unit f -> Unit g #

FunctorB (Proxy :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Proxy f -> Proxy g #

FunctorB b => FunctorB (Barbie b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.Wrappers

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Barbie b f -> Barbie b g #

FunctorB (Constant x :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Constant x f -> Constant x g #

FunctorB (Const x :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Const x f -> Const x g #

(FunctorB a, FunctorB b) => FunctorB (Sum a b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a0 :: k0). f a0 -> g a0) -> Sum a b f -> Sum a b g #

(FunctorB a, FunctorB b) => FunctorB (Product a b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a0 :: k0). f a0 -> g a0) -> Product a b f -> Product a b g #

(Functor f, FunctorB b) => FunctorB (Compose f b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a :: k0). f0 a -> g a) -> Compose f b f0 -> Compose f b g #

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)  -- naturality
btraverse Identity = Identity           -- identity
btraverse (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.

Minimal complete definition

Nothing

Methods

btraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> b f -> e (b g) #

Instances

Instances details
(FunctorB (HKD structure), GTraversableB (Rep structure)) => TraversableB (HKD structure :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Generic.HKD.Types

Methods

btraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> HKD structure f -> e (HKD structure g) #

TraversableB (Void :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.Trivial

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Void f -> e (Void g) #

TraversableB (Unit :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.Trivial

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Unit f -> e (Unit g) #

TraversableB (Proxy :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Proxy f -> e (Proxy g) #

TraversableB b => TraversableB (Barbie b :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.Wrappers

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Barbie b f -> e (Barbie b g) #

TraversableB (Constant a :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Constant a f -> e (Constant a g) #

TraversableB (Const a :: (k -> Type) -> Type) 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

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) 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

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) 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

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) 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

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'.
...