type-operators-0.2.0.0: Various type-level operators

Safe HaskellSafe
LanguageHaskell2010

Control.Type.Operator

Description

A collection of type-level operators.

Synopsis

Documentation

type (^>) = (->) infixr 5 Source #

A tightly binding version of -> that lets you strip parentheses from function types in certain spots. Example:

f :: Maybe Int ^> String
=
f :: Maybe (Int -> String)

type (<^) a b = (^>) b a infixr 5 Source #

A flipped ^>.

f :: Maybe String <^ Int
=
f :: Maybe (Int -> String)

Note: this is not partially applied like ^> and ->.

type ($) f a = f a infixr 2 Source #

Infix application.

f :: Either String $ Maybe Int
=
f :: Either String (Maybe Int)

type (&) a f = f a infixl 1 Source #

A flipped $.

f :: Maybe Int & Maybe
=
f :: Maybe (Maybe Int)

type ($$) f a = f a infixr 3 Source #

Infix application that can take two arguments in combination with $.

f :: Either $$ Int ^> Int $ Int ^> Int
=
f :: Either (Int -> Int) (Int -> Int)

type family (a :: k1) <+> (b :: k2) :: Constraint infixl 9 Source #

Map any constraints over any type variables.

a :: [Show, Read] <+> a => a -> a
=
a :: (Show a, Read a) => a -> a

a :: Show <+> [a, b, c] => a -> b -> c -> String
=
a :: (Show a, Show b, Show c) => a -> b -> c -> String
Instances
type (_ :: k1) <+> [] Source # 
Instance details

Defined in Control.Type.Operator

type (_ :: k1) <+> [] = ()
type (c ': cs :: [Type -> Constraint]) <+> (a :: Type) Source # 
Instance details

Defined in Control.Type.Operator

type (c ': cs :: [Type -> Constraint]) <+> (a :: Type) = (c a, a <+> cs)
type [] <+> (_ :: k2) Source # 
Instance details

Defined in Control.Type.Operator

type [] <+> (_ :: k2) = ()
type (c :: k -> Constraint) <+> (a ': as :: [k]) Source # 
Instance details

Defined in Control.Type.Operator

type (c :: k -> Constraint) <+> (a ': as :: [k]) = (c a, c <+> as)

type family (c :: k -> Constraint) <=> (as :: [k]) where ... infixl 9 Source #

Deprecated: Since (+) is now kind-polymorphic and accepts the arguments on either side (=) will be removed in a future version.

Map a constraint over several variables.

a :: Show <=> [a, b] => a -> b -> String
=
a :: (Show a, Show b) => a -> b -> String

Equations

c <=> '[] = (() :: Constraint) 
c <=> (h ': t) = (c h, (<=>) c t)