| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Interpolation.TH
Synopsis
- makeInterpolatorSumInstance :: Name -> Q [Dec]
- withUninterpolated :: Q [Dec] -> Q [Dec]
- withPolymorphic :: Q [Dec] -> Q [Dec]
- deriveUninterpolated :: Name -> Q [Dec]
Documentation
makeInterpolatorSumInstance :: Name -> Q [Dec] Source #
Make an instance of Default for Interpolator of an ADT. Can't do it for an arbitrary
Profunctor p because of partial functions. This splice is meant to be used in conjunction with
makeAdaptorAndInstance for records as a way to project Default instances down to all leaves.
data Foo' a b = Foo1 a | Foo2 b
makeInterpolatorSumInstance 'Foo
instance (Default Interpolator a1 b1, Default Interpolator a2 b2) => Default Interpolator (Foo' a1 a2) (Foo' b1 b2) where
def = Interpolator $ case
Foo1 x -> Foo1 $ runInterpolator def x
Foo2 x -> Foo2 $ runInterpolator def x
withUninterpolated :: Q [Dec] -> Q [Dec] Source #
When applied to a simple data type declaration, substitute a fully-polymorphic data type (suffixed with a "prime"), and type aliases for "normal" and "uninterpolated" variants.
For example, a record or newtype (using record syntax):
withUninterpolated [d|
data Foo = Foo
{ fooBar :: String
, fooBaz :: Maybe Int
} deriving (Eq, Show)
|]
Is equivalent to:
data Foo' bar baz = Foo
{ fooBar :: bar
, fooBaz :: baz
} deriving (Eq, Show)
type Foo = Foo' String (Maybe Int)
type UninterpolatedFoo = Foo' (Uninterpolated String) (Maybe (Uninterpolated Int))
Note: the trailing |] of the quasi quote bracket has to be indented or a parse error will occur.
A simple sum type whose constructors have one argument or less:
withUninterpolated [d|
data MaybeFoo
= AFoo Foo
| NoFoo
deriving (Eq, Show)
Expands to:
data MaybeFoo' aFoo
= AFoo aFoo
| NoFoo
deriving (Eq, Show)
type MaybeFoo = MaybeFoo' Foo
type UninterpolatedMaybeFoo = MaybeFoo' (Foo' (Uninterpolated String) (Maybe (Uninterpolated Int)))
-- Note: UninterpolatedMaybeFoo ~ MaybeFoo' UninterpolatedFoo
Whenever the type of a field is one for which an instance of FromTemplateValue is present, the
type is wrapped in Uninterpolated. Otherwise, an attempt is made to push Uninterpolated down
into the field's type, even if it's a type synonym such as one generated by this same macro.
Note: this splice is equivalent to withPolymorphic [d|data Foo ... |] followed by
deriveUninterpolated ''Foo.
withPolymorphic :: Q [Dec] -> Q [Dec] Source #
When applied to a simple data type declaration, substitute a fully-polymorphic data type (suffixed with a "prime"), and a simple type alias which matches the supplied declaration.
This splice does not include the corresponding Uninterpolated type, so it can be used separately
when needed. For example, if you want to define all your record types first, then define/derive
the Uninterpolated types for each. This can be important because the presence of a
FromTemplateValue instance, defined before the splice, will affect the shape of the derived
Uninterpolated type.
For example, a record or newtype (using record syntax):
withPolymorphic [d|
data Foo = Foo
{ fooBar :: String
, fooBaz :: Maybe Int
} deriving (Eq, Show)
|]
Is equivalent to:
data Foo' bar baz = Foo
{ fooBar :: bar
, fooBaz :: baz
} deriving (Eq, Show)
type Foo = Foo' String (Maybe Int)
Note: the trailing |] of the quasi quote bracket has to be indented or a parse error will occur.
deriveUninterpolated :: Name -> Q [Dec] Source #
Given the name of a type alias which specializes a polymorphic type (such as the "simple" type
generated by withPolymorphic), generate the corresponding Uninterpolated type alias which
replaces each simple type with an Uninterpolated form, taking account for which types have
FromTemplateValue instances.
Use this instead of withUninterpolated when you need to define instances for referenced types,
and you need flexibility in the ordering of declarations in your module's source.