temporal-sdk
Safe HaskellNone
LanguageHaskell2010

Data.EvalRecord

Description

This module is intended to be imported qualified, to avoid name clashes with Prelude and base functions:

import qualified Data.EvalRecord as Rec

A common Haskell idiom is to parameterise a datatype by a functor or GADT (or any "indexed type" k -> Type), a pattern sometimes called HKD). This parameter acts as a wrapper of the base type, turning it into a record that serves a different purpose. The canonical example would be:

data Person f
  = Person
      { name :: f String
      , age  :: f Int
      }

However, this library uses a different approach, where the parameter is a type-level function Type -> Exp Type, from the first-class-families package. The type of each field is then given by applying 'Eval (f x)' (also known as @@) to the field:

data Person (f :: Type -> Exp Type)
  = Person
      { name :: f @@ String
      , age  :: f @@ Int
      }

Let's say that we are writing an application where Person data will be read from a web form, validated, and stored in a database. Some possibles outfits that we could use along the way are:

-- for the raw input from the web-form,
webInput :: Person (ConstFn String)
webInput = Person John "30b"

-- for the result of parsing and validating,
validated :: Person (Pure1 (Either String))
validated = Person (Right John) (Left "Not a number")

-- Person Pure for the actual data,
domainModel :: Person Pure
domainModel = Person John 30

dbModel :: Person (Pure1 DbColumn) -- To describe how to read / write a Person to the db
dbModel = Person
  { name = DbColumn "name" (Right . fromString) toDbString
  , age  = DbColumn "age"  (readEither . fromString) show
  }

data DbColumn a
  = DbColumn
      { colName :: String
      , fromDb  :: DbDataParser a
      , toDb    :: a -> DbData
      }

In such application it is likely that one will have lots of types like Person so we will like to handle these transformations uniformly, without boilerplate or repetitions. This package provides classes to manipulate these types, using notions that are familiar to haskellers like Functor, Applicative or Traversable. For example, instead of writing an ad-hoc function that checks that all fields have a correct value, like

checkPerson :: Person (Either String) -> Either [String] (Person Pure)

we can write only one such function:

check :: TraversableRec rec => rec (Either String) -> Either [String] (rec Pure)
check be
  = case traverse (either (const Nothing) Just) be of
      Just bi -> Right bi
      Nothing -> Left (foldMap (either (:[]) (const [])) be)

Moreover, these classes come with template-haskell functions to derive the instances automatically, so that one can write:

import Data.EvalRecord
import Data.EvalRecord.TH

mkEvalRecord [d|
  data Bump = Bump
    { bump :: Maybe Int
    , bomp :: Bool
    , bamp :: String
    } deriving (Read, Show, Eq, Ord)
  |]
Synopsis

Type Witnesses

class WitnessFieldTypes (rec :: (Type -> Exp Type) -> Type) where Source #

Functions that try to convert from f @@ a to some other type don't work without a little help due to injectivity. This class provides that help by providing a function that provides a witness of the type of a for each field of the record.

Minimal complete definition

typeProxies, getAccessors, nestedFieldNames

data Metadata (a :: k) where Source #

A type witness for a field of type a.

For convenience, it also carries Typeable evidence and the name of the field.

Constructors

Metadata 

Fields

Lenses

data LensRec (rec :: (k -> Exp Type) -> Type) (a :: k) Source #

Constructors

LensRec 

Fields

getLens :: forall {k1} f rec (a :: k1) (h :: k1 -> Exp Type). Functor f => LensRec rec a -> ((h @@ a) -> f (h @@ a)) -> rec h -> f (rec h) Source #

Obtain a van-laarhoven lens (compatible with the lens library) from LensRec

nestLens :: forall {k} a b (c :: k). (forall (h :: k -> Exp Type). a h -> (b h -> a h, b h)) -> LensRec b c -> LensRec a c Source #

Functor

class FunctorRec (rec :: (Type -> Exp Type) -> Type) where Source #

Record-types that can be mapped over. Instances of FunctorRec should satisfy the following laws:

map id = id
map f . map g = map (f . g)

Methods

map :: forall (f :: Type -> Exp Type) (g :: Type -> Exp Type). (forall a. Metadata a -> (f @@ a) -> g @@ a) -> rec f -> rec g Source #

Traversable

class FunctorRec rec => TraversableRec (rec :: (Type -> Exp Type) -> Type) where Source #

Record-types that can be traversed from left to right. Instances should satisfy the following laws:

 t . traverse f   = traverse (t . f)  -- naturality
traverse Identity = Identity           -- identity
traverse (fmap g . f) = fmap (traverse g) . traverse f -- composition

Methods

traverse :: forall e (f :: Type -> Exp Type) (g :: Type -> Exp Type). Applicative e => (forall a. Metadata a -> (f @@ a) -> e (g @@ a)) -> rec f -> e (rec g) Source #

traverse_ :: forall e (f :: Type -> Exp Type) c. Applicative e => (forall a. Metadata a -> (f @@ a) -> e c) -> rec f -> e () Source #

Map each element to an action, evaluate these actions from left to right, and ignore the results.

Utility functions

for :: forall rec e (f :: Type -> Exp Type) (g :: Type -> Exp Type). (TraversableRec rec, Applicative e) => rec f -> (forall a. Metadata a -> (f @@ a) -> e (g @@ a)) -> e (rec g) Source #

traverse with the arguments flipped. Useful when the traversing function is a large lambda:

for someRecord $ fa -> ...

Since: 0.0.1.0

for_ :: forall rec e (f :: Type -> Exp Type) c. (TraversableRec rec, Applicative e) => rec f -> (forall a. Metadata a -> (f @@ a) -> e c) -> e () Source #

foldMap :: forall rec m (f :: Type -> Exp Type). (TraversableRec rec, Monoid m) => (forall a. Metadata a -> (f @@ a) -> m) -> rec f -> m Source #

Map each element to a monoid, and combine the results.

sequence :: forall e rec (f :: Type -> Exp Type). (Applicative e, TraversableRec rec) => rec (Pure1 e <=< f) -> e (rec f) Source #

Evaluate each action in the structure from left to right, and collect the results.

sequence' :: (Applicative e, TraversableRec rec) => rec (Pure1 e) -> e (rec (Pure :: Type -> Type -> Type)) Source #

A version of sequence with f specialized to Pure.

Distributive

class FunctorRec rec => DistributiveRec (rec :: (Type -> Exp Type) -> Type) where Source #

A FunctorRec where the effects can be distributed to the fields: distribute turns an effectful way of building a Record-type into a pure Record-type with effectful ways of computing the values of its fields.

This class is the categorical dual of TraversableRec, with distribute the dual of sequence and cotraverse the dual of traverse. As such, instances need to satisfy these laws:

distribute . h = map h) . distribute    -- naturality
distribute . Identity = map Identity                 -- identity

By specializing f to ((->) a) and g to Identity, we can define a function that decomposes a function on distributive records into a collection of simpler functions:

decompose :: DistributiveRec b => (a -> b Identity) -> b ((->) a)
decompose = map (fmap runIdentity . getCompose) . distribute

Lawful instances of the class can then be characterized as those that satisfy:

recompose . decompose = id
decompose . recompose = id

This means intuitively that instances need to have a fixed shape (i.e. no sum-types can be involved). Typically, this means record types, as long as they don't contain fields where the functor argument is not applied.

Methods

distribute :: forall f (g :: Type -> Exp Type). Functor f => f (rec g) -> rec (Pure1 f <=< g) Source #

distribute' :: (DistributiveRec rec, Functor f) => f (rec (Pure :: Type -> Type -> Type)) -> rec (Pure1 f) Source #

A version of distribute with g specialized to Pure.

cotraverse :: forall rec f (g :: Type -> Exp Type). (DistributiveRec rec, Functor f) => (forall a. f (g @@ a) -> f a) -> f (rec g) -> rec (Pure1 f) Source #

decompose :: DistributiveRec rec => (a -> rec (Pure :: Type -> Type -> Type)) -> rec (Pure1 ((->) a)) Source #

Decompose a function returning a distributive record into a collection of simpler functions.

recompose :: FunctorRec rec => rec (Pure1 ((->) a)) -> a -> rec (Pure :: Type -> Type -> Type) Source #

Recompose a decomposed function.

Applicative

class FunctorRec rec => ApplicativeRec (rec :: (Type -> Exp Type) -> Type) where Source #

A FunctorRec with application, providing operations to:

  • embed an "empty" value (pure)
  • align and combine values (prod)

It should satisfy the following laws:

Naturality of prod
map ((a, b) -> (f a, g b)) (u `prod' v) = map f u `prod' map g v
Left and right identity
map ((_, b) -> b) (pure e `prod' v) = v
map ((a, _) -> a) (u `prod' pure e) = u
Associativity
map ((a, (b, c)) -> ((a, b), c) (u `prod' (v `prod' w)) = (u `prod' v) `prod' w

It is to FunctorRec 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.

Methods

pure :: forall (f :: Type -> Exp Type). (forall a. Metadata a -> f @@ a) -> rec f Source #

prod :: forall (f :: Type -> Exp Type) (g :: Type -> Exp Type). rec f -> rec g -> rec (Tuple2 f g) Source #

data Tuple2 (a :: Type -> Exp Type) (b :: Type -> Exp Type) c d Source #

A first-class-families version of Product.

When used with Eval, it resolves in a tuple of the applied type-level functions.

Instances

Instances details
type Eval (Tuple2 f g x :: Type -> Type) Source # 
Instance details

Defined in Data.EvalRecord

type Eval (Tuple2 f g x :: Type -> Type) = (f @@ x, g @@ x)

Utility functions

zip :: forall rec (f :: Type -> Exp Type) (g :: Type -> Exp Type). ApplicativeRec rec => rec f -> rec g -> rec (Tuple2 f g) Source #

An alias of prod, since this is like a zip.

unzip :: forall rec (f :: Type -> Exp Type) (g :: Type -> Exp Type). ApplicativeRec rec => rec (Tuple2 f g) -> (rec f, rec g) Source #

An equivalent of unzip.

zipWith :: forall rec (f :: Type -> Exp Type) (g :: Type -> Exp Type) (h :: Type -> Exp Type). ApplicativeRec rec => (forall a. Metadata a -> (f @@ a) -> (g @@ a) -> h @@ a) -> rec f -> rec g -> rec h Source #

An equivalent of zipWith.

zipWith3 :: forall rec (f :: Type -> Exp Type) (g :: Type -> Exp Type) (h :: Type -> Exp Type) (i :: Type -> Exp Type). ApplicativeRec rec => (forall a. Metadata a -> (f @@ a) -> (g @@ a) -> (h @@ a) -> i @@ a) -> rec f -> rec g -> rec h -> rec i Source #

An equivalent of zipWith3.

zipWith4 :: forall rec (f :: Type -> Exp Type) (g :: Type -> Exp Type) (h :: Type -> Exp Type) (i :: Type -> Exp Type) (j :: Type -> Exp Type). ApplicativeRec rec => (forall a. Metadata a -> (f @@ a) -> (g @@ a) -> (h @@ a) -> (i @@ a) -> j @@ a) -> rec f -> rec g -> rec h -> rec i -> rec j Source #

An equivalent of zipWith4.

Constraints

class FunctorRec rec => ConstraintsRec (rec :: (Type -> Exp Type) -> Type) where Source #

Instances of this class provide means to talk about constraints, both at compile-time, using AllRec, and at run-time, in the form of Dict, via addDicts.

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 AllRec c T = (c Int, c String, c Bool)

  addDicts t = case t of
    A x y -> A (Dict, x) (Dict, y)
    B z w -> B (Dict, z) (Dict, w)

Now, when we given a T f, if we need to use the Show instance of their fields, we can use:

addDicts' :: AllRec Show b => b f -> b (Dict Show `Tuple2' f)

Associated Types

type AllRec (c :: k -> Constraint) (rec :: (Type -> Exp Type) -> Type) Source #

Methods

addDicts :: forall (c :: Type -> Constraint) (f :: Type -> Exp Type). AllRec c rec => rec f -> rec (Tuple2 (Pure1 (Dict c)) f) Source #

type AllRecF (c :: k -> Constraint) (f :: k1 -> Exp k) (b :: (Type -> Exp Type) -> Type) = AllRec (ClassF c f) b Source #

Similar to AllRec but will put the functor argument f between the constraint c and the type a. For example:

 AllRec  Show   Person ~ (Show    String,  Show    Int)
 AllRecF Show f Person ~ (Show (f @ String), Show (f @ Int))
 

class c (f @@ a) => ClassF (c :: k -> Constraint) (f :: k1 -> Exp k) (a :: k1) Source #

ClassF has one universal instance that makes ClassF c f a equivalent to c (f a). However, we have

'ClassF c f :: k -> Constraint

This is useful since it allows to define constraint-constructors like ClassF Monoid 'Pure1 Maybe'

Instances

Instances details
c (f @@ a) => ClassF (c :: k -> Constraint) (f :: k1 -> Exp k) (a :: k1) Source # 
Instance details

Defined in Data.EvalRecord

class c (f @@ a) (g @@ a) => ClassFG (c :: k -> k1 -> Constraint) (f :: k2 -> Exp k) (g :: k2 -> Exp k1) (a :: k2) Source #

Like ClassF but for binary relations.

Instances

Instances details
c (f @@ a) (g @@ a) => ClassFG (c :: k1 -> k2 -> Constraint) (f :: k3 -> Exp k1) (g :: k3 -> Exp k2) (a :: k3) Source # 
Instance details

Defined in Data.EvalRecord

class (c a, d a) => ((c :: k -> Constraint) & (d :: k -> Constraint)) (a :: k) Source #

Instances

Instances details
(c a, d a) => ((c :: k -> Constraint) & (d :: k -> Constraint)) (a :: k) Source # 
Instance details

Defined in Data.EvalRecord

data Dict (c :: k -> Constraint) (a :: k) where Source #

Dict c a is evidence that there exists an instance of c a.

It is essentially equivalent to Dict (c a) from the constraints package, but because of its kind, it allows us to define things like Dict Show.

Constructors

Dict :: forall {k} (c :: k -> Constraint) (a :: k). c a => Dict c a 

Instances

Instances details
Show (Dict c a) Source # 
Instance details

Defined in Data.EvalRecord

Methods

showsPrec :: Int -> Dict c a -> ShowS #

show :: Dict c a -> String #

showList :: [Dict c a] -> ShowS #

Eq (Dict c a) Source # 
Instance details

Defined in Data.EvalRecord

Methods

(==) :: Dict c a -> Dict c a -> Bool #

(/=) :: Dict c a -> Dict c a -> Bool #

Utility functions

dicts :: forall (c :: Type -> Constraint) b. (AllRec c b, ApplicativeRec b, ConstraintsRec b) => b (Pure1 (Dict c)) Source #

Similar to addDicts but can produce the instance dictionaries "out of the blue".

requiringDict :: forall {k} c (a :: k) r. (c a => r) -> Dict c a -> r Source #

Turn a constrained-function into an unconstrained one that uses the packed instance dictionary instead.

mapC :: forall c b (f :: Type -> Exp Type) (g :: Type -> Exp Type). (AllRec c b, ConstraintsRec b) => (forall a. c a => Metadata a -> (f @@ a) -> g @@ a) -> b f -> b g Source #

Like map but a constraint is allowed to be required on each element of rec

E.g. If all fields of rec are Showable then you could store each shown value in it's slot using 'ConstFn String':

showFields :: (AllRec Show rec, ConstraintsRec rec) => b Pure -> b (ConstFn String)
showFields = mapC @Show showField
  where
    showField :: forall a. Show a => Metadata a -> a -> String
    showField _ = show

Notice that one can use the (&) class as a way to require several constraints to hold simultaneously:

map @(Show & Eq & Enum) r

foldMapC :: forall c b m (f :: Type -> Exp Type). (TraversableRec b, ConstraintsRec b, AllRec c b, Monoid m) => (forall a. c a => Metadata a -> (f @@ a) -> m) -> b f -> m Source #

traverseC :: forall c b (f :: Type -> Exp Type) (g :: Type -> Exp Type) e. (TraversableRec b, ConstraintsRec b, AllRec c b, Applicative e) => (forall a. c a => Metadata a -> (f @@ a) -> e (g @@ a)) -> b f -> e (b g) Source #

Like traverse but with a constraint on the elements of b.

forC :: forall c b (f :: Type -> Exp Type) (g :: Type -> Exp Type) e. (TraversableRec b, ConstraintsRec b, AllRec c b, Applicative e) => b f -> (forall a. c a => Metadata a -> (f @@ a) -> e (g @@ a)) -> e (b g) Source #

traverseC with the arguments flipped. Useful when the traversing function is a large lambda:

forC someRec $ fa -> ...

Since: 0.0.1.0

zipWithC :: forall c b (f :: Type -> Exp Type) (g :: Type -> Exp Type) (h :: Type -> Exp Type). (AllRec c b, ConstraintsRec b, ApplicativeRec b) => (forall a. c a => Metadata a -> (f @@ a) -> (g @@ a) -> h @@ a) -> b f -> b g -> b h Source #

Like zipWith but with a constraint on the elements of b.

zipWith3C :: forall c b (f :: Type -> Exp Type) (g :: Type -> Exp Type) (h :: Type -> Exp Type) (i :: Type -> Exp Type). (AllRec c b, ConstraintsRec b, ApplicativeRec b) => (forall a. c a => Metadata a -> (f @@ a) -> (g @@ a) -> (h @@ a) -> i @@ a) -> b f -> b g -> b h -> b i Source #

Like zipWith3 but with a constraint on the elements of b.

zipWith4C :: forall c b (f :: Type -> Exp Type) (g :: Type -> Exp Type) (h :: Type -> Exp Type) (i :: Type -> Exp Type) (j :: Type -> Exp Type). (AllRec c b, ConstraintsRec b, ApplicativeRec b) => (forall a. c a => Metadata a -> (f @@ a) -> (g @@ a) -> (h @@ a) -> (i @@ a) -> j @@ a) -> b f -> b g -> b h -> b i -> b j Source #

Like zipWith4 but with a constraint on the elements of b.

pureC :: forall c (f :: Type -> Exp Type) b. (AllRecF c f b, ConstraintsRec b, ApplicativeRec b) => (forall a. c (f @@ a) => Metadata a -> f @@ a) -> b f Source #

Like pure but a constraint is allowed to be required on each element of b.

mempty :: forall (f :: Type -> Exp Type) b. (AllRecF Monoid f b, ConstraintsRec b, ApplicativeRec b) => b f Source #

Builds a b f, by applying mempty on every field of b.

Partial record mapping

data MapMatches (pred :: k) (f :: k1) a b Source #

Instances

Instances details
type Eval (MapMatches pred f a :: Type -> Type) Source # 
Instance details

Defined in Data.EvalRecord

type Eval (MapMatches pred f a :: Type -> Type) = ValueOnMatch (pred @@ a) (f @@ a) a

type family ValueOnMatch (cond :: Bool) (b :: k) (a :: k) :: k where ... Source #

Equations

ValueOnMatch 'True (b :: k) (_1 :: k) = b 
ValueOnMatch 'False (_1 :: k) (a :: k) = a 

class ApplyOnMatch (cond :: Bool) Source #

Minimal complete definition

applyOnMatch

Instances

Instances details
ApplyOnMatch 'False Source # 
Instance details

Defined in Data.EvalRecord

Methods

applyOnMatch :: Proxy 'False -> (a -> b) -> a -> ValueOnMatch 'False b a

ApplyOnMatch 'True Source # 
Instance details

Defined in Data.EvalRecord

Methods

applyOnMatch :: Proxy 'True -> (a -> b) -> a -> ValueOnMatch 'True b a

mapMatching :: forall (pred :: Type -> Exp Bool) (f :: Type -> Exp Type) (g :: Type -> Exp Type) rec. (FunctorRec rec, ConstraintsRec rec, AllRecF ApplyOnMatch (pred <=< f) rec) => Proxy pred -> (forall a. Metadata a -> (f @@ a) -> (g <=< f) @@ a) -> rec f -> rec (MapMatches pred g <=< f) Source #

applyPred :: forall {k} (pred :: Type -> Exp k) a. Proxy pred -> a -> Proxy (pred @@ a) Source #

Reexports

module Fcf