Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- type family AllConstrained c ts :: Constraint where ...
- type family IdentityElement (tensor :: Type -> Type -> Type)
- class MonoidOf tensor m where
- data N :: (Type -> Type -> Type) -> (k -> Type) -> [k] -> Type where
- nmap :: forall f g tensor. Bifunctor tensor => (forall x. f x -> g x) -> forall xs. N tensor f xs -> N tensor g xs
- nmapConstrained :: forall c f g tensor. Bifunctor tensor => (forall x. c x => f x -> g x) -> forall xs. AllConstrained c xs => N tensor f xs -> N tensor g xs
- nfold :: forall f r tensor. (Bifunctor tensor, MonoidOf tensor r) => (forall x. f x -> r) -> forall xs. N tensor f xs -> r
- nfoldConstrained :: forall c f r tensor. (Bifunctor tensor, MonoidOf tensor r) => (forall x. c x => f x -> r) -> forall xs. AllConstrained c xs => N tensor f xs -> r
- type Rec = N (,)
- rmap :: forall f g. (forall x. f x -> g x) -> forall xs. Rec f xs -> Rec g xs
- rmapConstrained :: forall c f g. (forall x. c x => f x -> g x) -> forall xs. AllConstrained c xs => Rec f xs -> Rec g xs
- rfold :: forall f r. Monoid r => (forall x. f x -> r) -> forall xs. Rec f xs -> r
- rfoldConstrained :: forall c f r. Monoid r => (forall x. c x => f x -> r) -> forall xs. AllConstrained c xs => Rec f xs -> r
- rget :: forall f xs a. Elem xs a => Rec f xs -> f a
- type HList = Rec Identity
- type Spine = Rec Proxy
- class KnownSpine xs where
- type Union = N Either
- umap :: forall f g. (forall x. f x -> g x) -> forall xs. Union f xs -> Union g xs
- umapConstrained :: forall c f g. (forall x. c x => f x -> g x) -> forall xs. AllConstrained c xs => Union f xs -> Union g xs
- ufold :: forall f r. (forall x. f x -> r) -> forall xs. Union f xs -> r
- ufoldConstrained :: forall c f r. (forall x. c x => f x -> r) -> forall xs. AllConstrained c xs => Union f xs -> r
- umatch :: forall f xs a. Elem xs a => Union f xs -> Maybe (f a)
- ulift :: forall f xs a. Elem xs a => f a -> Union f xs
- type OpenUnion = Union Identity
- type ElemEv a = Union ((:~:) a)
- class Elem' (Index x xs) x xs => Elem xs x
- elemEv :: forall xs a. Elem xs a => ElemEv a xs
General definitions
type family AllConstrained c ts :: Constraint where ... Source #
AllConstrained c '[] = () | |
AllConstrained c (t ': ts) = (c t, AllConstrained c ts) |
type family IdentityElement (tensor :: Type -> Type -> Type) Source #
Instances
type IdentityElement Either Source # | |
Defined in NType | |
type IdentityElement (,) Source # | |
Defined in NType |
data N :: (Type -> Type -> Type) -> (k -> Type) -> [k] -> Type where Source #
Base :: !(IdentityElement tensor) -> N tensor f '[] | |
Step :: !(tensor (f x) (N tensor f xs)) -> N tensor f (x ': xs) |
Instances
Eq (tensor (f x) (N tensor f xs)) => Eq (N tensor f (x ': xs)) Source # | |
Eq (IdentityElement tensor) => Eq (N tensor f ([] :: [k])) Source # | |
Ord (tensor (f x) (N tensor f xs)) => Ord (N tensor f (x ': xs)) Source # | |
Defined in NType compare :: N tensor f (x ': xs) -> N tensor f (x ': xs) -> Ordering # (<) :: N tensor f (x ': xs) -> N tensor f (x ': xs) -> Bool # (<=) :: N tensor f (x ': xs) -> N tensor f (x ': xs) -> Bool # (>) :: N tensor f (x ': xs) -> N tensor f (x ': xs) -> Bool # (>=) :: N tensor f (x ': xs) -> N tensor f (x ': xs) -> Bool # max :: N tensor f (x ': xs) -> N tensor f (x ': xs) -> N tensor f (x ': xs) # min :: N tensor f (x ': xs) -> N tensor f (x ': xs) -> N tensor f (x ': xs) # | |
Ord (IdentityElement tensor) => Ord (N tensor f ([] :: [k])) Source # | |
Defined in NType compare :: N tensor f [] -> N tensor f [] -> Ordering # (<) :: N tensor f [] -> N tensor f [] -> Bool # (<=) :: N tensor f [] -> N tensor f [] -> Bool # (>) :: N tensor f [] -> N tensor f [] -> Bool # (>=) :: N tensor f [] -> N tensor f [] -> Bool # | |
Show (tensor (f x) (N tensor f xs)) => Show (N tensor f (x ': xs)) Source # | |
Show (IdentityElement tensor) => Show (N tensor f ([] :: [k])) Source # | |
nmap :: forall f g tensor. Bifunctor tensor => (forall x. f x -> g x) -> forall xs. N tensor f xs -> N tensor g xs Source #
nmapConstrained :: forall c f g tensor. Bifunctor tensor => (forall x. c x => f x -> g x) -> forall xs. AllConstrained c xs => N tensor f xs -> N tensor g xs Source #
nfold :: forall f r tensor. (Bifunctor tensor, MonoidOf tensor r) => (forall x. f x -> r) -> forall xs. N tensor f xs -> r Source #
nfoldConstrained :: forall c f r tensor. (Bifunctor tensor, MonoidOf tensor r) => (forall x. c x => f x -> r) -> forall xs. AllConstrained c xs => N tensor f xs -> r Source #
Product types
rmapConstrained :: forall c f g. (forall x. c x => f x -> g x) -> forall xs. AllConstrained c xs => Rec f xs -> Rec g xs Source #
rfoldConstrained :: forall c f r. Monoid r => (forall x. c x => f x -> r) -> forall xs. AllConstrained c xs => Rec f xs -> r Source #
class KnownSpine xs where Source #
knownSpine :: Spine xs Source #
Instances
KnownSpine ([] :: [k]) Source # | |
Defined in NType knownSpine :: Spine [] Source # | |
KnownSpine xs => KnownSpine (x ': xs :: [k]) Source # | |
Defined in NType knownSpine :: Spine (x ': xs) Source # |
Sum types
umapConstrained :: forall c f g. (forall x. c x => f x -> g x) -> forall xs. AllConstrained c xs => Union f xs -> Union g xs Source #
ufoldConstrained :: forall c f r. (forall x. c x => f x -> r) -> forall xs. AllConstrained c xs => Union f xs -> r Source #