Safe Haskell | None |
---|---|
Language | Haskell2010 |
Extensions |
|
Impl is intended to be used as an alternative to the normal default typeclass methods machinery of Haskell.
In contrast with intrinsic-superclasses
, we must specify each link of the implementation heirarchy with an instance of Impl, rather than infer it from the superclass heirarchy.
The benefit of this more explicit style is complete control over default methods provided by subclasses, at the cost of some automation for the class creator.
Impl is most valuable when instantiating deep (or even undecidably recursive) typeclass hierarchies for multiple new datatypes, which is most common in client code.
Synopsis
- class Impl c where
- data Method a
- data Symbol
- type NamedMethods c = NamedExpQ (Methods c)
- type family NamedExpQ ss where ...
- type family as :-> r where ...
- type (:!) (name :: Symbol) a = NamedF Identity a name
- type (:?) (name :: Symbol) a = NamedF Maybe a name
- ($$) :: WithParam p fn fn' => fn -> Param p -> fn'
- defaults :: Param Defaults
- arg :: Name name -> (name :! a) -> a
- arg' :: Name name -> a -> (name :? a) -> a
- data Param p
- data NamedF (f :: Type -> Type) a (name :: Symbol) where
- methodsFor :: Name -> TypeQ
- type family (as :: [x]) ++ (bs :: [x]) :: [x] where ...
- type TypeQ = Q Type
- type DecsQ = Q [Dec]
The core Impl class
Typeclasses implementing Impl can build declaratios for their entire superclass heirarchy
from a collection of required or optional named methods, allowing potentially complex logic for defaulting.
See the example
internal library for how to implement instances of Impl
.
(Kind) This is the kind of type-level symbols. Declared here because class IP needs it
Instances
SingKind Symbol | Since: base-4.9.0.0 |
KnownSymbol a => SingI (a :: Symbol) | Since: base-4.9.0.0 |
Defined in GHC.Generics sing :: Sing a | |
data Sing (s :: Symbol) | |
Defined in GHC.Generics | |
type DemoteRep Symbol | |
Defined in GHC.Generics |
Reexported from base
type NamedMethods c = NamedExpQ (Methods c) Source #
type family NamedExpQ ss where ... Source #
>>>
:kind! NamedExpQ '[Required "foo", Optional "bar"]
= '["foo" :! ExpQ,"bar" :? ExpQ]
type family as :-> r where ... infixr 0 Source #
Converts a variable number of arguments into curried form. Ex:
>>>
:!kind '[Int,String,Double] :-> IO ()
Int -> String -> Double -> IO ()
Utilities for Named arguments
impl
uses Named arguments, which work best with OverloadedLabels
type (:!) (name :: Symbol) a = NamedF Identity a name #
Infix notation for the type of a named parameter.
A required named argument.
>>>
#foo 'a' :: "foo" :! Char
type (:?) (name :: Symbol) a = NamedF Maybe a name #
Infix notation for the type of an optional named parameter.
An optional named argument
>>>
#foo 'b' :: "foo" :? Char
($$) :: WithParam p fn fn' => fn -> Param p -> fn' Source #
Pass a named (optional or required) argument to a function in any order.
foo :: ("bar" :! String) -> ("baz" :? Char) -> IO ()
>>>
foo $$ #baz 'a' :: ("bar" :! String) -> IO ()
A special Param
to fill in the remaining Optional
arguments with Nothing
foo :: ("bar" :! String) -> ("baz" :? Char) -> ("quox" :? Int) -> IO ()
>>>
foo $$ #bar "Hello" $$ defaults :: IO ()
arg :: Name name -> (name :! a) -> a #
arg
unwraps a named parameter with the specified name. One way to use it is
to match on arguments with -XViewPatterns
:
fn (arg #t -> t) (arg #f -> f) = ...
This way, the names of parameters can be inferred from the patterns: no type
signature for fn
is required. In case a type signature for fn
is
provided, the parameters must come in the same order:
fn :: "t" :! Integer -> "f" :! Integer -> ... fn (arg #t -> t) (arg #f -> f) = ... -- ok fn (arg #f -> f) (arg #t -> t) = ... -- does not typecheck
arg
unwraps a named parameter with the specified name. One way to use it is
to match on arguments with -XViewPatterns
:
fn (arg #t -> t) (arg #f -> f) = ...
This way, the names of parameters can be inferred from the patterns: no type
signature for fn
is required. In case a type signature for fn
is
provided, the parameters must come in the same order:
fn :: "t" :! Integer -> "f" :! Integer -> ... fn (arg #t -> t) (arg #f -> f) = ... -- ok fn (arg #f -> f) (arg #t -> t) = ... -- does not typecheck
A parameter passable as a named argument. Used implicitly by '($$)' with @OverloadedLabels
data NamedF (f :: Type -> Type) a (name :: Symbol) where #
Assign a name to a value of type a
wrapped in f
.
#verbose True :: NamedF Identity Bool "verbose"
A named argument that could be required or optional depending on the f
parameter