| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Prairie.Class
Description
This module defines the type class Record which enables much of the
 functionality of the library. You can define instances of this record
 manually, or you may use the TemplateHaskell deriving function in
 Prairie.TH.
We'll use an example type User throughout the documentation in this
 module.
data User = User
 { name :: String
 , age :: Int
 }
Since: 0.0.1.0
Synopsis
- class Record rec where- data Field rec :: Type -> Type
- recordFieldLens :: Field rec ty -> Lens' rec ty
- tabulateRecordA :: Applicative m => (forall ty. Field rec ty -> m ty) -> m rec
- recordFieldLabel :: Field rec ty -> Text
 
- allFields :: Record rec => [SomeField rec]
- tabulateRecord :: Record rec => (forall ty. Field rec ty -> ty) -> rec
- fieldMap :: Record rec => Map Text (SomeField rec)
- getRecordField :: Record rec => Field rec ty -> rec -> ty
- setRecordField :: Record rec => Field rec ty -> ty -> rec -> rec
- data SomeField rec where
- class Record r => FieldDict (c :: Type -> Constraint) (r :: Type) where- getFieldDict :: Field r a -> Dict (c a)
 
- withFieldDict :: forall c rec a r. FieldDict c rec => Field rec a -> (c a => r) -> r
- class Record rec => SymbolToField (sym :: Symbol) (rec :: Type) (a :: Type) | rec sym -> a where- symbolToField :: Field rec a
 
Documentation
class Record rec where Source #
Instances of this class have a datatype Field which allow you to
 represent fields as a concrete datatype. This allows you to have
 significant flexibility in working with data.
Since: 0.0.1.0
Minimal complete definition
Associated Types
data Field rec :: Type -> Type Source #
A datatype representing fields on the record.
This will be a GADT with one constructor for each record field. By
 convention, it's best to name the constructors as with the type name
 leading and the field name following. This convention prevents any
 possible conflicts from different instances of Field.
Using our example type User, we would define this as:
data Field User ty where UserName :: Field User String UserAge :: Field User Int
Now, we have a value UserName that corresponds with the name field
 on a User. The type of User and name are interesting to compare:
UserName :: Field User String name :: User -> String
Since: 0.0.1.0
Methods
recordFieldLens :: Field rec ty -> Lens' rec ty Source #
Given a Field on the record, this function acts as a Lens' into
 the record. This allows you to use a Field as a getter or setter.
An example implementation for our User type might look like this:
recordFieldLens field =
  case field of
    UserName ->
      lens name (\u n -> u { name = n })
    UserAge ->
     lens age (\u a -> u { age = a })
If you have derived lenses (either from Template Haskell or
 generic-lens, then you can provide those directly.
Since: 0.0.1.0
tabulateRecordA :: Applicative m => (forall ty. Field rec ty -> m ty) -> m rec Source #
Construct a Record by providing an Applicative action
 returning a value for each Field on the Record.
Example:
tabulateRecordA $ \field -> case field of
    UserName -> Just "Matt"
    UserAge -> Nothing
tabulateRecordA $ \field -> case field of
    UserName -> getLine
    UserAge -> do
        ageStr <- getLine
        case readMaybe ageStr of
            Nothing -> fail $ "Expected Int, got: " <> ageStr
            Just a -> pure a
Since: 0.0.2.0
recordFieldLabel :: Field rec ty -> Text Source #
Assign a Text label for a record Field.
This allows Fields to be converted to Text, which is useful for
 serialization concerns. For derserializing a Field, consider using
 fieldMap :: Map Text (SomeField rec)
Record field labels can be given a stock derived Show instance,
 which works for the default implementation of the class.
Since: 0.0.1.0
allFields :: Record rec => [SomeField rec] Source #
An enumeration of fields on the record.
This value builds the fields using tabulateRecordA and the Const
 type.
As of 0.0.2.0, this is an ordinary top-level function and not a class
 member.
Since: 0.0.1.0
tabulateRecord :: Record rec => (forall ty. Field rec ty -> ty) -> rec Source #
This function allows you to construct a Record by providing
 a value for each Field on the record.
As of 0.0.2.0, this is defined in terms of tabulateRecordA.
Since: 0.0.1.0
getRecordField :: Record rec => Field rec ty -> rec -> ty Source #
Use a Field to access the corresponding value in the record.
Since: 0.0.1.0
setRecordField :: Record rec => Field rec ty -> ty -> rec -> rec Source #
Use a Field to set the corresponding value in the record.
Since: 0.0.1.0
data SomeField rec where Source #
An existential wrapper on a Field. This hides the type of the value
 of the field. This wrapper allows you to have a collection of Fields
 for a record, or to have useful instances for classes like Eq where
 the type of the values being compared must be the same.
Since: 0.0.1.0
Instances
| Record rec => FromJSON (SomeField rec) Source # | This instance delegates to the underlying instance of  Since: 0.0.1.0 | 
| Defined in Prairie.Class | |
| (forall a. ToJSON (Field rec a)) => ToJSON (SomeField rec) Source # | This instance delegates to the underlying instance of  Since: 0.0.1.0 | 
| (forall a. Show (Field rec a)) => Show (SomeField rec) Source # | You can write a standalone deriving instance for  deriving stock instance This instance is derived, so it'll result in: >>> show (SomeField UserAge) SomeField UserAge Since: 0.0.1.0 | 
| (forall a. Eq (Field rec a), FieldDict (Typeable :: Type -> Constraint) rec) => Eq (SomeField rec) Source # | |
class Record r => FieldDict (c :: Type -> Constraint) (r :: Type) where Source #
This class allows you to summon a type class instance based on a Field
 of the record. Use this type class when you need to assert that all the
 fields of a record satisfy some type class instance.
For example, suppose we want to write a generic logging utility for all records where all fields on the record is loggable.
class Loggable a where toLog :: a -> LogMessage
We can implement a function based on Record to log it:
logRecord :: (FieldDict Loggable rec) => rec -> LogMessage logRecord record = foldMap goallFieldswhere go (SomeFieldfield) =withFieldDict@Loggable $ toLog (getRecordFieldfield record)
The second parameter to withFieldDict will have the instance of
 'Loggable a' in scope.
You can define instances polymorphic in the constraint with the
 ConstraintKinds language extension.
Since: 0.0.1.0
Arguments
| :: forall c rec a r. FieldDict c rec | |
| => Field rec a | The record field we want to unpack. We need this value in order to know what type we want the constraint to apply to. | 
| -> (c a => r) | A value that assumes the constraint  | 
| -> r | 
Given a record field :: , this function brings the
 type class instance Field rec ac a into scope for the third argument.
This function is intended to be used with a TypeApplication for the
 constraint you want to instantiate. It is most useful for working with
 generic records in type class instances.
Since: 0.0.1.0
class Record rec => SymbolToField (sym :: Symbol) (rec :: Type) (a :: Type) | rec sym -> a where Source #
This type class enables you to map a Symbols to a record Field.
To use this, you'll define an instance
instanceSymbolToField"age" User Int where symbolToField = UserAge instanceSymbolToField"name" User String where symbolToField = UserName
The main utility here is that you can then write OverloadedSymbols
 that correspond to record fields.
nameField :: (SymbolToField'"name" rec a) =>Fieldrec a nameField = #name userNameField ::FieldUser String userNameField = #name
Note that there's nothing forcing you to use a symbol that exactly matches the type. You can write multiple instances of this for each constructor. The following two instances are perfectly happy to live together.
instanceSymbolToField"name" User String where symbolToField = UserName instanceSymbolToField"userName" User String where symbolToField = UserName
Since: 0.0.1.0
Methods
symbolToField :: Field rec a Source #
This function is designed to be used with a type application:
symbolToField @"age"
Since: 0.0.1.0