impl-0.2.0.0: Framework for defaulting superclasses

Safe HaskellNone
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • TemplateHaskell
  • TemplateHaskellQuotes
  • AllowAmbiguousTypes
  • TypeFamilies
  • ViewPatterns
  • PolyKinds
  • DataKinds
  • KindSignatures
  • TypeOperators
  • ExplicitNamespaces
  • LambdaCase
  • OverloadedLabels
  • PatternSynonyms
  • TypeApplications

Impl

Contents

Description

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

The core Impl class

class Impl c where Source #

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.

Associated Types

type Methods c :: [Method Symbol] Source #

Methods

impl :: TypeQ -> NamedMethods c :-> DecsQ Source #

Instantiate the implementing class along with all its superclasses Ex:

impl @Monad [t|[]|]
  $$ #return [|\x -> [x]|]
  $$ #bind   [|flip concatMap|]

data Method a Source #

Constructors

Required a 
Optional a 

data Symbol #

(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

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep Symbol :: Type

Methods

fromSing :: Sing a -> DemoteRep Symbol

KnownSymbol a => SingI (a :: Symbol)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing a

data Sing (s :: Symbol) 
Instance details

Defined in GHC.Generics

data Sing (s :: Symbol) where
type DemoteRep Symbol 
Instance details

Defined in GHC.Generics

type DemoteRep Symbol = String

Reexported from base

type NamedMethods c = NamedExpQ (Methods c) Source #

Named TH Exps for the class method implementations

type family NamedExpQ ss where ... Source #

>>> :kind! NamedExpQ '[Required "foo", Optional "bar"]
= '["foo" :! ExpQ,"bar" :? ExpQ]

Equations

NamedExpQ '[] = '[] 
NamedExpQ (Required s ': ss) = (s :! ExpQ) ': NamedExpQ ss 
NamedExpQ (Optional s ': ss) = (s :? ExpQ) ': NamedExpQ ss 

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 ()

Equations

(a ': as) :-> r = a -> as :-> r 
'[] :-> r = r 

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 ()

defaults :: Param Defaults #

Passing defaults to a function fills all unspecified optional parameters with Nothing:

fn            :: "b" :! Bool -> "x" :? Char -> Int -> IO ()
fn ! defaults :: "b" :! Bool ->                Int -> 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

arg' :: Name name -> a -> (name :? a) -> a Source #

A variation of arg for optional arguments. Requires a default value to handle the case when the optional argument was omitted:

 fn (arg' #answer 42 -> ans) = ...

In case you want to get a value wrapped in Maybe instead, Arg'

data Param p #

Instances
(p ~ NamedF f a name, InjValue f) => IsLabel name (a -> Param p) 
Instance details

Defined in Named.Internal

Methods

fromLabel :: a -> Param p #

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"

Bundled Patterns

pattern Arg :: forall a (name :: Symbol). a -> name :! a

Match on an argument without specifying its name. See also: arg.

pattern Arg' :: Maybe a -> name :? a

Construct or match an optional named argument

Instances
(name ~ name', a ~ a', InjValue f) => IsLabel name (a -> NamedF f a' name') 
Instance details

Defined in Named.Internal

Methods

fromLabel :: a -> NamedF f a' name' #

A named argument that could be required or optional depending on the f parameter

TH reexports and utilities

methodsFor Source #

Arguments

:: Name

Typeclass name

-> TypeQ
 :: [Method Symbol]

Deprecated: reify doesn't currently allow introspecting default definitions, so they are always Required

Retrieve the method names of a typeclass as a typelevel list of Method Symbols. A good default for instantiating the Methods type, which is robust against changing method names.

type family (as :: [x]) ++ (bs :: [x]) :: [x] where ... Source #

Type level list append

Equations

'[] ++ bs = bs 
(a ': as) ++ bs = a ': (as ++ bs) 

type TypeQ = Q Type #

type DecsQ = Q [Dec] #