module Data.Diverse.TypeLevel where
import Data.Diverse.TypeLevel.Internal
import Data.Kind
import GHC.TypeLits
type UniqueMember x xs = (Unique x xs, KnownNat (IndexOf x xs))
type family UniqueMembers (xs :: [k]) (ys :: [k]) :: Constraint where
UniqueMembers '[] ys = ()
UniqueMembers (x ': xs) ys = (UniqueMember x ys, UniqueMembers xs ys)
type UniqueLabelMember l xs = (UniqueLabel l xs, KnownNat (IndexOf (KindAtLabel l xs) xs))
type MaybeUniqueMember x xs = (Unique x xs, KnownNat (PositionOf x xs))
type MemberAt n x xs = (KnownNat n, x ~ KindAtIndex n xs)
type MaybeMemberAt n x xs = (KnownNat n, KindAtPositionIs n x xs)
type family SnocUnique (xs :: [k]) (x :: k) :: [k] where
SnocUnique '[] x = '[x]
SnocUnique (x ': xs) x = x ': xs
SnocUnique (y ': xs) x = y ': SnocUnique xs x
type family AppendUnique (xs :: [k]) (ys :: [k]) :: [k] where
AppendUnique '[] xs = xs
AppendUnique xs '[] = xs
AppendUnique xs xs = xs
AppendUnique xs (y ': ys) = AppendUnique (SnocUnique xs y) ys
type family UniqueIfExists ys x xs :: Constraint where
UniqueIfExists '[] x xs = ()
UniqueIfExists (y ': ys) y xs = Unique y xs
UniqueIfExists (y ': ys) x xs = UniqueIfExists ys x xs
type IsDistinct (xs :: [k]) = IsDistinctImpl xs xs
type family Nub (xs :: [k]) :: [k] where
Nub '[] = '[]
Nub (x ': xs) = NubImpl xs x xs
type Unique (x :: k) (xs :: [k]) = UniqueImpl xs x xs
type UniqueLabel (l :: k1) (xs :: [k]) = UniqueLabelImpl xs l xs
type family UniqueLabels (ls :: [k1]) (xs :: [k]) :: Constraint where
UniqueLabels '[] xs = ()
UniqueLabels (l ': ls) xs = (UniqueLabel l xs, UniqueLabels ls xs)
type IndexOf (x :: k) (xs :: [k]) = IndexOfImpl xs x xs
type PositionOf (x :: k) (xs :: [k]) = PositionOfImpl 0 x xs
type KindAtIndex (n :: Nat) (xs :: [k]) = KindAtIndexImpl n xs n xs
type KindAtLabel (l :: k1) (xs :: [k]) = KindAtLabelImpl l xs xs
type family KindAtPositionIs (n :: Nat) (x :: k) (xs :: [k]) :: Constraint where
KindAtPositionIs 0 x xs = ()
KindAtPositionIs n x xs = (x ~ KindAtIndexImpl (n 1) xs (n 1) xs)
type family KindsAtIndices (ns :: [Nat]) (xs :: [k]) :: [k] where
KindsAtIndices '[] xs = '[]
KindsAtIndices (n ': ns) xs = KindAtIndex n xs ': KindsAtIndices ns xs
type family KindsAtLabels (ls :: [k1]) (xs :: [k]) :: [k] where
KindsAtLabels '[] xs = '[]
KindsAtLabels (l ': ls) xs = KindAtLabel l xs ': KindsAtLabels ls xs
type family Remove (x :: k) (xs :: [k]) :: [k] where
Remove x '[] = '[]
Remove x (x ': xs) = xs
Remove x (y ': xs) = y ': Remove x xs
type Replace (x :: k) (y :: k) (xs :: [k]) = ReplaceImpl x y xs
type Replaces (xs :: [k]) (ys :: [k]) (zs :: [k]) = ReplacesImpl xs ys xs ys zs
type RemoveIndex (n :: Nat) (xs :: [k]) = RemoveIndexImpl n xs n xs
type ReplaceIndex (n :: Nat) (y :: k) (xs :: [k]) = ReplaceIndexImpl n xs n y xs
type ReplacesIndex (ns :: [Nat]) (ys :: [k]) (xs :: [k]) = ReplacesIndexImpl 0 ns ys xs
type family Before (x :: k) (xs :: [k]) :: [k] where
Before x '[] = '[]
Before x (x ': xs) = '[]
Before x (y ': xs) = y ': Before x xs
type family To (x :: k) (xs :: [k]) :: [k] where
To x '[] = '[]
To x (x ': xs) = '[x]
To x (y ': xs) = y ': To x xs
type family After (x :: k) (xs :: [k]) :: [k] where
After x '[] = '[]
After x (x ': xs) = xs
After x (y ': xs) = After x xs
type family From (x :: k) (xs :: [k]) :: [k] where
From x '[] = '[]
From x (x ': xs) = (x ': xs)
From x (y ': xs) = From x xs
type family BeforeIndex (n :: Nat) (xs :: [k]) :: [k] where
BeforeIndex n '[] = '[]
BeforeIndex 0 xs = '[]
BeforeIndex n (x ': xs) = x ': BeforeIndex (n 1) xs
type family ToIndex (n :: Nat) (xs :: [k]) :: [k] where
ToIndex n '[] = '[]
ToIndex 0 (x ': xs) = '[x]
ToIndex n (x ': xs) = x ': ToIndex (n 1) xs
type family AfterIndex (n :: Nat) (xs :: [k]) :: [k] where
AfterIndex n '[] = '[]
AfterIndex 0 (_ ': xs) = xs
AfterIndex n (x ': xs) = AfterIndex (n 1) xs
type family FromIndex (n :: Nat) (xs :: [k]) :: [k] where
FromIndex n '[] = '[]
FromIndex 0 xs = xs
FromIndex n (x ': xs) = FromIndex (n 1) xs
type family Tail (xs :: [k]) :: [k] where
Tail '[] = TypeError ('Text "Tail error: empty type list")
Tail (x ': xs) = xs
type family Head (xs :: [k]) :: k where
Head '[] = TypeError ('Text "Head error: empty type list")
Head (x ': xs) = x
type family Last (xs :: [k]) :: k where
Last '[] = TypeError ('Text "Last error: empty type list")
Last (x ': x' ': xs) = Last (x' ': xs)
Last '[x] = x
type family Length (xs :: [k]) :: Nat where
Length '[] = 0
Length (x ': xs) = 1 + Length xs
type SameLength (xs :: [k1]) (ys :: [k2]) = SameLengthImpl xs ys xs ys
type family Complement (xs :: [k]) (ys :: [k]) :: [k] where
Complement xs '[] = xs
Complement xs (y ': ys) = Complement (Remove y xs) ys
type family Append (xs :: [k]) (ys :: [k]) :: [k] where
Append xs '[] = xs
Append '[] ys = ys
Append (x ': xs) ys = x ': Append xs ys
type family Init (xs :: [k]) :: [k] where
Init '[] = TypeError ('Text "Init error: empty type list")
Init '[x] = '[]
Init (x ': xs) = x ': Init xs
type Zip (xs :: [k]) (ys :: [k]) = ZipImpl xs ys xs ys
type family CaseResult (c ::[k1] -> k2) (x :: k1) :: k2
type family CaseResults (c ::[k1] -> k2) (xs :: [k1]) :: [k2] where
CaseResults c '[] = '[]
CaseResults c (x ': xs) = CaseResult c x ': CaseResults c xs
type family AllConstrained (c :: k -> Constraint) (xs :: [k]) :: Constraint where
AllConstrained c '[] = ()
AllConstrained c (x ': xs) = (c x, AllConstrained c xs)