{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE MonomorphismRestriction #-} {-# LANGUAGE StandaloneDeriving #-} {-# OPTIONS -fwarn-missing-signatures #-} module Generics.MultiRec.TH.Alt.DerivOptions ( DerivOptions(..), ) where data DerivOptions ft = DerivOptions { -- | A list of: -- -- > (type quotation, name of corresponding constructor of the family GADT) -- -- This defines our mutually recursive family. The types must resolve to -- @data@types or @newtype@s of kind @*@ (type synonyms will be expanded). familyTypes :: ft -- | Name of the family GADT (this type has to be generated -- manually because TH doesn't support GADTs yet) , indexGadtName :: String -- | Scheme for producing names for the -- empty types corresponding to constructors. The first arg is the name -- of the type (as given in 'familyTypes'), the second arg is the name -- of the constructor (builtins will be called: @NIL@, @CONS@, @TUPLE2@, @TUPLE3@ ...) , constructorNameModifier :: String -> String -> String -- | Name of the pattern functor ('PF') to generate , patternFunctorName :: String -- | Print various informational messges? , verbose :: Bool -- , mkSanityChecks :: Bool } instance Functor DerivOptions where fmap f d = d { familyTypes = (f . familyTypes) d }