Copyright | (c) 2016 Allele Dev; 2017 Ixperta Solutions s.r.o.; 2017 Alexis King; 2024 Sayo Koyoneda |
---|---|
License | MPL-2.0 (see the LICENSE file) AND BSD-3-Clause (see the LICENSE.BSD3 file) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Data.Effect.OpenUnion.Internal
Description
Synopsis
- newtype P (e :: k) (es :: [k]) = P {}
- type FindElem (e :: a) (es :: [a]) = KnownNat (ElemIndex e es)
- elemNo :: forall {k} (e :: k) (es :: [k]). FindElem e es => P e es
- type family ElemIndex (e :: a) (es :: [a]) :: Natural where ...
- type family ElemAt (i :: Natural) (es :: [k]) :: k where ...
- class IfNotFound (e :: k) (r :: [k]) (w :: [k])
- type LookupError (key :: kk) (w :: [ke]) = TypeError ((('Text "The key \8216" ':<>: 'ShowType key) ':<>: 'Text "\8217 does not exist in the type-level list") ':$$: (('Text " \8216" ':<>: 'ShowType w) ':<>: 'Text "\8217")) :: k
- type family (xs :: [a]) ++ (ys :: [a]) :: [a] where ...
- wordVal :: forall (n :: Nat). KnownNat n => Word
- class IsSuffixOf (es :: k) (es' :: k1) where
- type family Length (es :: [a]) :: Natural where ...
- class KnownNat (Length es) => KnownLength (es :: [a])
- reifyLength :: forall {a} (es :: [a]). KnownLength es => Word
- type family PrefixLength (es :: [a]) (es' :: [a]) :: Natural where ...
- type WeakenN (len :: Natural) (es :: [a]) (es' :: [a]) = (es ~ Drop len es', KnownNat len)
- type WeakenUnder (offset :: Natural) (es :: [a]) (es' :: [a]) = (WeakenNUnder (PrefixLength es es') offset es es', KnownNat (PrefixLength es es'))
- type WeakenNUnder (len :: Natural) (offset :: Natural) (es :: [a]) (es' :: [a]) = (WeakenN len (Drop offset es) (Drop offset es'), KnownNat offset)
- type Strengthen (es :: [a]) (es' :: [a]) = (StrengthenMap (PrefixLength es' es) es es', KnownNat (PrefixLength es' es))
- type StrengthenN (len :: Natural) (es :: [k]) (es' :: [k]) = (StrengthenMap len es es', KnownNat len)
- type StrengthenUnder (offset :: Natural) (es :: [k]) (es' :: [k]) = StrengthenNUnder (PrefixLength es' es) offset es es'
- type StrengthenNUnder (len :: Natural) (offset :: Natural) (es :: [k]) (es' :: [k]) = (StrengthenMap len (Drop offset es) (Drop offset es'), KnownNat len, KnownNat offset)
- type StrengthenMap (len :: Natural) (es :: [k]) (es' :: [k]) = StrengthenMap_ (len == 0) len es es'
- class isLenZero ~ (len == 0) => StrengthenMap_ (isLenZero :: Bool) (len :: Natural) (es :: [k]) (es' :: [k]) where
- strengthenMap :: Word -> Word
- strengthenMapUnder :: forall {k} (len :: Natural) (offset :: Natural) (es :: [k]) (es' :: [k]). StrengthenNUnder len offset es es' => Word -> Word
- type BundleUnder (u :: [a] -> a) (offset :: Natural) (es :: [a]) (es' :: [a]) (bundle :: [a]) = (es' ~ (Take offset es ++ (u bundle ': Drop (Length bundle) (Drop offset es))), es ~ (Take offset es' ++ (bundle ++ Drop 1 (Drop offset es'))), bundle ~ Take (PrefixLength (Drop 1 (Drop offset es')) (Drop offset es)) (Drop offset es), KnownLength bundle, KnownNat offset, Length bundle ~ PrefixLength (Drop 1 (Drop offset es')) (Drop offset es))
- type Split (es :: [a]) (init :: [a]) (tail :: [a]) = (es ~ (init ++ tail), init ~ Take (PrefixLength tail es) es, tail ~ Drop (Length init) es, KnownLength init, Length init ~ PrefixLength tail es)
- type family Take (n :: Natural) (es :: [a]) :: [a] where ...
- type family Drop (n :: Natural) (es :: [a]) :: [a] where ...
- type Reverse (es :: [a]) = Reverse_ ('[] :: [a]) es
- type family Reverse_ (acc :: [a]) (es :: [a]) :: [a] where ...
Documentation
newtype P (e :: k) (es :: [k]) Source #
Represents position of element e :: k
in a type list es :: [k]
.
class IfNotFound (e :: k) (r :: [k]) (w :: [k]) Source #
Instance resolution for this class fails with a custom type error
if e :: k
is not in the list w :: [k]
.
Instances
IfNotFound (e :: k) (r :: [k]) (w :: [k]) Source # | Pass if |
Defined in Data.Effect.OpenUnion.Internal | |
(TypeError ((('Text "\8216" ':<>: 'ShowType e) ':<>: 'Text "\8217 is not a member of the type-level list") ':$$: (('Text " \8216" ':<>: 'ShowType w) ':<>: 'Text "\8217")) :: Constraint) => IfNotFound (e :: k) ('[] :: [k]) (w :: [k]) Source # | If we reach an empty list, that’s a failure, since it means the type isn’t in the list. |
Defined in Data.Effect.OpenUnion.Internal | |
IfNotFound (e :: a) (e ': r :: [a]) (w :: [a]) Source # | |
Defined in Data.Effect.OpenUnion.Internal | |
IfNotFound e r w => IfNotFound (e :: a) (e' ': r :: [a]) (w :: [a]) Source # | |
Defined in Data.Effect.OpenUnion.Internal |
type LookupError (key :: kk) (w :: [ke]) = TypeError ((('Text "The key \8216" ':<>: 'ShowType key) ':<>: 'Text "\8217 does not exist in the type-level list") ':$$: (('Text " \8216" ':<>: 'ShowType w) ':<>: 'Text "\8217")) :: k Source #
class IsSuffixOf (es :: k) (es' :: k1) where Source #
Instances
IsSuffixOf (es :: k) (es :: k) Source # | |
Defined in Data.Effect.OpenUnion.Internal | |
IsSuffixOf es es' => IsSuffixOf (es :: k) (e ': es' :: [a]) Source # | |
Defined in Data.Effect.OpenUnion.Internal |
class KnownNat (Length es) => KnownLength (es :: [a]) Source #
Instances
KnownNat (Length es) => KnownLength (es :: [a]) Source # | |
Defined in Data.Effect.OpenUnion.Internal |
reifyLength :: forall {a} (es :: [a]). KnownLength es => Word Source #
type family PrefixLength (es :: [a]) (es' :: [a]) :: Natural where ... Source #
Equations
PrefixLength (es :: [a]) (es :: [a]) = 0 | |
PrefixLength (es :: [a]) (e ': es' :: [a]) = 1 + PrefixLength es es' |
type WeakenUnder (offset :: Natural) (es :: [a]) (es' :: [a]) = (WeakenNUnder (PrefixLength es es') offset es es', KnownNat (PrefixLength es es')) Source #
type WeakenNUnder (len :: Natural) (offset :: Natural) (es :: [a]) (es' :: [a]) = (WeakenN len (Drop offset es) (Drop offset es'), KnownNat offset) Source #
type Strengthen (es :: [a]) (es' :: [a]) = (StrengthenMap (PrefixLength es' es) es es', KnownNat (PrefixLength es' es)) Source #
type StrengthenN (len :: Natural) (es :: [k]) (es' :: [k]) = (StrengthenMap len es es', KnownNat len) Source #
type StrengthenUnder (offset :: Natural) (es :: [k]) (es' :: [k]) = StrengthenNUnder (PrefixLength es' es) offset es es' Source #
type StrengthenNUnder (len :: Natural) (offset :: Natural) (es :: [k]) (es' :: [k]) = (StrengthenMap len (Drop offset es) (Drop offset es'), KnownNat len, KnownNat offset) Source #
type StrengthenMap (len :: Natural) (es :: [k]) (es' :: [k]) = StrengthenMap_ (len == 0) len es es' Source #
class isLenZero ~ (len == 0) => StrengthenMap_ (isLenZero :: Bool) (len :: Natural) (es :: [k]) (es' :: [k]) where Source #
Methods
strengthenMap :: Word -> Word Source #
Instances
StrengthenMap_ 'True 0 (es :: [k]) (es :: [k]) Source # | |
Defined in Data.Effect.OpenUnion.Internal Methods strengthenMap :: Word -> Word Source # | |
(StrengthenMap (len - 1) es es', FindElem e es, (len == 0) ~ 'False) => StrengthenMap_ 'False len (e ': es :: [k]) (es' :: [k]) Source # | |
Defined in Data.Effect.OpenUnion.Internal Methods strengthenMap :: Word -> Word Source # |
strengthenMapUnder :: forall {k} (len :: Natural) (offset :: Natural) (es :: [k]) (es' :: [k]). StrengthenNUnder len offset es es' => Word -> Word Source #
type BundleUnder (u :: [a] -> a) (offset :: Natural) (es :: [a]) (es' :: [a]) (bundle :: [a]) = (es' ~ (Take offset es ++ (u bundle ': Drop (Length bundle) (Drop offset es))), es ~ (Take offset es' ++ (bundle ++ Drop 1 (Drop offset es'))), bundle ~ Take (PrefixLength (Drop 1 (Drop offset es')) (Drop offset es)) (Drop offset es), KnownLength bundle, KnownNat offset, Length bundle ~ PrefixLength (Drop 1 (Drop offset es')) (Drop offset es)) Source #
type Split (es :: [a]) (init :: [a]) (tail :: [a]) = (es ~ (init ++ tail), init ~ Take (PrefixLength tail es) es, tail ~ Drop (Length init) es, KnownLength init, Length init ~ PrefixLength tail es) Source #