docrecords-0.1.0.0: Vinyl-based records with hierarchical field names, default values and documentation

Safe HaskellNone
LanguageHaskell2010

Data.DocRecord

Contents

Description

This modules provides extensible records where each field includes a documentation.

Synopsis

Examples

Here is an example of use:

>>> :set -XDataKinds -XTypeApplications -XOverloadedStrings
>>> import Data.Function ((&))
>>> import qualified Data.Text.IO as T
>>> import Data.Aeson (toJSON)
>>> let age  = docField   @"age"  @Int    12  "This is the field giving the age"
>>> let size = docField   @"size" @Double 130 "This is the field giving the size (in cm)"
>>> let name = fieldNoDef @"name" @String     "This is the field giving the name"
>>> let defaultPerson = age :& name :& size :& RNil
>>> let namedDefault = name ..~ "Bernard" $ defaultPerson
>>> defaultPerson
{age =: 12
, name (empty: NoDefault)
, size =: 130.0
}

A DocRec can be serializeddeserialized tofrom Json or Yaml.

>>> let j = toJSON namedDefault
>>> j
Object (fromList [("size",Number 130.0),("age",Number 12.0),("name",String "Bernard")])
>>> fromJSONAs defaultPerson j
Success {age =: 12
, name =: "Bernard"
, size =: 130.0
}

rlens :: (RecElem record r r rs rs (RIndex r rs), RecElemFCtx record f, Functor g) => (f r -> g (f r)) -> record f rs -> g (record f rs) #

Type-preserving field lens. This type is simpler to work with than that of rlens'.

type RElem (x :: k) (rs :: [k]) = RecElem (Rec :: (k -> Type) -> [k] -> Type) x x rs rs #

RecElem for classic vinyl Rec types.

type RSubset = RecSubset (Rec :: (k -> Type) -> [k] -> Type) #

rlabels :: AllFields fs => Rec (Const String :: (Symbol, k) -> Type) fs #

Produce a Rec of the labels of a Rec of ElFields.

(<<$$>>) :: AllFields fs => (forall (a :: (Symbol, k)). KnownField a => f a -> g a) -> Rec f fs -> Rec g fs #

Operator synonym for rmapf.

rpuref :: AllFields fs => (forall (a :: (Symbol, k)). KnownField a => f a) -> Rec f fs #

Construct a Rec with ElField elements.

rmapf :: AllFields fs => (forall (a :: (Symbol, k)). KnownField a => f a -> g a) -> Rec f fs -> Rec g fs #

Map a function between functors across a Rec taking advantage of knowledge that each element is an ElField.

(=:=) :: KnownSymbol s => Label s -> a -> FieldRec ((,) s a ': ([] :: [(Symbol, Type)])) #

Shorthand for a FieldRec with a single field.

rlensf :: (Functor g, HasField record l us us v v, RecElemFCtx record ElField) => Label l -> (v -> g v) -> record ElField us -> g (record ElField us) #

A type-preserving lens into the payload value of a Rec field identified by a Label.

rlensf' :: (Functor g, HasField record l us us' v v', RecElemFCtx record ElField) => Label l -> (v -> g v') -> record ElField us -> g (record ElField us') #

A lens into the payload value of a Rec field identified by a Label.

rlensfL :: (Functor g, HasField record l us us v v, RecElemFCtx record f) => Label l -> (f (l ::: v) -> g (f (l ::: v))) -> record f us -> g (record f us) #

A type-preserving lens into a Rec identified by a Label.

rlensfL' :: (Functor g, HasField record l us us' v v', RecElemFCtx record f) => Label l -> (f (l ::: v) -> g (f (l ::: v'))) -> record f us -> g (record f us') #

A lens into a Rec identified by a Label.

rputf :: (HasField record l us us v v, KnownSymbol l, RecElemFCtx record ElField) => Label l -> v -> record ElField us -> record ElField us #

Set a named field without changing its type. rputf #foo 23 sets the field named #foo to 23.

rputf' :: (HasField record l us us' v v', KnownSymbol l, RecElemFCtx record ElField) => Label l -> v' -> record ElField us -> record ElField us' #

Set a named field. rputf' #foo 23 sets the field named #foo to 23.

rvalf :: (HasField record l us us v v, RecElemFCtx record ElField) => Label l -> record ElField us -> v #

Get the value associated with a named field from a record.

rgetf :: (HasField record l us us v v, RecElemFCtx record f) => Label l -> record f us -> f (l ::: v) #

Get a named field from a record.

traverseField :: (KnownSymbol s, Functor f) => (a -> b) -> f (ElField ((,) s a)) -> ElField ((,) s (f b)) #

Something in the spirit of traverse for ElField whose kind fights the standard library.

fieldMap :: (a -> b) -> ElField ((,) s a) -> ElField ((,) s b) #

ElField is isomorphic to a functor something like Compose ElField ('(,) s).

getLabel :: ElField ((,) s t) -> String #

Get the label name of an ElField.

getField :: ElField ((,) s t) -> t #

Get the data payload of an ElField.

type (:::) (a :: k) (b :: k1) = (,) a b #

Alias for Field spec

type FieldRec = Rec ElField #

A record of named fields.

type AFieldRec (ts :: [(Symbol, Type)]) = ARec ElField ts #

An ARec of named fields to provide constant-time field access.

type HList = Rec Identity #

Heterogeneous list whose elements are evaluated during list construction.

type LazyHList = Rec Thunk #

Heterogeneous list whose elements are left as-is during list construction (cf. HList).

data SField (field :: k) :: forall k. k -> Type #

A proxy for field types.

Constructors

SField 
Instances
Eq (SField a) 
Instance details

Defined in Data.Vinyl.Derived

Methods

(==) :: SField a -> SField a -> Bool #

(/=) :: SField a -> SField a -> Bool #

Ord (SField a) 
Instance details

Defined in Data.Vinyl.Derived

Methods

compare :: SField a -> SField a -> Ordering #

(<) :: SField a -> SField a -> Bool #

(<=) :: SField a -> SField a -> Bool #

(>) :: SField a -> SField a -> Bool #

(>=) :: SField a -> SField a -> Bool #

max :: SField a -> SField a -> SField a #

min :: SField a -> SField a -> SField a #

KnownSymbol s => Show (SField ((,) s t)) 
Instance details

Defined in Data.Vinyl.Derived

Methods

showsPrec :: Int -> SField (s, t) -> ShowS #

show :: SField (s, t) -> String #

showList :: [SField (s, t)] -> ShowS #

type family FieldType (l :: k) (fs :: [(k, k1)]) :: k1 where ... #

Equations

FieldType (l :: t) ([] :: [(t, k)]) = (TypeError ((Text "Cannot find label " :<>: ShowType l) :<>: Text " in fields") :: k) 
FieldType (l :: k1) ((l ::: v) ': fs :: [(k1, k2)]) = v 
FieldType (l :: k1) ((l' ::: v') ': fs :: [(k1, k2)]) = FieldType l fs 

data Label (a :: Symbol) #

Proxy for label type

Constructors

Label 
Instances
s ~ s' => IsLabel s (Label s') 
Instance details

Defined in Data.Vinyl.Derived

Methods

fromLabel :: Label s' #

Eq (Label a) 
Instance details

Defined in Data.Vinyl.Derived

Methods

(==) :: Label a -> Label a -> Bool #

(/=) :: Label a -> Label a -> Bool #

Show (Label a) 
Instance details

Defined in Data.Vinyl.Derived

Methods

showsPrec :: Int -> Label a -> ShowS #

show :: Label a -> String #

showList :: [Label a] -> ShowS #

class (KnownSymbol (Fst a), a ~ (,) (Fst a) (Snd a)) => KnownField (a :: (Symbol, k)) #

Defines a constraint that lets us extract the label from an ElField. Used in rmapf and rpuref.

Instances
KnownSymbol l => KnownField (l ::: v :: (Symbol, k)) 
Instance details

Defined in Data.Vinyl.Derived

type AllFields (fs :: [(Symbol, k)]) = (RPureConstrained (KnownField :: (Symbol, k) -> Constraint) fs, RecApplicative fs, RApply fs) #

Shorthand for working with records of fields as in rmapf and rpuref.

type family Unlabeled (ts :: [(k, a)]) :: [a] where ... #

Remove the first component (e.g. the label) from a type-level list of pairs.

Equations

Unlabeled ([] :: [(k, a)]) = ([] :: [a]) 
Unlabeled ((,) s x ': xs :: [(k, a)]) = x ': Unlabeled xs 

class StripFieldNames (ts :: [(Symbol, Type)]) where #

Facilities for removing and replacing the type-level label, or column name, part of a record.

Methods

stripNames :: Rec ElField ts -> Rec Identity (Unlabeled ts) #

stripNames' :: Functor f => Rec (f :. ElField) ts -> Rec f (Unlabeled ts) #

withNames :: Rec Identity (Unlabeled ts) -> Rec ElField ts #

withNames' :: Functor f => Rec f (Unlabeled ts) -> Rec (f :. ElField) ts #

Instances
StripFieldNames ([] :: [(Symbol, Type)]) 
Instance details

Defined in Data.Vinyl.Derived

Methods

stripNames :: Rec ElField [] -> Rec Identity (Unlabeled []) #

stripNames' :: Functor f => Rec (f :. ElField) [] -> Rec f (Unlabeled []) #

withNames :: Rec Identity (Unlabeled []) -> Rec ElField [] #

withNames' :: Functor f => Rec f (Unlabeled []) -> Rec (f :. ElField) [] #

(KnownSymbol s, StripFieldNames ts) => StripFieldNames ((,) s t ': ts) 
Instance details

Defined in Data.Vinyl.Derived

Methods

stripNames :: Rec ElField ((s, t) ': ts) -> Rec Identity (Unlabeled ((s, t) ': ts)) #

stripNames' :: Functor f => Rec (f :. ElField) ((s, t) ': ts) -> Rec f (Unlabeled ((s, t) ': ts)) #

withNames :: Rec Identity (Unlabeled ((s, t) ': ts)) -> Rec ElField ((s, t) ': ts) #

withNames' :: Functor f => Rec f (Unlabeled ((s, t) ': ts)) -> Rec (f :. ElField) ((s, t) ': ts) #

type family (as :: [k]) ++ (bs :: [k]) :: [k] where ... #

Append for type-level lists.

Equations

([] :: [k]) ++ (bs :: [k]) = bs 
(a ': as :: [k]) ++ (bs :: [k]) = a ': (as ++ bs) 

type family AllFst c p :: Constraint where ... Source #

Equations

AllFst c (r ': rs) = (c (Fst r), AllFst c rs) 
AllFst c '[] = () 

type family AllSnd c p :: Constraint where ... Source #

Equations

AllSnd c (r ': rs) = (c (Snd r), AllSnd c rs) 
AllSnd c '[] = () 

Types

data PathWithType a b Source #

Just a type-level tuple, for easier to read type signatures

Constructors

a :|: b 
Instances
PrefixPath s ([] :: [PathWithType [Symbol] Type]) Source # 
Instance details

Defined in Data.DocRecord

Associated Types

type PrefixingAll s [] :: [PathWithType [Symbol] Type] Source #

Methods

prefixPath :: NamedField f => Rec f [] -> Rec f (PrefixingAll s []) Source #

(PrefixPath s ps, ShowPath (s ++ p1)) => PrefixPath s ((p1 :|: t) ': ps) Source # 
Instance details

Defined in Data.DocRecord

Associated Types

type PrefixingAll s ((p1 :|: t) ': ps) :: [PathWithType [Symbol] Type] Source #

Methods

prefixPath :: NamedField f => Rec f ((p1 :|: t) ': ps) -> Rec f (PrefixingAll s ((p1 :|: t) ': ps)) Source #

(RMap rs, AllSnd ToJSON rs, AllFst (ShowPath :: [Symbol] -> Constraint) rs) => ToJSON (Rec DocField rs) Source #

Just ignores the docstrings

Instance details

Defined in Data.DocRecord

(AllSnd ToJSON rs, AllFst (ShowPath :: [Symbol] -> Constraint) rs) => ToJSON (Rec PossiblyEmptyField rs) Source # 
Instance details

Defined in Data.DocRecord

(RMap rs, FromJSON (Rec PossiblyEmptyField rs)) => FromJSON (Rec DocField rs) Source #

Just sets the docstrings to empty

Instance details

Defined in Data.DocRecord

(FromJSON t, FromJSON (Rec PossiblyEmptyField rs), ShowPath s) => FromJSON (Rec PossiblyEmptyField ((s :|: t) ': rs)) Source # 
Instance details

Defined in Data.DocRecord

Methods

parseJSON :: Value -> Parser (Rec PossiblyEmptyField ((s :|: t) ': rs)) #

parseJSONList :: Value -> Parser [Rec PossiblyEmptyField ((s :|: t) ': rs)] #

FromJSON (Rec PossiblyEmptyField ([] :: [PathWithType [Symbol] Type])) Source # 
Instance details

Defined in Data.DocRecord

(NamedField f, FieldWithTag Text f, FieldWithTag SourceTag f, FieldFromCLI (s :|: t), RecFromCLI (Rec f rs), ShowPath s) => RecFromCLI (Rec f ((s :|: t) ': rs)) Source # 
Instance details

Defined in Data.DocRecord.OptParse

Methods

parseRecFromCLI_ :: HashMap [Text] String -> Rec f ((s :|: t) ': rs) -> Parser (Rec f ((s :|: t) ': rs)) Source #

allPaths :: Rec f ((s :|: t) ': rs) -> [[Text]] Source #

RecFromCLI (Rec f ([] :: [PathWithType [Symbol] Type])) Source # 
Instance details

Defined in Data.DocRecord.OptParse

Methods

parseRecFromCLI_ :: HashMap [Text] String -> Rec f [] -> Parser (Rec f []) Source #

allPaths :: Rec f [] -> [[Text]] Source #

(ApplyRec fns fields results, ShowPath s) => ApplyRec ((a -> b) ': fns) ((s :|: a) ': fields) ((s :|: b) ': results) Source # 
Instance details

Defined in Data.DocRecord

Methods

appRec :: NamedField f => Rec Identity ((a -> b) ': fns) -> Rec f ((s :|: a) ': fields) -> Rec f ((s :|: b) ': results) Source #

(NamedField f, NamedFieldTag tag) => NamedField (Compose (Tagged tag) f) Source # 
Instance details

Defined in Data.DocRecord

Methods

rfield :: ShowPath s => Lens (Compose (Tagged tag) f (s :|: a)) (Compose (Tagged tag) f (s :|: b)) (Maybe a) (Maybe b) Source #

fromValue :: ShowPath s => a -> Compose (Tagged tag) f (s :|: a) Source #

mapField :: ShowPath s => (t -> t') -> Compose (Tagged tag) f (s :|: t) -> Compose (Tagged tag) f (s :|: t') Source #

(=:) :: ShowPath s => DocField (s :|: a) -> a -> Rec (Compose (Tagged tag) f) ((s :|: a) ': []) Source #

changePath :: ShowPath s' => Compose (Tagged tag) f (s :|: a) -> Compose (Tagged tag) f (s' :|: a) Source #

NamedField f => NamedField (Compose PossiblyEmpty f) Source # 
Instance details

Defined in Data.DocRecord

Methods

rfield :: ShowPath s => Lens (Compose PossiblyEmpty f (s :|: a)) (Compose PossiblyEmpty f (s :|: b)) (Maybe a) (Maybe b) Source #

fromValue :: ShowPath s => a -> Compose PossiblyEmpty f (s :|: a) Source #

mapField :: ShowPath s => (t -> t') -> Compose PossiblyEmpty f (s :|: t) -> Compose PossiblyEmpty f (s :|: t') Source #

(=:) :: ShowPath s => DocField (s :|: a) -> a -> Rec (Compose PossiblyEmpty f) ((s :|: a) ': []) Source #

changePath :: ShowPath s' => Compose PossiblyEmpty f (s :|: a) -> Compose PossiblyEmpty f (s' :|: a) Source #

type PrefixingAll s ([] :: [PathWithType [Symbol] Type]) Source # 
Instance details

Defined in Data.DocRecord

type PrefixingAll s ([] :: [PathWithType [Symbol] Type]) = ([] :: [PathWithType [Symbol] Type])
type PrefixingAll s ((p1 :|: t) ': ps) Source # 
Instance details

Defined in Data.DocRecord

type PrefixingAll s ((p1 :|: t) ': ps) = ((s ++ p1) :|: t) ': PrefixingAll s ps

type FieldWithTag tag field = FieldWithTag_ tag field (FieldDirectlyContainsTag tag field) Source #

Tells whether fieldTag can be used on a Field

fieldTag :: FieldWithTag_ tag field hasTag => Traversal' (field r) tag Source #

Retrieves or modifies a tag (documentation, source...) within a field

data Field (pathAndType :: PathWithType [Symbol] *) where Source #

The most basic field. We don't use ElField from vinyl so we can use the PathWithType kind instead of tuple and paths instead of just names.

Constructors

Field :: ShowPath s => !t -> Field (s :|: t) 
Instances
NamedField Field Source # 
Instance details

Defined in Data.DocRecord

Methods

rfield :: ShowPath s => Lens (Field (s :|: a)) (Field (s :|: b)) (Maybe a) (Maybe b) Source #

fromValue :: ShowPath s => a -> Field (s :|: a) Source #

mapField :: ShowPath s => (t -> t') -> Field (s :|: t) -> Field (s :|: t') Source #

(=:) :: ShowPath s => DocField (s :|: a) -> a -> Rec Field ((s :|: a) ': []) Source #

changePath :: ShowPath s' => Field (s :|: a) -> Field (s' :|: a) Source #

Eq a => Eq (Field (s :|: a)) Source # 
Instance details

Defined in Data.DocRecord

Methods

(==) :: Field (s :|: a) -> Field (s :|: a) -> Bool #

(/=) :: Field (s :|: a) -> Field (s :|: a) -> Bool #

Ord a => Ord (Field (s :|: a)) Source # 
Instance details

Defined in Data.DocRecord

Methods

compare :: Field (s :|: a) -> Field (s :|: a) -> Ordering #

(<) :: Field (s :|: a) -> Field (s :|: a) -> Bool #

(<=) :: Field (s :|: a) -> Field (s :|: a) -> Bool #

(>) :: Field (s :|: a) -> Field (s :|: a) -> Bool #

(>=) :: Field (s :|: a) -> Field (s :|: a) -> Bool #

max :: Field (s :|: a) -> Field (s :|: a) -> Field (s :|: a) #

min :: Field (s :|: a) -> Field (s :|: a) -> Field (s :|: a) #

(Show t, ShowPath s) => Show (Field (s :|: t)) Source # 
Instance details

Defined in Data.DocRecord

Methods

showsPrec :: Int -> Field (s :|: t) -> ShowS #

show :: Field (s :|: t) -> String #

showList :: [Field (s :|: t)] -> ShowS #

Semigroup t => Semigroup (Field (s :|: t)) Source # 
Instance details

Defined in Data.DocRecord

Methods

(<>) :: Field (s :|: t) -> Field (s :|: t) -> Field (s :|: t) #

sconcat :: NonEmpty (Field (s :|: t)) -> Field (s :|: t) #

stimes :: Integral b => b -> Field (s :|: t) -> Field (s :|: t) #

(ShowPath s, Monoid t) => Monoid (Field (s :|: t)) Source # 
Instance details

Defined in Data.DocRecord

Methods

mempty :: Field (s :|: t) #

mappend :: Field (s :|: t) -> Field (s :|: t) -> Field (s :|: t) #

mconcat :: [Field (s :|: t)] -> Field (s :|: t) #

(RMap rs, AllSnd ToJSON rs, AllFst (ShowPath :: [Symbol] -> Constraint) rs) => ToJSON (Rec DocField rs) Source #

Just ignores the docstrings

Instance details

Defined in Data.DocRecord

(AllSnd ToJSON rs, AllFst (ShowPath :: [Symbol] -> Constraint) rs) => ToJSON (Rec PossiblyEmptyField rs) Source # 
Instance details

Defined in Data.DocRecord

(RMap rs, FromJSON (Rec PossiblyEmptyField rs)) => FromJSON (Rec DocField rs) Source #

Just sets the docstrings to empty

Instance details

Defined in Data.DocRecord

(FromJSON t, FromJSON (Rec PossiblyEmptyField rs), ShowPath s) => FromJSON (Rec PossiblyEmptyField ((s :|: t) ': rs)) Source # 
Instance details

Defined in Data.DocRecord

Methods

parseJSON :: Value -> Parser (Rec PossiblyEmptyField ((s :|: t) ': rs)) #

parseJSONList :: Value -> Parser [Rec PossiblyEmptyField ((s :|: t) ': rs)] #

FromJSON (Rec PossiblyEmptyField ([] :: [PathWithType [Symbol] Type])) Source # 
Instance details

Defined in Data.DocRecord

data Tagged tag a Source #

Wraps a field and gives it some tag

Constructors

Tagged 

Fields

Instances
Functor (Tagged tag) Source # 
Instance details

Defined in Data.DocRecord

Methods

fmap :: (a -> b) -> Tagged tag a -> Tagged tag b #

(<$) :: a -> Tagged tag b -> Tagged tag a #

Monoid tag => Applicative (Tagged tag) Source # 
Instance details

Defined in Data.DocRecord

Methods

pure :: a -> Tagged tag a #

(<*>) :: Tagged tag (a -> b) -> Tagged tag a -> Tagged tag b #

liftA2 :: (a -> b -> c) -> Tagged tag a -> Tagged tag b -> Tagged tag c #

(*>) :: Tagged tag a -> Tagged tag b -> Tagged tag b #

(<*) :: Tagged tag a -> Tagged tag b -> Tagged tag a #

Eq a => Eq (Tagged tag a) Source # 
Instance details

Defined in Data.DocRecord

Methods

(==) :: Tagged tag a -> Tagged tag a -> Bool #

(/=) :: Tagged tag a -> Tagged tag a -> Bool #

Ord a => Ord (Tagged tag a) Source # 
Instance details

Defined in Data.DocRecord

Methods

compare :: Tagged tag a -> Tagged tag a -> Ordering #

(<) :: Tagged tag a -> Tagged tag a -> Bool #

(<=) :: Tagged tag a -> Tagged tag a -> Bool #

(>) :: Tagged tag a -> Tagged tag a -> Bool #

(>=) :: Tagged tag a -> Tagged tag a -> Bool #

max :: Tagged tag a -> Tagged tag a -> Tagged tag a #

min :: Tagged tag a -> Tagged tag a -> Tagged tag a #

Show a => Show (Tagged tag a) Source # 
Instance details

Defined in Data.DocRecord

Methods

showsPrec :: Int -> Tagged tag a -> ShowS #

show :: Tagged tag a -> String #

showList :: [Tagged tag a] -> ShowS #

Semigroup a => Semigroup (Tagged tag a) Source #

The tag is right-biased

Instance details

Defined in Data.DocRecord

Methods

(<>) :: Tagged tag a -> Tagged tag a -> Tagged tag a #

sconcat :: NonEmpty (Tagged tag a) -> Tagged tag a #

stimes :: Integral b => b -> Tagged tag a -> Tagged tag a #

(Monoid tag, Monoid a) => Monoid (Tagged tag a) Source # 
Instance details

Defined in Data.DocRecord

Methods

mempty :: Tagged tag a #

mappend :: Tagged tag a -> Tagged tag a -> Tagged tag a #

mconcat :: [Tagged tag a] -> Tagged tag a #

(RMap rs, AllSnd ToJSON rs, AllFst (ShowPath :: [Symbol] -> Constraint) rs) => ToJSON (Rec DocField rs) Source #

Just ignores the docstrings

Instance details

Defined in Data.DocRecord

(RMap rs, FromJSON (Rec PossiblyEmptyField rs)) => FromJSON (Rec DocField rs) Source #

Just sets the docstrings to empty

Instance details

Defined in Data.DocRecord

(NamedField f, NamedFieldTag tag) => NamedField (Compose (Tagged tag) f) Source # 
Instance details

Defined in Data.DocRecord

Methods

rfield :: ShowPath s => Lens (Compose (Tagged tag) f (s :|: a)) (Compose (Tagged tag) f (s :|: b)) (Maybe a) (Maybe b) Source #

fromValue :: ShowPath s => a -> Compose (Tagged tag) f (s :|: a) Source #

mapField :: ShowPath s => (t -> t') -> Compose (Tagged tag) f (s :|: t) -> Compose (Tagged tag) f (s :|: t') Source #

(=:) :: ShowPath s => DocField (s :|: a) -> a -> Rec (Compose (Tagged tag) f) ((s :|: a) ': []) Source #

changePath :: ShowPath s' => Compose (Tagged tag) f (s :|: a) -> Compose (Tagged tag) f (s' :|: a) Source #

type WithDoc = Tagged Text Source #

Wraps a field and gives it some documentation

newtype PossiblyEmpty a Source #

Wraps a field so that it can have no value

Constructors

PE (Either MissingValueReason a) 
Instances
Functor PossiblyEmpty Source # 
Instance details

Defined in Data.DocRecord

Methods

fmap :: (a -> b) -> PossiblyEmpty a -> PossiblyEmpty b #

(<$) :: a -> PossiblyEmpty b -> PossiblyEmpty a #

Applicative PossiblyEmpty Source # 
Instance details

Defined in Data.DocRecord

Eq a => Eq (PossiblyEmpty a) Source # 
Instance details

Defined in Data.DocRecord

Ord a => Ord (PossiblyEmpty a) Source # 
Instance details

Defined in Data.DocRecord

(Show (f (s :|: a2)), ShowPath s) => Show (PossiblyEmpty (f (s :|: a2))) Source # 
Instance details

Defined in Data.DocRecord

Methods

showsPrec :: Int -> PossiblyEmpty (f (s :|: a2)) -> ShowS #

show :: PossiblyEmpty (f (s :|: a2)) -> String #

showList :: [PossiblyEmpty (f (s :|: a2))] -> ShowS #

Semigroup a => Semigroup (PossiblyEmpty a) Source # 
Instance details

Defined in Data.DocRecord

Semigroup a => Monoid (PossiblyEmpty a) Source # 
Instance details

Defined in Data.DocRecord

(RMap rs, AllSnd ToJSON rs, AllFst (ShowPath :: [Symbol] -> Constraint) rs) => ToJSON (Rec DocField rs) Source #

Just ignores the docstrings

Instance details

Defined in Data.DocRecord

(AllSnd ToJSON rs, AllFst (ShowPath :: [Symbol] -> Constraint) rs) => ToJSON (Rec PossiblyEmptyField rs) Source # 
Instance details

Defined in Data.DocRecord

(RMap rs, FromJSON (Rec PossiblyEmptyField rs)) => FromJSON (Rec DocField rs) Source #

Just sets the docstrings to empty

Instance details

Defined in Data.DocRecord

(FromJSON t, FromJSON (Rec PossiblyEmptyField rs), ShowPath s) => FromJSON (Rec PossiblyEmptyField ((s :|: t) ': rs)) Source # 
Instance details

Defined in Data.DocRecord

Methods

parseJSON :: Value -> Parser (Rec PossiblyEmptyField ((s :|: t) ': rs)) #

parseJSONList :: Value -> Parser [Rec PossiblyEmptyField ((s :|: t) ': rs)] #

FromJSON (Rec PossiblyEmptyField ([] :: [PathWithType [Symbol] Type])) Source # 
Instance details

Defined in Data.DocRecord

NamedField f => NamedField (Compose PossiblyEmpty f) Source # 
Instance details

Defined in Data.DocRecord

Methods

rfield :: ShowPath s => Lens (Compose PossiblyEmpty f (s :|: a)) (Compose PossiblyEmpty f (s :|: b)) (Maybe a) (Maybe b) Source #

fromValue :: ShowPath s => a -> Compose PossiblyEmpty f (s :|: a) Source #

mapField :: ShowPath s => (t -> t') -> Compose PossiblyEmpty f (s :|: t) -> Compose PossiblyEmpty f (s :|: t') Source #

(=:) :: ShowPath s => DocField (s :|: a) -> a -> Rec (Compose PossiblyEmpty f) ((s :|: a) ': []) Source #

changePath :: ShowPath s' => Compose PossiblyEmpty f (s :|: a) -> Compose PossiblyEmpty f (s' :|: a) Source #

pattern PEField :: (NamedField f, ShowPath s) => Maybe a -> Compose PossiblyEmpty f (s :|: a) Source #

type DocRec = Rec DocField Source #

A extensible record of documented fields with values

type family FieldTypes rs where ... Source #

To forget the field paths and get only the field types

Equations

FieldTypes '[] = '[] 
FieldTypes ((s :|: t) ': rs) = t ': FieldTypes rs 

class NamedField field where Source #

Redefines rfield and (=:) from Data.Vinyl.Derived so they can work over different kinds of fields.

Minimal complete definition

rfield, fromValue, changePath

Methods

rfield :: ShowPath s => Lens (field (s :|: a)) (field (s :|: b)) (Maybe a) (Maybe b) Source #

Lens to the payload of a field

fromValue :: ShowPath s => a -> field (s :|: a) Source #

Construct a NamedField from a value

mapField :: ShowPath s => (t -> t') -> field (s :|: t) -> field (s :|: t') Source #

Transform the value inside the field if there is one

(=:) :: ShowPath s => DocField (s :|: a) -> a -> Rec field '[s :|: a] infixl 7 Source #

Shorthand to create a NamedField with a single field, using a DocField as an example.

changePath :: ShowPath s' => field (s :|: a) -> field (s' :|: a) Source #

Instances
NamedField Field Source # 
Instance details

Defined in Data.DocRecord

Methods

rfield :: ShowPath s => Lens (Field (s :|: a)) (Field (s :|: b)) (Maybe a) (Maybe b) Source #

fromValue :: ShowPath s => a -> Field (s :|: a) Source #

mapField :: ShowPath s => (t -> t') -> Field (s :|: t) -> Field (s :|: t') Source #

(=:) :: ShowPath s => DocField (s :|: a) -> a -> Rec Field ((s :|: a) ': []) Source #

changePath :: ShowPath s' => Field (s :|: a) -> Field (s' :|: a) Source #

(NamedField f, NamedFieldTag tag) => NamedField (Compose (Tagged tag) f) Source # 
Instance details

Defined in Data.DocRecord

Methods

rfield :: ShowPath s => Lens (Compose (Tagged tag) f (s :|: a)) (Compose (Tagged tag) f (s :|: b)) (Maybe a) (Maybe b) Source #

fromValue :: ShowPath s => a -> Compose (Tagged tag) f (s :|: a) Source #

mapField :: ShowPath s => (t -> t') -> Compose (Tagged tag) f (s :|: t) -> Compose (Tagged tag) f (s :|: t') Source #

(=:) :: ShowPath s => DocField (s :|: a) -> a -> Rec (Compose (Tagged tag) f) ((s :|: a) ': []) Source #

changePath :: ShowPath s' => Compose (Tagged tag) f (s :|: a) -> Compose (Tagged tag) f (s' :|: a) Source #

NamedField f => NamedField (Compose PossiblyEmpty f) Source # 
Instance details

Defined in Data.DocRecord

Methods

rfield :: ShowPath s => Lens (Compose PossiblyEmpty f (s :|: a)) (Compose PossiblyEmpty f (s :|: b)) (Maybe a) (Maybe b) Source #

fromValue :: ShowPath s => a -> Compose PossiblyEmpty f (s :|: a) Source #

mapField :: ShowPath s => (t -> t') -> Compose PossiblyEmpty f (s :|: t) -> Compose PossiblyEmpty f (s :|: t') Source #

(=:) :: ShowPath s => DocField (s :|: a) -> a -> Rec (Compose PossiblyEmpty f) ((s :|: a) ': []) Source #

changePath :: ShowPath s' => Compose PossiblyEmpty f (s :|: a) -> Compose PossiblyEmpty f (s' :|: a) Source #

class NamedFieldTag tag where Source #

Tells the default tag to apply when creating a Field with fromValue

Methods

defaultTag :: tag Source #

Tells the default tag to apply when creating a Field with fromValue

tagFromDoc :: Text -> tag Source #

Permits to possibly keep the doc when setting a field

type IntermediaryLevel s rs = IntermediaryLevel_ (s :|: DocRec rs) Source #

Used to indicate "virtual" fields, that won't be directly filled with data but will be used by rinclude, rdrill, '(-.)' and '(-/)' to pinpoint a subrecord in the hierarchy and indicate what this subrecord is meant to contain

type FlattenedLevel s rs = s `PrefixingAll` rs Source #

Transforming the type of an IntermediaryLevel into a regular record

class RElem f rs (RIndex' f rs f rs) => HasField rs f Source #

Tells whether rs contains Field f. It replaces vinyl's (∈) to provide better error messages

Instances
RElem f (r ': rs) (RIndex' f (r ': rs) f (r ': rs)) => HasField (r ': rs :: [k]) (f :: k) Source # 
Instance details

Defined in Data.DocRecord

class RSubset rs ss (RImage' rs ss rs ss) => Includes ss rs Source #

Tells whether rs contains Field f. It replaces vinyl's (⊆) to provide better error messages

Instances
Includes (ss :: [k]) ([] :: [k]) Source # 
Instance details

Defined in Data.DocRecord

RSubset (r ': rs) ss (RImage' (r ': rs) ss (r ': rs) ss) => Includes (ss :: [a]) (r ': rs :: [a]) Source # 
Instance details

Defined in Data.DocRecord

type EquivalentTo rs ss = (rs `Includes` ss, ss `Includes` rs) Source #

Replaces vinyl REquivalent to provide better error messages

type family Difference a b where ... Source #

Equations

Difference ts' (t ': ts) = Difference (DeleteIn t ts') ts 
Difference ts' '[] = ts' 

type ToJSONFields fields = (ToJSON `AllSnd` fields, Typeable `AllSnd` fields, ShowPath `AllFst` fields) Source #

A shortcut to ensure all fields in list are convertible to JSON

data RecBijection f as bs Source #

Transforms a 'Rec f as' into a 'Rec f bs' and the other way around. This is exactly like an Iso from Lens, but using an Iso makes it harder to implement (). Maybe in the future we'll get back to regular Lenses and Isos (because this way composition of Isos and Lenses together is done for us and behaves sanely. Plus we get plain old function composition instead of having to import Control.Category). This could be done by making bijectField/addConstField etc

Constructors

RecBijection 

Fields

Instances
Category (RecBijection f :: [u] -> [u] -> Type) Source # 
Instance details

Defined in Data.DocRecord

Methods

id :: RecBijection f a a #

(.) :: RecBijection f b c -> RecBijection f a b -> RecBijection f a c #

class ShowPath p where Source #

Minimal complete definition

showPathList

Methods

showPathList :: proxy p -> [Text] Source #

showPath :: proxy p -> Text Source #

Instances
ShowPath ([] :: [k]) Source # 
Instance details

Defined in Data.DocRecord

Methods

showPathList :: proxy [] -> [Text] Source #

showPath :: proxy [] -> Text Source #

(ShowPath ps, KnownSymbol p) => ShowPath (p ': ps :: [Symbol]) Source # 
Instance details

Defined in Data.DocRecord

Methods

showPathList :: proxy (p ': ps) -> [Text] Source #

showPath :: proxy (p ': ps) -> Text Source #

class ApplyRec fns fields results | fns fields -> results where Source #

Applies a record of functions to a record of data. It's a bit like the () operator from vinyl but it permits to change the type of the fields, which () from vinyl doesn't.

Methods

appRec :: NamedField f => Rec Identity fns -> Rec f fields -> Rec f results Source #

Instances
ApplyRec ([] :: [Type]) a a Source # 
Instance details

Defined in Data.DocRecord

Methods

appRec :: NamedField f => Rec Identity [] -> Rec f a -> Rec f a Source #

(ApplyRec fns fields results, ShowPath s) => ApplyRec ((a -> b) ': fns) ((s :|: a) ': fields) ((s :|: b) ': results) Source # 
Instance details

Defined in Data.DocRecord

Methods

appRec :: NamedField f => Rec Identity ((a -> b) ': fns) -> Rec f ((s :|: a) ': fields) -> Rec f ((s :|: b) ': results) Source #

data MD Source #

Used to indicate that a field contains no useful value, only metadata (doc)

Constructors

MD 
Instances
Eq MD Source # 
Instance details

Defined in Data.DocRecord

Methods

(==) :: MD -> MD -> Bool #

(/=) :: MD -> MD -> Bool #

Ord MD Source # 
Instance details

Defined in Data.DocRecord

Methods

compare :: MD -> MD -> Ordering #

(<) :: MD -> MD -> Bool #

(<=) :: MD -> MD -> Bool #

(>) :: MD -> MD -> Bool #

(>=) :: MD -> MD -> Bool #

max :: MD -> MD -> MD #

min :: MD -> MD -> MD #

Show MD Source # 
Instance details

Defined in Data.DocRecord

Methods

showsPrec :: Int -> MD -> ShowS #

show :: MD -> String #

showList :: [MD] -> ShowS #

ToJSON MD Source # 
Instance details

Defined in Data.DocRecord

FromJSON MD Source # 
Instance details

Defined in Data.DocRecord

type family Fst a where ... Source #

Equations

Fst (a :|: b) = a 

type family Snd a where ... Source #

Equations

Snd (a :|: b) = b 

Utils

removeDoc :: Compose WithDoc f st -> f st Source #

chooseHighestPriority :: Ord a => Compose (Tagged a) (Compose (Tagged Text) f) x -> Compose (Tagged a) (Compose (Tagged Text) f) x -> Compose (Tagged a) (Compose (Tagged Text) f) x Source #

When two fields are tagged with an Ord, return the field with the highest one. Right field is returned if both tags are equal.

fld :: forall s a rs field proxy. (NamedField field, rs `HasField` (s :|: a), ShowPath s) => proxy (s :|: a) -> Lens' (Rec field rs) (Maybe a) Source #

Lens for getting a field's value inside some NamedField. Shortcut for rlens f . rfield

runcurryF :: forall ts f1 f a. OnFields ts f1 (CurriedF f ts a) => f1 -> Rec f ts -> a Source #

runcurryAF :: forall ts f1 f g a. (Applicative f, OnFields ts f1 (CurriedF g ts a)) => f1 -> Rec (Compose f g) ts -> f a Source #

docField :: forall s t. KnownSymbol s => t -> Text -> DocField ('[s] :|: t) Source #

Used to create a field template

itmLevel :: forall s rs. KnownSymbol s => Text -> DocRec rs -> IntermediaryLevel '[s] rs Source #

Used to create an intermediary field

fieldPath :: forall st p. ShowPath (Fst st) => p st -> Text Source #

fieldPathList :: forall st p. ShowPath (Fst st) => p st -> [Text] Source #

fieldFromDef :: forall s t. (KnownSymbol s, Default t) => Text -> DocField ('[s] :|: t) Source #

Used to create a field from a default

fieldNoDef :: forall s t. Text -> DocField ('[s] :|: t) Source #

Used to create a field that will not have a default value

singleton :: NamedField f => t -> Rec f '['[] :|: t] Source #

A record with just an anonymous field. Useful when only the position of the field is important

useDef :: (NamedField f, ShowPath s) => DocField (s :|: t) -> Rec f '[s :|: t] Source #

Directly use a default value as part of a record. Will fail if f doesn't have a default value

fromJSONAs :: FromJSON x => x -> Value -> Result x Source #

Just a shortcut to fix the record type that we are expecting in return

>>> let (Success p) = fromJSONAs defaultPerson j
>>> p
{age =: 12
, name =: "Bernard"
, size =: 130.0
}
         ^^^ At this step (when pattern matching on Success)
          we can re-order the fields of defaultPerson
          or even get just a subset of them

(^^.) :: (NamedField field, rs `HasField` (s :|: t), ShowPath s, Monoid t) => Rec field rs -> proxy (s :|: t) -> t infixl 8 Source #

r ^^. n is just a shortcut for r ^. fld n . _Just. Since the field can be empty it requires it to be a Monoid

(^^?) :: (NamedField field, rs `HasField` (s :|: t), ShowPath s) => Rec field rs -> proxy (s :|: t) -> Maybe t infixl 8 Source #

r ^^? n is just a shortcut for r ^. fld n >>> let v2 = namedDefault & age %%~ (+1) >>> v2^^?age Just 13

(^^?!) :: (NamedField field, rs `HasField` (s :|: t), ShowPath s) => Rec field rs -> proxy (s :|: t) -> t infixl 8 Source #

r ^^?! n is just a shortcut for r ^?! fld n . L._Just. It fails if the field doesn't contain a value. >>> let v2 = namedDefault & age %%~ (+1) >>> v2^^?!age 13

(%%~) :: (NamedField field, rs `HasField` (s :|: t), ShowPath s) => proxy (s :|: t) -> (t -> t) -> Rec field rs -> Rec field rs infixr 4 Source #

n %%~ f is just a shortcut for fld n . _Just %~ f. You can use it to set nested records. For instance, myPerson & parent%%~age..~30 sets to 30 the age of the parent in the object myPerson.

(..~) :: (NamedField field, rs `HasField` (s :|: t), ShowPath s) => proxy (s :|: t) -> t -> Rec field rs -> Rec field rs infixr 4 Source #

n ..~ v is just a shortcut for fld n .~ Just v

>>> name ..~ "Bernard" $ defaultPerson
{age =: 12
, name =: "Bernard"
, size =: 130.0
}

renamedAs :: (ShowPath s', NamedField f) => proxy (s' :|: a) -> f (s :|: a) -> f (s' :|: a) Source #

Change the name of a field from the name of another

rsubset :: (Functor g, ss `Includes` rs) => (Rec f rs -> g (Rec f rs)) -> Rec f ss -> g (Rec f ss) Source #

Just a version of rsubset that uses the Includes constraint, for better error messages

rcast :: ss `Includes` rs => Rec f ss -> Rec f rs Source #

Just a version of rcast that uses the Includes constraint, for better error messages

rreplace :: ss `Includes` rs => Rec f rs -> Rec f ss -> Rec f ss Source #

Just a version of rcast that uses the Includes constraint, for better error messages

rcastAs :: rs `Includes` selected => p selected -> Rec f rs -> Rec f selected Source #

Splits a record in two parts by using an existing record type.

rsplit :: (rs `Includes` selected, rs `Includes` (rs `Difference` selected)) => Rec f rs -> (Rec f selected, Rec f (rs `Difference` selected)) Source #

Splits a record in two parts.

rsplitFrom :: (rs `Includes` selected, rs `Includes` (rs `Difference` selected)) => p selected -> Rec f rs -> (Rec f selected, Rec f (rs `Difference` selected)) Source #

Splits a record in two parts by using an existing record type.

rdifference :: (rs `Includes` selected, rs `Includes` (rs `Difference` selected)) => Rec f rs -> p selected -> Rec f (rs `Difference` selected) Source #

Subtracts one record from another. In other term, splits a record in two parts by selecting the fields from an existing record

rintersection :: (a `Includes` (a `Difference` b), a `Includes` (a `Intersection` b), b `Includes` (b `Intersection` a), b `Includes` (b `Difference` a)) => Rec f a -> Rec f b -> (Rec f (a `Difference` b), Rec f (a `Intersection` b), Rec f (b `Intersection` a), Rec f (b `Difference` a)) Source #

Returns (fields only in a, values in a of fields in both, values in b of fields in both, fields only in b)

class PrefixPath (s :: [Symbol]) rs where Source #

Associated Types

type PrefixingAll s rs :: [PathWithType [Symbol] *] Source #

Methods

prefixPath :: NamedField f => Rec f rs -> Rec f (s `PrefixingAll` rs) Source #

Instances
PrefixPath s ([] :: [PathWithType [Symbol] Type]) Source # 
Instance details

Defined in Data.DocRecord

Associated Types

type PrefixingAll s [] :: [PathWithType [Symbol] Type] Source #

Methods

prefixPath :: NamedField f => Rec f [] -> Rec f (PrefixingAll s []) Source #

(PrefixPath s ps, ShowPath (s ++ p1)) => PrefixPath s ((p1 :|: t) ': ps) Source # 
Instance details

Defined in Data.DocRecord

Associated Types

type PrefixingAll s ((p1 :|: t) ': ps) :: [PathWithType [Symbol] Type] Source #

Methods

prefixPath :: NamedField f => Rec f ((p1 :|: t) ': ps) -> Rec f (PrefixingAll s ((p1 :|: t) ': ps)) Source #

rinclude :: forall s rs. (PrefixPath s rs, ShowPath s) => IntermediaryLevel s rs -> DocRec (FlattenedLevel s rs) Source #

Flatten a field of records into a record by altering the path of each subfield

(-.) :: (ComposableNesting f lvl2, NestedLvlConstraints rs f p lvl2, ShowPath (s ++ p)) => IntermediaryLevel s rs -> f (p :|: lvl2) -> NestedLvl s f p lvl2 infixr 9 Source #

Appends together two fields in a nested fashion. Will build either a final DocField or another IntermediaryLevel, depending on the second argument.

rdrill :: forall s inner outer f. (inner ~ (s `UnprefixingAll` (s `PrefixingAll` inner)), UnprefixPath s (s `PrefixingAll` inner), outer `Includes` (s `PrefixingAll` inner), NamedField f) => IntermediaryLevel s inner -> Rec f outer -> Rec f inner Source #

Selects a subrecord from a record r, using an IntermediaryLevel. (This IntermediaryLevel has normally originally been passed to rinclude to obtain r)

rsplitDrill :: forall s inner outer f. (inner ~ (s `UnprefixingAll` (s `PrefixingAll` inner)), UnprefixPath s (s `PrefixingAll` inner), outer `Includes` (s `PrefixingAll` inner), outer `Includes` (outer `Difference` FlattenedLevel s inner), NamedField f) => IntermediaryLevel s inner -> Rec f outer -> (Rec f inner, Rec f (outer `Difference` FlattenedLevel s inner)) Source #

Combines a drill and a split

rfoldSubset Source #

Arguments

:: (outer `Includes` inner, ((p :|: t) ': outer) `Includes` outer') 
=> proxy inner

The list of fields to target

-> (Rec f inner -> f (p :|: t)) 
-> Rec f outer 
-> Rec f outer' 

Merges a whole subset of the tree to a single field

funder :: forall s p t. ShowPath (s ': p) => DocField (p :|: t) -> DocField ((s ': p) :|: t) Source #

A version of '(-.)' for when you don't have an IntermediaryLevel to use as prefix and just want a single-symbol prefix

runder :: forall s selected f. (PrefixPath '[s] selected, NamedField f) => Rec f selected -> Rec f ('[s] `PrefixingAll` selected) Source #

A version of '(-/)' for when you don't have an IntermediaryLevel to use as prefix and just want a single-symbol prefix

(-/) :: forall s rs selected f. (rs `Includes` selected, PrefixPath s selected, NamedField f) => IntermediaryLevel s rs -> Rec f selected -> Rec f (s `PrefixingAll` selected) infixr 6 Source #

A version of '(-.)' for altering the paths of a whole record at once

withSameFields :: Rec f rs -> Rec g rs -> t -> t Source #

Just a helper to fix some types

(&:) :: t -> Rec IdentityField ts -> Rec IdentityField (t ': ts) infixr 5 Source #

Just a shortcut to build identity records (i.e. simple heterogeneous lists. Useful for applying different function over different fields of a record with ApplyRec

recFrom :: forall f rs. BuildRecFrom f rs '[] (FirstFieldSkipped rs) => DocRec rs -> RecCtor f rs '[] (FirstFieldSkipped rs) Source #

Generic construct for records. It takes as many arguments as the example DocRec contains fields, except for MD fields which are skipped.

invertRecBij :: RecBijection f as bs -> RecBijection f bs as Source #

Returns the inverse of the bijection

(<<|>>) :: ((as `Intersection` as') ~ '[], (bs `Intersection` bs') ~ '[], (as ++ as') `Includes` as, (as ++ as') `Includes` as', (bs ++ bs') `Includes` bs, (bs ++ bs') `Includes` bs') => RecBijection f as bs -> RecBijection f as' bs' -> RecBijection f (as ++ as') (bs ++ bs') Source #

Composes two RecBijections in a parallel fashion.

bijectField :: forall s f a b. (ShowPath s, NamedField f) => (a -> b) -> (b -> a) -> RecBijection f '[s :|: a] '[s :|: b] Source #

Creates a RecBijection that just maps over a singleton Rec

bijectField' :: forall s s' f a b. (ShowPath s, ShowPath s', NamedField f) => (a -> b) -> (b -> a) -> RecBijection f '[s :|: a] '[s' :|: b] Source #

Creates a RecBijection that just maps over a singleton Rec and changes the name along

renameField :: forall s s' f a. (ShowPath s, ShowPath s', NamedField f) => RecBijection f '[s :|: a] '[s' :|: a] Source #

Creates a RecBijection that changes the path of the field in a singleton Rec

addConstField :: forall s f a. f (s :|: a) -> RecBijection f '[] '[s :|: a] Source #

Just adds a field that will be constant

bijectUnder :: forall s f as bs. (as ~ UnprefixingAll s (PrefixingAll s as), bs ~ UnprefixingAll s (PrefixingAll s bs), PrefixPath s as, PrefixPath s bs, NamedField f, UnprefixPath s (PrefixingAll s as), UnprefixPath s (PrefixingAll s bs)) => RecBijection f as bs -> RecBijection f (s `PrefixingAll` as) (s `PrefixingAll` bs) Source #

A version of '(-/)' for RecBijections

showDocumentation Source #

Arguments

:: (ShowPath `AllFst` rs, Typeable `AllSnd` rs) 
=> Int

Character limit for types

-> Rec (Compose WithDoc field) rs 
-> Text 

Displays all the field names, types, and documentation contained in a record

>>> T.putStrLn $ showDocumentation 20 defaultPerson
age :: Int : This is the field giving the age
name :: [Char] : This is the field giving the name
size :: Double : This is the field giving the size (in cm)