HappyTree-0.2018.1.5

Safe HaskellNone
LanguageHaskell2010

Lib

Documentation

type family RevAppend (a :: [a]) (a :: [a]) :: [a] where ... Source #

Equations

RevAppend '[] x = x 
RevAppend ((:) x xs) n = Apply (Apply RevAppendSym0 xs) (Apply (Apply (:$) x) n) 

data RevAppendSym0 (l :: TyFun [a6989586621679076944] (TyFun [a6989586621679076944] [a6989586621679076944] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679076944] (TyFun [a6989586621679076944] [a6989586621679076944] -> Type) -> *) (RevAppendSym0 a6989586621679076944) Source # 

Methods

suppressUnusedWarnings :: Proxy (RevAppendSym0 a6989586621679076944) t -> () #

type Apply [a6989586621679076944] (TyFun [a6989586621679076944] [a6989586621679076944] -> Type) (RevAppendSym0 a6989586621679076944) l Source # 
type Apply [a6989586621679076944] (TyFun [a6989586621679076944] [a6989586621679076944] -> Type) (RevAppendSym0 a6989586621679076944) l = RevAppendSym1 a6989586621679076944 l

data RevAppendSym1 (l :: [a6989586621679076944]) (l :: TyFun [a6989586621679076944] [a6989586621679076944]) Source #

Instances

SuppressUnusedWarnings ([a6989586621679076944] -> TyFun [a6989586621679076944] [a6989586621679076944] -> *) (RevAppendSym1 a6989586621679076944) Source # 

Methods

suppressUnusedWarnings :: Proxy (RevAppendSym1 a6989586621679076944) t -> () #

type Apply [a] [a] (RevAppendSym1 a l1) l2 Source # 
type Apply [a] [a] (RevAppendSym1 a l1) l2 = RevAppend a l1 l2

type RevAppendSym2 (t :: [a6989586621679076944]) (t :: [a6989586621679076944]) = RevAppend t t Source #

type family TakeElemAux (a :: [a]) (a :: [a]) :: [(a, [a])] where ... Source #

Equations

TakeElemAux l '[] = '[] 
TakeElemAux l ((:) r rs) = Apply (Apply (:$) (Apply (Apply Tuple2Sym0 r) (Apply (Apply RevAppendSym0 l) rs))) (Apply (Apply TakeElemAuxSym0 (Apply (Apply (:$) r) l)) rs) 

data TakeElemAuxSym0 (l :: TyFun [a6989586621679076943] (TyFun [a6989586621679076943] [(a6989586621679076943, [a6989586621679076943])] -> Type)) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679076943] (TyFun [a6989586621679076943] [(a6989586621679076943, [a6989586621679076943])] -> Type) -> *) (TakeElemAuxSym0 a6989586621679076943) Source # 

Methods

suppressUnusedWarnings :: Proxy (TakeElemAuxSym0 a6989586621679076943) t -> () #

type Apply [a6989586621679076943] (TyFun [a6989586621679076943] [(a6989586621679076943, [a6989586621679076943])] -> Type) (TakeElemAuxSym0 a6989586621679076943) l Source # 
type Apply [a6989586621679076943] (TyFun [a6989586621679076943] [(a6989586621679076943, [a6989586621679076943])] -> Type) (TakeElemAuxSym0 a6989586621679076943) l = TakeElemAuxSym1 a6989586621679076943 l

data TakeElemAuxSym1 (l :: [a6989586621679076943]) (l :: TyFun [a6989586621679076943] [(a6989586621679076943, [a6989586621679076943])]) Source #

Instances

SuppressUnusedWarnings ([a6989586621679076943] -> TyFun [a6989586621679076943] [(a6989586621679076943, [a6989586621679076943])] -> *) (TakeElemAuxSym1 a6989586621679076943) Source # 

Methods

suppressUnusedWarnings :: Proxy (TakeElemAuxSym1 a6989586621679076943) t -> () #

type Apply [a] [(a, [a])] (TakeElemAuxSym1 a l1) l2 Source # 
type Apply [a] [(a, [a])] (TakeElemAuxSym1 a l1) l2 = TakeElemAux a l1 l2

type TakeElemAuxSym2 (t :: [a6989586621679076943]) (t :: [a6989586621679076943]) = TakeElemAux t t Source #

type family TakeElem (a :: [a]) :: [(a, [a])] where ... Source #

Equations

TakeElem a_6989586621679076982 = Apply (Apply TakeElemAuxSym0 '[]) a_6989586621679076982 

type TakeElemSym1 (t :: [a6989586621679076942]) = TakeElem t Source #

data TakeElemSym0 (l :: TyFun [a6989586621679076942] [(a6989586621679076942, [a6989586621679076942])]) Source #

Instances

SuppressUnusedWarnings (TyFun [a6989586621679076942] [(a6989586621679076942, [a6989586621679076942])] -> *) (TakeElemSym0 a6989586621679076942) Source # 

Methods

suppressUnusedWarnings :: Proxy (TakeElemSym0 a6989586621679076942) t -> () #

type Apply [a] [(a, [a])] (TakeElemSym0 a) l Source # 
type Apply [a] [(a, [a])] (TakeElemSym0 a) l = TakeElem a l

sTakeElem :: forall (t :: [a]). Sing t -> Sing (Apply TakeElemSym0 t :: [(a, [a])]) Source #

sTakeElemAux :: forall (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply TakeElemAuxSym0 t) t :: [(a, [a])]) Source #

sRevAppend :: forall (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply RevAppendSym0 t) t :: [a]) Source #

takeElem :: [a] -> [(a, [a])] Source #

takeElemAux :: [a] -> [a] -> [(a, [a])] Source #

revAppend :: [a] -> [a] -> [a] Source #

class (SplitCode a ~ Code a, Generic a) => SplitStructure a where Source #

Minimal complete definition

splitStructureTo

Associated Types

type SplitCode a :: [[*]] Source #

class Ord a => SplitOrd a Source #

newtype SplitStructureOnAux dt b r a Source #

Constructors

SplitStructureOnAux 

Fields

newtype SplitOrderOn dt b a Source #

Constructors

SplitOrderOn 

Fields

newtype TakeElemTypeAux a Source #

Constructors

TakeElemTypeAux 

Fields

type family TakeElemAuxType (a :: [*]) (b :: [*]) :: * Source #

Instances

type family TakeElemType (a :: [*]) :: * Source #

Instances

revAppendDT :: NP f a -> NP f b -> NP f (RevAppend a b) Source #

sListCons :: Proxy a -> SList b -> SList (a ': b) Source #

unSListCons :: forall (a :: [k]). SList (_ ': a) -> SList a Source #

sopAppend :: NP f a -> NP f b -> NP f (a :++ b) Source #

npToSList :: NP f a -> SList a Source #

eval :: DecisionTree a b -> NP I a -> b Source #