Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
A collection of type-level operators.
- type (^>) = (->)
- type (<^) a b = (^>) b a
- type ($) f a = f a
- type (&) a f = f a
- type ($$) f a = f a
- type family (c :: [k -> Constraint]) <+> (a :: k) where ...
- type family (c :: k -> Constraint) <=> (as :: [k]) where ...
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 ($) f a = f a infixr 2 Source #
Infix application.
f :: Either String $ Maybe Int = f :: Either String (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 (c :: [k -> Constraint]) <+> (a :: k) where ... infixl 9 Source #
Map several constraints over a single variable.
a :: [Show, Read] <+> a => a -> a = a :: (Show a, Read a) => a -> a
'[] <+> a = (() :: Constraint) | |
(ch ': ct) <+> a = (ch a, (<+>) ct a) |
type family (c :: k -> Constraint) <=> (as :: [k]) where ... infixl 9 Source #
Map a constraint over several variables.
a :: Show <=> [a, b] => a -> b -> String = a :: (Show a, Show b) => a -> b -> String
c <=> '[] = (() :: Constraint) | |
c <=> (h ': t) = (c h, (<=>) c t) |