| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Symantic.Base.Algebrable
Contents
Synopsis
- adt :: forall adt repr k. Dimapable repr => Generic adt => RepOfEoT adt => EoTOfRep adt => repr (EoT (ADT adt) -> k) k -> repr (adt -> k) k
- class Tupable repr where- (<:>) :: repr (a -> k) k -> repr (b -> k) k -> repr ((a, b) -> k) k
 
- class Unitable repr where- unit :: repr (() -> k) k
 
- class Constant repr where- constant :: a -> repr (a -> k) k
 
- class Eitherable repr where
- class Emptyable repr where- empty :: repr k k
 
- class Optionable repr where
- class Repeatable repr where
- class Substractable repr where- (<->) :: repr a k -> repr k' k' -> repr a k
 
- class Dicurryable repr where
- construct :: forall args a k repr. Dicurryable repr => Generic a => EoTOfRep a => CurryN args => Tuples args ~ EoT (ADT a) => args ~ Args (args -..-> a) => (args -..-> a) -> repr (args -..-> k) k -> repr (a -> k) k
Documentation
adt :: forall adt repr k. Dimapable repr => Generic adt => RepOfEoT adt => EoTOfRep adt => repr (EoT (ADT adt) -> k) k -> repr (adt -> k) k Source #
Class Tupable
Class Unitable
Class Constant
Class Eitherable
class Eitherable repr where Source #
Minimal complete definition
Nothing
Class Emptyable
Class Optionable
class Optionable repr where Source #
Minimal complete definition
Nothing
Methods
option :: Transformable repr => Optionable (UnTrans repr) => repr k k -> repr k k Source #
option :: repr k k -> repr k k Source #
optional :: Transformable repr => Optionable (UnTrans repr) => repr (a -> k) k -> repr (Maybe a -> k) k Source #
optional :: repr (a -> k) k -> repr (Maybe a -> k) k Source #
Class Repeatable
class Repeatable repr where Source #
Minimal complete definition
Nothing
Methods
many0 :: Transformable repr => Repeatable (UnTrans repr) => repr (a -> k) k -> repr ([a] -> k) k Source #
many0 :: repr (a -> k) k -> repr ([a] -> k) k Source #
many1 :: Transformable repr => Repeatable (UnTrans repr) => repr (a -> k) k -> repr ([a] -> k) k Source #
Class Substractable
class Substractable repr where Source #
Minimal complete definition
Nothing
Methods
(<->) :: Transformable repr => Substractable (UnTrans repr) => repr a k -> repr k' k' -> repr a k infixr 3 Source #
(<->) :: repr a k -> repr k' k' -> repr a k infixr 3 Source #
Class Dicurryable
class Dicurryable repr where Source #
Minimal complete definition
Nothing
Methods
dicurry :: CurryN args => proxy args -> (args -..-> r) -> (r -> Tuples args) -> repr (args -..-> k) k -> repr (r -> k) k Source #
dicurry :: Transformable repr => Dicurryable (UnTrans repr) => CurryN args => proxy args -> (args -..-> r) -> (r -> Tuples args) -> repr (args -..-> k) k -> repr (r -> k) k Source #