Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- class ArgDict f where
- type ConstraintsFor f (c :: k -> Constraint) :: Constraint
- type ConstraintsFor' f (c :: k -> Constraint) (g :: k' -> k) :: Constraint
- class ArgDictV f where
- type ConstraintsForV (f :: (k -> k') -> *) (c :: k' -> Constraint) (g :: k) :: Constraint
- type Has (c :: k -> Constraint) f = (ArgDict f, ConstraintsFor f c)
- type Has' (c :: k -> Constraint) f (g :: k' -> k) = (ArgDict f, ConstraintsFor' f c g)
- type HasV c f g = (ArgDictV f, ConstraintsForV f c g)
- has :: forall c f a r. Has c f => f a -> (c a => r) -> r
- has' :: forall c g f a r. Has' c f g => f a -> (c (g a) => r) -> r
- hasV :: forall c g f v r. HasV c f g => f v -> (c (v g) => r) -> r
- whichever :: forall c t a r. ForallF c t => (c (t a) => r) -> r
- class Implies1 c d where
Documentation
class ArgDict f where Source #
Morally, this class is for GADTs whose indices can be finitely enumerated. It provides operations which will select the appropriate type class dictionary from among a list of contenders based on a value of the type. There are a few different variations of this which we'd like to be able to support, and they're all implemented in the same fashion at the term level, by pattern matching on the constructors of the GADT, and producing Dict as the result. It would be nice to have some way to stop the proliferation of these variants and unify the existing ones, but at the moment, it appears to require honest type level functions. (Closed type families which must be fully applied didn't quite cut it when I tried). Some symbolic type-level application could do the trick, but I didn't want to go quite that far at the time of writing.
type ConstraintsFor f (c :: k -> Constraint) :: Constraint Source #
type ConstraintsFor' f (c :: k -> Constraint) (g :: k' -> k) :: Constraint Source #
argDict :: ConstraintsFor f c => f a -> Dict (c a) Source #
argDict' :: ConstraintsFor' f c g => f a -> Dict (c (g a)) Source #
class ArgDictV f where Source #
This places a tighter restriction on the kind of f, and so needs to be a separate class.
type ConstraintsForV (f :: (k -> k') -> *) (c :: k' -> Constraint) (g :: k) :: Constraint Source #
argDictV :: ConstraintsForV f c g => f v -> Dict (c (v g)) Source #
type Has (c :: k -> Constraint) f = (ArgDict f, ConstraintsFor f c) Source #
type Has' (c :: k -> Constraint) f (g :: k' -> k) = (ArgDict f, ConstraintsFor' f c g) Source #
type HasV c f g = (ArgDictV f, ConstraintsForV f c g) Source #