Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data ContTag
- type family StackConstraints (n :: Nat) (c :: k) (cSucc :: k' -> Constraint) (m :: k') :: Constraint where ...
- type family IteratePop (n :: Nat) (c :: k) (m :: Type -> Type) :: Type -> Type where ...
- type family Pop (c :: k) (m :: k') :: k'
- predNat :: forall n. KnownNat n => Either (n :~: 0) (Dict (KnownNat (n - 1)))
- nonZeroNat :: forall n c cSucc m a. KnownNat (n - 1) => (IteratePop n c m a :~: IteratePop (n - 1) c (Pop c m) a, StackConstraints n c cSucc m :~: (cSucc m, StackConstraints (n - 1) c cSucc (Pop c m)))
- depth :: forall n c cSucc m a. (KnownNat n, StackConstraints n c cSucc m) => (forall m. cSucc m => Pop c m a -> m a) -> IteratePop n c m a -> m a
- module GHC.TypeNats
Documentation
ContT is polykinded, which leads to issues checking that ContT ~ ContT!
type family StackConstraints (n :: Nat) (c :: k) (cSucc :: k' -> Constraint) (m :: k') :: Constraint where ... Source #
StackConstraints 0 c cSucc m = () | |
StackConstraints n c cSucc m = (cSucc m, StackConstraints (n - 1) c cSucc (Pop c m)) |
type family IteratePop (n :: Nat) (c :: k) (m :: Type -> Type) :: Type -> Type where ... Source #
IteratePop 0 c m = m | |
IteratePop n c m = IteratePop (n - 1) c (Pop c m) |
type family Pop (c :: k) (m :: k') :: k' Source #
Instances
type Pop ContTag (m :: Type -> Type) Source # | |
type Pop MaybeT (m :: Type -> Type) Source # | |
type Pop ExceptT (m :: Type -> Type) Source # | |
type Pop ReaderT (m :: Type -> Type) Source # | |
type Pop StateT (m :: Type -> Type) Source # | |
type Pop WriterT (m :: Type -> Type) Source # | |
type Pop AccumT (m :: Type -> Type) Source # | |
type Pop SelectT (m :: Type -> Type) Source # | |
nonZeroNat :: forall n c cSucc m a. KnownNat (n - 1) => (IteratePop n c m a :~: IteratePop (n - 1) c (Pop c m) a, StackConstraints n c cSucc m :~: (cSucc m, StackConstraints (n - 1) c cSucc (Pop c m))) Source #
depth :: forall n c cSucc m a. (KnownNat n, StackConstraints n c cSucc m) => (forall m. cSucc m => Pop c m a -> m a) -> IteratePop n c m a -> m a Source #
module GHC.TypeNats