| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Data.Label.Derive
Contents
Description
Template Haskell functions for automatically generating labels for algebraic
datatypes, newtypes and GADTs. There are two basic modes of label generation,
the mkLabels family of functions create labels (and optionally type
signatures) in scope as top level funtions, the getLabel family of funtions
create labels as expressions that can be named and typed manually.
In the case of multi-constructor datatypes some fields might not always be
available and the derived labels will be partial. Partial labels are provided
with an additional type context that forces them to be only usable in the
Partial or Failing context.
- mkLabel :: Name -> Q [Dec]
- mkLabels :: [Name] -> Q [Dec]
- mkLabelsNamed :: (String -> String) -> [Name] -> Q [Dec]
- getLabel :: Name -> Q Exp
- fclabels :: Q [Dec] -> Q [Dec]
- mkLabelsWith :: (String -> String) -> Bool -> Bool -> Bool -> Bool -> Name -> Q [Dec]
- getLabelWith :: Bool -> Bool -> Bool -> Name -> Q Exp
- defaultNaming :: String -> String
Generate labels in scope.
mkLabel :: Name -> Q [Dec] Source
Derive labels including type signatures for all the record selectors in a single datatype. The types will be polymorphic and can be used in an arbitrary context.
mkLabels :: [Name] -> Q [Dec] Source
Derive labels including type signatures for all the record selectors for a collection of datatypes. The types will be polymorphic and can be used in an arbitrary context.
mkLabelsNamed :: (String -> String) -> [Name] -> Q [Dec] Source
Like mkLabels, but uses the specified function to produce custom names
 for the labels.
For instance, (drop 1 . dropWhile (/='_')) creates a label
 val from a record Rec { rec_val :: X }.
Produce labels as expressions.
getLabel :: Name -> Q Exp Source
Derive unnamed labels as n-tuples that can be named manually. The types will be polymorphic and can be used in an arbitrary context.
Example:
(left, right) = $(getLabel ''Either)
The lenses can now also be typed manually:
left :: (Either a b -> Either c b) :~> (a -> c) right :: (Either a b -> Either a c) :~> (b -> c)
Note: Because of the abstract nature of the generated lenses and the top
 level pattern match, it might be required to use NoMonomorphismRestriction
 in some cases.
First class record labels.
fclabels :: Q [Dec] -> Q [Dec] Source
Derive labels for all the record types in the supplied declaration. The record fields don't need an underscore prefix. Multiple data types / newtypes are allowed at once.
The advantage of this approach is that you don't need to explicitly hide the
 original record accessors from being exported and they won't show up in the
 derived Show instance.
Example:
fclabels [d|
  data Record = Record
    { int  :: Int
    , bool :: Bool
    } deriving Show
  |]ghci> modify int (+2) (Record 1 False) Record 3 False
Low level derivation functions.
Arguments
| :: (String -> String) | Supply a function to perform custom label naming. | 
| -> Bool | Generate type signatures or not. | 
| -> Bool | Generate concrete type or abstract type. When
   true the signatures will be concrete and can only
   be used in the appropriate context. Total labels
   will use ( | 
| -> Bool | |
| -> Bool | Generate inline pragma or not. | 
| -> Name | The type to derive labels for. | 
| -> Q [Dec] | 
Low level standalone label derivation function.
Arguments
| :: Bool | Generate type signatures or not. | 
| -> Bool | Generate concrete type or abstract type. When true the
   signatures will be concrete and can only be used in the
   appropriate context. Total labels will use ( | 
| -> Bool | |
| -> Name | The type to derive labels for. | 
| -> Q Exp | 
Low level label as expression derivation function.
defaultNaming :: String -> String Source
Default way of generating a label name from the Haskell record selector
 name. If the original selector starts with an underscore, remove it and make
 the next character lowercase. Otherwise, add l, and make the next
 character uppercase.