Copyright | (C) 2019 Ryan Scott |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Ryan Scott |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module defines Options
that control finer details of how the Template
Haskell machinery works, as well as an mtl
-like OptionsMonad
class
and an OptionsM
monad transformer.
Synopsis
- data Options
- defaultOptions :: Options
- genQuotedDecs :: Options -> Bool
- genSingKindInsts :: Options -> Bool
- promotedClassName :: Options -> Name -> Name
- promotedValueName :: Options -> Name -> Maybe Uniq -> Name
- singledDataTypeName :: Options -> Name -> Name
- singledClassName :: Options -> Name -> Name
- singledDataConName :: Options -> Name -> Name
- singledValueName :: Options -> Name -> Name
- defunctionalizedName :: Options -> Name -> Int -> Name
- promotedTopLevelValueName :: Options -> Name -> Name
- promotedLetBoundValueName :: Options -> Name -> Uniq -> Name
- defunctionalizedName0 :: Options -> Name -> Name
- class DsMonad m => OptionsMonad m where
- getOptions :: m Options
- data OptionsM m a
- withOptions :: Options -> OptionsM m a -> m a
Options
Options that control the finer details of how singletons
' Template
Haskell machinery works.
defaultOptions :: Options Source #
Sensible default Options
.
genQuotedDecs
defaults to True
.
That is, quoted declarations are generated alongside their promoted and
singled counterparts.
genSingKindInsts
defaults to True
.
That is, SingKind
instances are generated.
The default behaviors for promotedClassName
, promotedValueNamePrefix
,
singledDataTypeName
, singledClassName
, singledDataConName
,
singledValueName
, and defunctionalizedName
are described in the
"On names" section of the singletons
README
.
Options record selectors
genQuotedDecs :: Options -> Bool Source #
genSingKindInsts :: Options -> Bool Source #
promotedClassName :: Options -> Name -> Name Source #
Given the name of the original, unrefined class, produces the name of the promoted equivalent of the class.
promotedValueName :: Options -> Name -> Maybe Uniq -> Name Source #
Given the name of the original, unrefined value, produces the name of
the promoted equivalent of the value. This is used for both top-level
and let
-bound names, and the difference is encoded in the
argument. If promoting a top-level name, the argument
is Maybe
Uniq
Nothing
. If promoting a let
-bound name, the argument is
Just uniq
, where uniq
is a globally unique number that can be used
to distinguish the name from other local definitions of the same name
(e.g., if two functions both use let x = ... in x
).
singledDataTypeName :: Options -> Name -> Name Source #
Given the name of the original, unrefined data type, produces the name of the corresponding singleton type.
singledClassName :: Options -> Name -> Name Source #
Given the name of the original, unrefined class, produces the name of the singled equivalent of the class.
singledDataConName :: Options -> Name -> Name Source #
Given the name of the original, unrefined data constructor, produces the name of the corresponding singleton data constructor.
singledValueName :: Options -> Name -> Name Source #
Given the name of the original, unrefined value, produces the name of the singled equivalent of the value.
defunctionalizedName :: Options -> Name -> Int -> Name Source #
Given the original name and the number of parameters it is applied to
(the Int
argument), produces a type-level function name that can be
partially applied when given the same number of parameters.
Note that defunctionalization works over both term-level names (producing symbols for the promoted name) and type-level names (producing symbols directly for the name itself). As a result, this callback is used for names in both the term and type namespaces.
Derived functions over Options
promotedTopLevelValueName :: Options -> Name -> Name Source #
Given the name of the original, unrefined, top-level value, produces the name of the promoted equivalent of the value.
promotedLetBoundValueName :: Options -> Name -> Uniq -> Name Source #
Given the name of the original, unrefined, let
-bound value and its
globally unique number, produces the name of the promoted equivalent of the
value.
defunctionalizedName0 :: Options -> Name -> Name Source #
Given the original name of a function (term- or type-level), produces a
type-level function name that can be partially applied even without being
given any arguments (i.e., 0
arguments).
OptionsMonad
class DsMonad m => OptionsMonad m where Source #
Class that describes monads that contain Options
.
getOptions :: m Options Source #
Instances
OptionsMonad Q Source # | |
Defined in Data.Singletons.TH.Options getOptions :: Q Options Source # | |
OptionsMonad m => OptionsMonad (DsM m) Source # | |
Defined in Data.Singletons.TH.Options getOptions :: DsM m Options Source # | |
DsMonad m => OptionsMonad (OptionsM m) Source # | Turn any |
Defined in Data.Singletons.TH.Options getOptions :: OptionsM m Options Source # | |
OptionsMonad m => OptionsMonad (ReaderT r m) Source # | |
Defined in Data.Singletons.TH.Options getOptions :: ReaderT r m Options Source # | |
OptionsMonad m => OptionsMonad (StateT s m) Source # | |
Defined in Data.Singletons.TH.Options getOptions :: StateT s m Options Source # | |
(OptionsMonad m, Monoid w) => OptionsMonad (WriterT w m) Source # | |
Defined in Data.Singletons.TH.Options getOptions :: WriterT w m Options Source # | |
(OptionsMonad m, Monoid w) => OptionsMonad (RWST r w s m) Source # | |
Defined in Data.Singletons.TH.Options getOptions :: RWST r w s m Options Source # |
A convenient implementation of the OptionsMonad
class. Use by calling
withOptions
.