singletons-th-3.2: A framework for generating singleton types
Copyright(C) 2019 Ryan Scott
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Singletons.TH.Options

Description

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

Options

data Options Source #

Options that control the finer details of how singletons-th's 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 #

If True, then quoted declarations will be generated alongside their promoted and singled counterparts. If False, then quoted declarations will be discarded.

genSingKindInsts :: Options -> Bool Source #

If True, then SingKind instances will be generated. If False, they will be omitted entirely. This can be useful in scenarios where TH-generated SingKind instances do not typecheck (for instance, when generating singletons for GADTs).

promotedDataTypeOrConName :: Options -> Name -> Name Source #

Given the name of the original data type or data constructor, produces the name of the promoted equivalent. Unlike the singling-related options, in which there are separate singledDataTypeName and singledDataConName functions, we combine the handling of promoted data types and data constructors into a single option. This is because the names of promoted data types and data constructors can be difficult to distinguish in certain contexts without expensive compile-time checks.

Because of the DataKinds extension, most data type and data constructor names can be used in promoted contexts without any changes. As a result, this option will act like the identity function 99% of the time. There are some situations where it can be useful to override this option, however, as it can be used to promote primitive data types that do not have proper type-level equivalents, such as Natural and Text. See the "Arrows, Nat, Symbol, and literals" section of the singletons README for more details.

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 Maybe Uniq argument. If promoting a top-level name, the argument is 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.

Instances

Instances details
OptionsMonad Q Source # 
Instance details

Defined in Data.Singletons.TH.Options

DsMonad m => OptionsMonad (OptionsM m) Source #

Turn any DsMonad into an OptionsMonad.

Instance details

Defined in Data.Singletons.TH.Options

OptionsMonad m => OptionsMonad (DsM m) Source # 
Instance details

Defined in Data.Singletons.TH.Options

OptionsMonad m => OptionsMonad (ReaderT r m) Source # 
Instance details

Defined in Data.Singletons.TH.Options

Methods

getOptions :: ReaderT r m Options Source #

OptionsMonad m => OptionsMonad (StateT s m) Source # 
Instance details

Defined in Data.Singletons.TH.Options

Methods

getOptions :: StateT s m Options Source #

(OptionsMonad m, Monoid w) => OptionsMonad (WriterT w m) Source # 
Instance details

Defined in Data.Singletons.TH.Options

Methods

getOptions :: WriterT w m Options Source #

(OptionsMonad m, Monoid w) => OptionsMonad (RWST r w s m) Source # 
Instance details

Defined in Data.Singletons.TH.Options

Methods

getOptions :: RWST r w s m Options Source #

data OptionsM m a Source #

A convenient implementation of the OptionsMonad class. Use by calling withOptions.

Instances

Instances details
MonadTrans OptionsM Source # 
Instance details

Defined in Data.Singletons.TH.Options

Methods

lift :: Monad m => m a -> OptionsM m a

MonadFail m => MonadFail (OptionsM m) Source # 
Instance details

Defined in Data.Singletons.TH.Options

Methods

fail :: String -> OptionsM m a

MonadIO m => MonadIO (OptionsM m) Source # 
Instance details

Defined in Data.Singletons.TH.Options

Methods

liftIO :: IO a -> OptionsM m a

Applicative m => Applicative (OptionsM m) Source # 
Instance details

Defined in Data.Singletons.TH.Options

Methods

pure :: a -> OptionsM m a

(<*>) :: OptionsM m (a -> b) -> OptionsM m a -> OptionsM m b

liftA2 :: (a -> b -> c) -> OptionsM m a -> OptionsM m b -> OptionsM m c

(*>) :: OptionsM m a -> OptionsM m b -> OptionsM m b

(<*) :: OptionsM m a -> OptionsM m b -> OptionsM m a

Functor m => Functor (OptionsM m) Source # 
Instance details

Defined in Data.Singletons.TH.Options

Methods

fmap :: (a -> b) -> OptionsM m a -> OptionsM m b

(<$) :: a -> OptionsM m b -> OptionsM m a

Monad m => Monad (OptionsM m) Source # 
Instance details

Defined in Data.Singletons.TH.Options

Methods

(>>=) :: OptionsM m a -> (a -> OptionsM m b) -> OptionsM m b

(>>) :: OptionsM m a -> OptionsM m b -> OptionsM m b

return :: a -> OptionsM m a

DsMonad m => OptionsMonad (OptionsM m) Source #

Turn any DsMonad into an OptionsMonad.

Instance details

Defined in Data.Singletons.TH.Options

Quasi m => Quasi (OptionsM m) Source # 
Instance details

Defined in Data.Singletons.TH.Options

Methods

qNewName :: String -> OptionsM m Name

qReport :: Bool -> String -> OptionsM m ()

qRecover :: OptionsM m a -> OptionsM m a -> OptionsM m a

qLookupName :: Bool -> String -> OptionsM m (Maybe Name)

qReify :: Name -> OptionsM m Info

qReifyFixity :: Name -> OptionsM m (Maybe Fixity)

qReifyType :: Name -> OptionsM m Type

qReifyInstances :: Name -> [Type] -> OptionsM m [Dec]

qReifyRoles :: Name -> OptionsM m [Role]

qReifyAnnotations :: Data a => AnnLookup -> OptionsM m [a]

qReifyModule :: Module -> OptionsM m ModuleInfo

qReifyConStrictness :: Name -> OptionsM m [DecidedStrictness]

qLocation :: OptionsM m Loc

qRunIO :: IO a -> OptionsM m a

qGetPackageRoot :: OptionsM m FilePath

qAddDependentFile :: FilePath -> OptionsM m ()

qAddTempFile :: String -> OptionsM m FilePath

qAddTopDecls :: [Dec] -> OptionsM m ()

qAddForeignFilePath :: ForeignSrcLang -> String -> OptionsM m ()

qAddModFinalizer :: Q () -> OptionsM m ()

qAddCorePlugin :: String -> OptionsM m ()

qGetQ :: Typeable a => OptionsM m (Maybe a)

qPutQ :: Typeable a => a -> OptionsM m ()

qIsExtEnabled :: Extension -> OptionsM m Bool

qExtsEnabled :: OptionsM m [Extension]

qPutDoc :: DocLoc -> String -> OptionsM m ()

qGetDoc :: DocLoc -> OptionsM m (Maybe String)

Quote m => Quote (OptionsM m) Source # 
Instance details

Defined in Data.Singletons.TH.Options

Methods

newName :: String -> OptionsM m Name #

DsMonad m => DsMonad (OptionsM m) Source # 
Instance details

Defined in Data.Singletons.TH.Options

Methods

localDeclarations :: OptionsM m [Dec] #

withOptions :: Options -> OptionsM m a -> m a Source #

Declare the Options that a TH computation should use.