lenses-0.1.2: Simple Functional LensesSource codeContentsIndex
Data.Lenses.Template
Description

This module provides an automatic Template Haskell routine to scour data type definitions and generate lense objects for them automatically.

It was copied almost verbatim (2 line change) from the wonderful Data.Accessors.Template module made by Luke Palmer, and Henning Thielemann.

You will need to add:

{-# LANGUAGE TemplateHaskell, FlexibleContexts #-}

to the top of any modules that use this one.

Synopsis
nameDeriveLenses :: Name -> (String -> Maybe String) -> Q [Dec]
deriveLenses :: Name -> Q [Dec]
Documentation
nameDeriveLenses :: Name -> (String -> Maybe String) -> Q [Dec]Source
nameDeriveLenses n f where n is the name of a data type declared with data and f is a function from names of fields in that data type to the name of the corresponding accessor. If f returns Nothing, then no accessor is generated for that field.
deriveLenses :: Name -> Q [Dec]Source

deriveLenses n where n is the name of a data type declared with data looks through all the declared fields of the data type, and for each field ending in an underscore generates an accessor of the same name without the underscore.

It is nameDeriveLenses n f where f satisfies

 f (s ++ "_") = Just s
 f x          = Nothing    -- otherwise

For example, given the data type:

 data Score = Score { p1Score_ :: Int
                    , p2Score_ :: Int
                    , rounds   :: Int
                    }

deriveLenses will generate the following objects:

 p1Score :: (MonadState Score m) => StateT Int m b -> m b
 p1Score = fromGetSet p1Score_ (\x s -> s { p1Score_ = x })
 p2Score :: (MonadState Score m) => StateT Int m b -> m b
 p2Score = fromGetSet p2Score_ (\x s -> s { p2Score_ = x })

It is used with Template Haskell syntax like:

 $( deriveLenses ''TypeName )

And will generate accessors when TypeName was declared using data or newtype.

Produced by Haddock version 2.4.2