Safe Haskell | None |
---|---|
Language | Haskell2010 |
NOTE highly experimental
- data SplitType
- type family CalcSplitType splitType varTy where ...
- type family ArgTy argTy where ...
- newtype Split uId splitType synVar = Split {
- getSplit :: synVar
- split :: Proxy (uId :: Symbol) -> Proxy (splitType :: SplitType) -> synVar -> Split uId splitType synVar
- collectIx :: forall uId ls i. SplitIxCol uId (SameSid uId (Elm ls i)) (Elm ls i) => Proxy uId -> Elm ls i -> SplitIxTy uId (SameSid uId (Elm ls i)) (Elm ls i)
- type family SameSid uId elm :: Bool where ...
- type family OR a b where ...
- class Zconcat x y where
- class SplitIxCol uId b e where
- data Proxy k t :: forall k. k -> * = Proxy
Documentation
type family CalcSplitType splitType varTy where ... Source #
The Arg synVar
means that we probably need to rewrite the internal
type resolution now!
CalcSplitType Fragment varTy = () | |
CalcSplitType Final varTy = varTy |
newtype Split uId splitType synVar Source #
Wraps a normal non-terminal and attaches a type-level unique identier
and z-ordering (with the unused Z
at 0
).
TODO attach empty/non-empty stuff (or get from non-splitted synvar?)
TODO re-introduce z-ordering later (once we have a sort fun)
SplitIxCol uId (SameSid uId (Elm ls i)) (Elm ls i) => SplitIxCol uId True (Elm ((:!:) ls (Split sId splitType (TwITblBt arr c j x mF mB r))) i) Source # | |
SplitIxCol uId (SameSid uId (Elm ls i)) (Elm ls i) => SplitIxCol uId True (Elm ((:!:) ls (Split sId splitType (TwITbl m arr c j x))) i) Source # | |
Element ls i => Element ((:!:) ls (Split uId splitType (TwITblBt arr c j x mF mB r))) i Source # | |
Element ls i => Element ((:!:) ls (Split uId splitType (TwITbl m arr c j x))) i Source # | |
Build (Split uId splitType synVar) Source # | |
type SplitIxTy uId True (Elm ((:!:) ls (Split sId splitType (TwITblBt arr c j x mF mB r))) i) Source # | |
type SplitIxTy uId True (Elm ((:!:) ls (Split sId splitType (TwITbl m arr c j x))) i) Source # | |
data Elm ((:!:) ls (Split uId splitType (TwITblBt arr c j x mF mB r))) Source # | |
data Elm ((:!:) ls (Split uId splitType (TwITbl m arr c j x))) Source # | |
type Arg ((:!:) ls (Split uId splitType (TwITblBt arr c j x mF mB r))) Source # | |
type Arg ((:!:) ls (Split uId splitType (TwITbl m arr c j x))) Source # | |
type RecElm ((:!:) ls (Split uId splitType (TwITblBt arr c j x mF mB r))) i Source # | |
type RecElm ((:!:) ls (Split uId splitType (TwITbl m arr c j x))) i Source # | |
type Stack (Split uId splitType synVar) Source # | |
split :: Proxy (uId :: Symbol) -> Proxy (splitType :: SplitType) -> synVar -> Split uId splitType synVar Source #
TODO Here, we probably want to default to a NonEmpty
condition. Or at
least have different versions of split
.
collectIx :: forall uId ls i. SplitIxCol uId (SameSid uId (Elm ls i)) (Elm ls i) => Proxy uId -> Elm ls i -> SplitIxTy uId (SameSid uId (Elm ls i)) (Elm ls i) Source #
collectIx
gobbles up indices that are tagged with the same symbolic
identifier.
type family SameSid uId elm :: Bool where ... Source #
Closed type family that gives us a (type) function for type symbol equality.
class SplitIxCol uId b e where Source #
Actually collect split indices based on if we managed to find the
right Split
synvar (based on the right symbol).
TODO this is not completely right, or? Since we should consider inside/outside?
TODO splitIxCol
will need the index type i
to combine running index
and index into the actual lookup part.
(SplitIxCol uId (SameSid uId (Elm ls i)) (Elm ls i), Zconcat (SplitIxTy uId (SameSid uId (Elm ls i)) (Elm ls i)) (SplitIxTy uId (SameSid uId (TermSymbol a b)) (TermSymbol a b))) => SplitIxCol uId True (Elm ((:!:) ls (TermSymbol a b)) i) Source # | |
SplitIxCol uId (SameSid uId (Elm ls i)) (Elm ls i) => SplitIxCol uId True (Elm ((:!:) ls (Split sId splitType (TwITblBt arr c j x mF mB r))) i) Source # | |
SplitIxCol uId (SameSid uId (Elm ls i)) (Elm ls i) => SplitIxCol uId True (Elm ((:!:) ls (Split sId splitType (TwITbl m arr c j x))) i) Source # | |
(SplitIxCol uId (SameSid uId (Elm ls i)) (Elm ls i), Element ((:!:) ls l) i, (~) * (RecElm ((:!:) ls l) i) (Elm ls i)) => SplitIxCol uId False (Elm ((:!:) ls l) i) Source # | |
SplitIxCol uId b (Elm S i) Source # | |
data Proxy k t :: forall k. k -> * #
A concrete, poly-kinded proxy type
Monad (Proxy *) | |
Functor (Proxy *) | |
Applicative (Proxy *) | |
Foldable (Proxy *) | |
Traversable (Proxy *) | |
Generic1 (Proxy *) | |
Alternative (Proxy *) | |
MonadPlus (Proxy *) | |
Eq1 (Proxy *) | Since: 4.9.0.0 |
Ord1 (Proxy *) | Since: 4.9.0.0 |
Read1 (Proxy *) | Since: 4.9.0.0 |
Show1 (Proxy *) | Since: 4.9.0.0 |
Hashable1 (Proxy *) | |
Bounded (Proxy k s) | |
Enum (Proxy k s) | |
Eq (Proxy k s) | |
Data t => Data (Proxy * t) | |
Ord (Proxy k s) | |
Read (Proxy k s) | |
Show (Proxy k s) | |
Ix (Proxy k s) | |
Generic (Proxy k t) | |
Semigroup (Proxy k s) | |
Monoid (Proxy k s) | |
Hashable (Proxy * a) | |
type Rep1 (Proxy *) | |
type Rep (Proxy k t) | |