Safe Haskell | None |
---|---|
Language | Haskell2010 |
Continuations, modelled as functions wrapped in a contravariant functor.
Synopsis
- newtype r ! a = K {
- (!) :: a -> r
- class Contravariant (f :: Type -> Type) where
- class Contravariant f => Representable (f :: Type -> Type) where
- idK :: a ! a
Continuations
newtype r ! a infixl 7 Source #
Continuations, represented as functions. Note that the type parameters are in the opposite order, making this type a Contravariant
functor.
Instances
ContravariantCPS r ((!) r) Source # | |
Contrapplicative r ((!) r) Source # | |
Contrapply r ((!) r) Source # | |
Contravariant ((!) r) Source # | |
Representable ((!) r) Source # | |
Category (!) Source # | |
r ~ s => Adjunction ((!) r) ((!) s) Source # | |
Defined in Data.Functor.Continuation | |
type Rep ((!) r) Source # | |
Defined in Data.Functor.Continuation |
Contravariant
class Contravariant (f :: Type -> Type) where #
The class of contravariant functors.
Whereas in Haskell, one can think of a Functor
as containing or producing
values, a contravariant functor is a functor that can be thought of as
consuming values.
As an example, consider the type of predicate functions a -> Bool
. One
such predicate might be negative x = x < 0
, which
classifies integers as to whether they are negative. However, given this
predicate, we can re-use it in other situations, providing we have a way to
map values to integers. For instance, we can use the negative
predicate
on a person's bank balance to work out if they are currently overdrawn:
newtype Predicate a = Predicate { getPredicate :: a -> Bool } instance Contravariant Predicate where contramap f (Predicate p) = Predicate (p . f) | `- First, map the input... `----- then apply the predicate. overdrawn :: Predicate Person overdrawn = contramap personBankBalance negative
Any instance should be subject to the following laws:
Note, that the second law follows from the free theorem of the type of
contramap
and the first law, so you need only check that the former
condition holds.
Instances
class Contravariant f => Representable (f :: Type -> Type) where #
Instances
Representable Predicate | |
Representable (U1 :: Type -> Type) | |
Representable (Op r) | |
Representable (Proxy :: Type -> Type) | |
Representable ((!) r) Source # | |
(Representable f, Representable g) => Representable (f :*: g) | |
(Representable f, Representable g) => Representable (Product f g) | |