Safe Haskell | None |
---|---|
Language | Haskell2010 |
Symantic.Dityped.Lang
Synopsis
- class Composable repr where
- (<.>) :: repr a b -> repr b c -> repr a c
- class Constant repr where
- constant :: a -> repr (a -> k) 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
- class Dimapable repr where
- dimap :: (a -> b) -> (b -> a) -> repr (a -> k) k -> repr (b -> k) k
- class Eitherable repr where
- adt :: forall adt repr k. Dimapable repr => Generic adt => RepOfEoT adt => EoTOfRep adt => repr (EoT (ADT adt) -> k) k -> repr (adt -> k) k
- class Emptyable repr where
- empty :: repr k k
- class Optionable repr where
- class Permutable repr where
- type Permutation (repr :: * -> * -> *) = (r :: * -> * -> *) | r -> repr
- permutable :: Permutation repr (a -> k) k -> repr (a -> k) k
- perm :: repr (a -> k) k -> Permutation repr (a -> k) k
- noPerm :: Permutation repr k k
- permWithDefault :: a -> repr (a -> k) k -> Permutation repr (a -> k) k
- optionalPerm :: Eitherable repr => Dimapable repr => Permutable repr => repr (a -> k) k -> Permutation repr (Maybe a -> k) k
- (<&>) :: Permutable repr => Tupable (Permutation repr) => repr (a -> k) k -> Permutation repr (b -> k) k -> Permutation repr ((a, b) -> k) k
- (<?&>) :: Eitherable repr => Dimapable repr => Permutable repr => Tupable (Permutation repr) => repr (a -> k) k -> Permutation repr (b -> k) k -> Permutation repr ((Maybe a, b) -> k) k
- (<*&>) :: Eitherable repr => Repeatable repr => Dimapable repr => Permutable repr => Tupable (Permutation repr) => repr (a -> k) k -> Permutation repr (b -> k) k -> Permutation repr (([a], b) -> k) k
- (<+&>) :: Eitherable repr => Repeatable repr => Dimapable repr => Permutable repr => Tupable (Permutation repr) => repr (a -> k) k -> Permutation repr (b -> k) k -> Permutation repr (([a], b) -> k) k
- class Repeatable repr where
- class Routable repr where
- data a :!: b = a :!: b
- class Substractable repr where
- (<->) :: repr a k -> repr k' k' -> repr a 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 Voidable repr where
- void :: a -> repr (a -> b) k -> repr b k
Class Composable
class Composable repr where Source #
Minimal complete definition
Nothing
Methods
(<.>) :: repr a b -> repr b c -> repr a c infixr 4 Source #
default (<.>) :: FromDerived2 Composable repr => repr a b -> repr b c -> repr a c Source #
Class Constant
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 #
default dicurry :: FromDerived1 Dicurryable repr => CurryN args => proxy args -> (args -..-> r) -> (r -> Tuples args) -> repr (args -..-> k) k -> repr (r -> k) k Source #
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 Source #
Class Dimapable
Class Eitherable
class Eitherable repr where Source #
Minimal complete definition
Nothing
Methods
(<+>) :: repr (a -> k) k -> repr (b -> k) k -> repr (Either a b -> k) k infixr 3 Source #
default (<+>) :: FromDerived2 Eitherable repr => repr (a -> k) k -> repr (b -> k) k -> repr (Either a b -> k) k Source #
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 Emptyable
Class Optionable
class Optionable repr where Source #
Minimal complete definition
Nothing
Methods
option :: repr k k -> repr k k Source #
default option :: FromDerived1 Optionable repr => repr k k -> repr k k Source #
optional :: repr (a -> k) k -> repr (Maybe a -> k) k Source #
default optional :: FromDerived1 Optionable repr => repr (a -> k) k -> repr (Maybe a -> k) k Source #
Class Permutable
class Permutable repr where Source #
Minimal complete definition
Associated Types
type Permutation (repr :: * -> * -> *) = (r :: * -> * -> *) | r -> repr Source #
type Permutation repr = Permutation (Derived repr)
Methods
permutable :: Permutation repr (a -> k) k -> repr (a -> k) k Source #
perm :: repr (a -> k) k -> Permutation repr (a -> k) k Source #
noPerm :: Permutation repr k k Source #
permWithDefault :: a -> repr (a -> k) k -> Permutation repr (a -> k) k Source #
optionalPerm :: Eitherable repr => Dimapable repr => Permutable repr => repr (a -> k) k -> Permutation repr (Maybe a -> k) k Source #
(<&>) :: Permutable repr => Tupable (Permutation repr) => repr (a -> k) k -> Permutation repr (b -> k) k -> Permutation repr ((a, b) -> k) k infixr 4 Source #
(<?&>) :: Eitherable repr => Dimapable repr => Permutable repr => Tupable (Permutation repr) => repr (a -> k) k -> Permutation repr (b -> k) k -> Permutation repr ((Maybe a, b) -> k) k infixr 4 Source #
(<*&>) :: Eitherable repr => Repeatable repr => Dimapable repr => Permutable repr => Tupable (Permutation repr) => repr (a -> k) k -> Permutation repr (b -> k) k -> Permutation repr (([a], b) -> k) k infixr 4 Source #
(<+&>) :: Eitherable repr => Repeatable repr => Dimapable repr => Permutable repr => Tupable (Permutation repr) => repr (a -> k) k -> Permutation repr (b -> k) k -> Permutation repr (([a], b) -> k) k infixr 4 Source #
Class Repeatable
class Repeatable repr where Source #
Minimal complete definition
Nothing
Methods
many0 :: repr (a -> k) k -> repr ([a] -> k) k Source #
default many0 :: FromDerived1 Repeatable repr => repr (a -> k) k -> repr ([a] -> k) k Source #
many1 :: repr (a -> k) k -> repr ([a] -> k) k Source #
default many1 :: FromDerived1 Repeatable repr => repr (a -> k) k -> repr ([a] -> k) k Source #
Class Routable
Type (:!:
)
data a :!: b infixr 3 Source #
Like (,)
but infixr
.
Mostly useful for clarity when using Routable
.
Constructors
a :!: b infixr 3 |
Class Substractable
class Substractable repr where Source #
Minimal complete definition
Nothing
Methods
(<->) :: repr a k -> repr k' k' -> repr a k infixr 3 Source #
default (<->) :: FromDerived2 Substractable repr => repr a k -> repr k' k' -> repr a k Source #