heftia-0.4.0.0: higher-order effects done right
Copyright(c) 2016 Allele Dev; 2017 Ixperta Solutions s.r.o.; 2017 Alexis King; 2024 Sayo Koyoneda
LicenseMPL-2.0 (see the LICENSE file) AND BSD-3-Clause (see the LICENSE.BSD3 file)
Maintainerymdfield@outlook.jp
Safe HaskellNone
LanguageGHC2021

Data.Effect.OpenUnion.Internal

Description

 
Synopsis

Documentation

newtype P (e :: k) (es :: [k]) Source #

Represents position of element e :: k in a type list es :: [k].

Constructors

P 

Fields

type FindElem (e :: a) (es :: [a]) = KnownNat (ElemIndex e es) Source #

elemNo :: forall {k} (e :: k) (es :: [k]). FindElem e es => P e es Source #

type family ElemIndex (e :: a) (es :: [a]) :: Natural where ... Source #

Equations

ElemIndex (e :: a) (e ': es :: [a]) = 0 
ElemIndex (e :: a) (_1 ': es :: [a]) = 1 + ElemIndex e es 

type family ElemAt (i :: Natural) (es :: [k]) :: k where ... Source #

Equations

ElemAt 0 (e ': _1 :: [k]) = e 
ElemAt n (_1 ': es :: [k]) = ElemAt (n - 1) es 

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

Instances details
IfNotFound (e :: k) (r :: [k]) (w :: [k]) Source #

Pass if r is uninstantiated. The incoherence here is safe, since picking this instance doesn’t cause any variation in behavior, except possibly the production of an inferior error message. For more information, see lexi-lambda/freer-simple#3, which describes the motivation in more detail.

Instance details

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.

Instance details

Defined in Data.Effect.OpenUnion.Internal

IfNotFound (e :: a) (e ': r :: [a]) (w :: [a]) Source # 
Instance details

Defined in Data.Effect.OpenUnion.Internal

IfNotFound e r w => IfNotFound (e :: a) (e' ': r :: [a]) (w :: [a]) Source # 
Instance details

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 #

type family (xs :: [a]) ++ (ys :: [a]) :: [a] where ... infixr 5 Source #

Equations

('[] :: [a]) ++ (ys :: [a]) = ys 
(x ': xs :: [a]) ++ (ys :: [a]) = x ': (xs ++ ys) 

wordVal :: forall (n :: Nat). KnownNat n => Word Source #

class IsSuffixOf (es :: k) (es' :: k1) where Source #

Instances

Instances details
IsSuffixOf (es :: k) (es :: k) Source # 
Instance details

Defined in Data.Effect.OpenUnion.Internal

IsSuffixOf es es' => IsSuffixOf (es :: k) (e ': es' :: [a]) Source # 
Instance details

Defined in Data.Effect.OpenUnion.Internal

type family Length (es :: [a]) :: Natural where ... Source #

Equations

Length ('[] :: [a]) = 0 
Length (e ': es :: [a]) = 1 + Length es 

class KnownNat (Length es) => KnownLength (es :: [a]) Source #

Instances

Instances details
KnownNat (Length es) => KnownLength (es :: [a]) Source # 
Instance details

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 WeakenN (len :: Natural) (es :: [a]) (es' :: [a]) = (es ~ Drop len es', KnownNat len) Source #

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 #

Instances

Instances details
StrengthenMap_ 'True 0 (es :: [k]) (es :: [k]) Source # 
Instance details

Defined in Data.Effect.OpenUnion.Internal

(StrengthenMap (len - 1) es es', FindElem e es, (len == 0) ~ 'False) => StrengthenMap_ 'False len (e ': es :: [k]) (es' :: [k]) Source # 
Instance details

Defined in Data.Effect.OpenUnion.Internal

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 #

type family Take (n :: Natural) (es :: [a]) :: [a] where ... Source #

Equations

Take 0 (es :: [a]) = '[] :: [a] 
Take n (e ': es :: [a]) = e ': Take (n - 1) es 

type family Drop (n :: Natural) (es :: [a]) :: [a] where ... Source #

Equations

Drop 0 (es :: [a]) = es 
Drop n (e ': es :: [a]) = Drop (n - 1) es 

type Reverse (es :: [a]) = Reverse_ ('[] :: [a]) es Source #

type family Reverse_ (acc :: [a]) (es :: [a]) :: [a] where ... Source #

Equations

Reverse_ (acc :: [a]) ('[] :: [a]) = acc 
Reverse_ (acc :: [a]) (e ': es :: [a]) = Reverse_ (e ': acc) es