first-class-instances-0.1.0.0: First class typeclass instances

Safe HaskellNone
LanguageHaskell2010

FCI

Description

First-class instances (FCI) - interface for explicit manipulation of representations of constraints.

Synopsis

Documentation

type Inst c = Inst c Source #

Type that maps constraint to it's representation. You can get hold of representation of some special constraints and classes that use mkInst.

For example:

class Bar a => Foo a where
  baz :: a
  qux :: a -> b -> [(a, b)]

mkInst 'Foo

creates datatype instance:

type instance Inst (Foo a) = Dict (Foo a)
data instance Dict (Foo a) = Foo{
    _Bar :: Inst (Bar a)
  , baz  :: a
  , qux  :: forall b. a -> b -> [(a, b)]
  }

You can get hold of representation of global instance using inst. You are free to modify and read it and you can use (==>) to apply it as constraint in context of some subexpression. See mkInst for more info about format of generated representation.

mkInst :: Name -> Q [Dec] Source #

Creates first class instance representation from based on class. Generated representation is record of class members following simple format:

  • name of record constructor is name of original class
  • superclass constraints are transformed into fields containing their representation, names of fields are generated this way:

    • Prefix names (Show, Applicative) are prefixed with _
    • Operators (('~')) are prefixed with ||
    • Tuples are converted into prefix names _Tuple
    • Additional occurencies of same prefix name get postfix index starting from 1
    • Additional occurencies of same operator are postfixed with increasing number of |s
  • methods get their own fields, names of fields are names of methods prefixed with _

To avoid possibly breaking assumptions author of class may have made about it's instances, you can only create representation for class in current module.

inst :: forall c. c => Inst c Source #

Reflects constraint into correspoding representation - can be used to access normal class instances from the environment. This function is meant to be used with TypeApplications when it's usage is ambiguous.

TODO: example

(==>) :: forall c r. Inst c -> (c => r) -> r infixr 0 Source #

Reifies first class instance into constraint in context of supplied continuation.

For example:

>>> newtype Foo a = Foo a deriving Show
>>> coerceFunctor @Foo ==> (+1) <$> Foo 1
Foo 2

type Newtype f = forall a. (Coercible a (f a), Coercible (f a) a) Source #

Allows to coerce type back and forth between it's argument when safe.

type Dict = Dict Source #

Type of representation of class instance. You can get instance for your class using mkInst and access value of global instance using inst. Prefer Inst in signatures when working with constraint representations.