Created
April 11, 2016 07:37
-
-
Save christiaanb/bc31072c7ff9de81e0a140c449297f91 to your computer and use it in GitHub Desktop.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE RankNTypes, DataKinds, PolyKinds, GADTs, TypeFamilies, | |
FlexibleContexts, TemplateHaskell, ScopedTypeVariables, | |
UndecidableInstances, TypeOperators, FlexibleInstances #-} | |
import Data.Proxy | |
import GHC.Types | |
type KindOf (a :: k) = ('KProxy :: KProxy k) | |
data TyFun :: * -> * -> * | |
type family Apply (f :: TyFun k1 k2 -> *) (x :: k1) :: k2 | |
class SuppressUnusedWarnings (t :: k) where | |
suppressUnusedWarnings :: Proxy t -> () | |
type Let1627449119LgoSym5 t_afok | |
t_afol | |
t_afom | |
(t_afon :: b_afnR) | |
(t_afoo :: [a_afnQ]) = | |
Let1627449119Lgo t_afok t_afol t_afom t_afon t_afoo | |
instance SuppressUnusedWarnings Let1627449119LgoSym4 where | |
suppressUnusedWarnings _ | |
= snd | |
((,) | |
Let1627449119LgoSym4KindInference ()) | |
data Let1627449119LgoSym4 l_afoE | |
l_afoF | |
l_afoG | |
(l_afoH :: b_afnR) | |
(l_afoD :: TyFun [a_afnQ] b_afnR) | |
= forall arg_afoI. KindOf (Apply (Let1627449119LgoSym4 l_afoE l_afoF l_afoG l_afoH) arg_afoI) ~ KindOf (Let1627449119LgoSym5 l_afoE l_afoF l_afoG l_afoH arg_afoI) => | |
Let1627449119LgoSym4KindInference | |
type instance Apply (Let1627449119LgoSym4 l_afoE l_afoF l_afoG l_afoH) l_afoD = Let1627449119LgoSym5 l_afoE l_afoF l_afoG l_afoH l_afoD | |
instance SuppressUnusedWarnings Let1627449119LgoSym3 where | |
suppressUnusedWarnings _ | |
= snd | |
((,) | |
Let1627449119LgoSym3KindInference ()) | |
data Let1627449119LgoSym3 l_afoz | |
l_afoA | |
l_afoB | |
(l_afoy :: TyFun b_afnR (TyFun [a_afnQ] b_afnR | |
-> Type)) | |
= forall arg_afoC. KindOf (Apply (Let1627449119LgoSym3 l_afoz l_afoA l_afoB) arg_afoC) ~ KindOf (Let1627449119LgoSym4 l_afoz l_afoA l_afoB arg_afoC) => | |
Let1627449119LgoSym3KindInference | |
type instance Apply (Let1627449119LgoSym3 l_afoz l_afoA l_afoB) l_afoy = Let1627449119LgoSym4 l_afoz l_afoA l_afoB l_afoy | |
instance SuppressUnusedWarnings Let1627449119LgoSym2 where | |
suppressUnusedWarnings _ | |
= snd | |
((,) | |
Let1627449119LgoSym2KindInference ()) | |
data Let1627449119LgoSym2 l_afov l_afow l_afou | |
= forall arg_afox. KindOf (Apply (Let1627449119LgoSym2 l_afov l_afow) arg_afox) ~ KindOf (Let1627449119LgoSym3 l_afov l_afow arg_afox) => | |
Let1627449119LgoSym2KindInference | |
type instance Apply (Let1627449119LgoSym2 l_afov l_afow) l_afou = Let1627449119LgoSym3 l_afov l_afow l_afou | |
instance SuppressUnusedWarnings Let1627449119LgoSym1 where | |
suppressUnusedWarnings _ | |
= snd | |
((,) | |
Let1627449119LgoSym1KindInference ()) | |
data Let1627449119LgoSym1 l_afos l_afor | |
= forall arg_afot. KindOf (Apply (Let1627449119LgoSym1 l_afos) arg_afot) ~ KindOf (Let1627449119LgoSym2 l_afos arg_afot) => | |
Let1627449119LgoSym1KindInference | |
type instance Apply (Let1627449119LgoSym1 l_afos) l_afor = Let1627449119LgoSym2 l_afos l_afor | |
instance SuppressUnusedWarnings Let1627449119LgoSym0 where | |
suppressUnusedWarnings _ | |
= snd | |
((,) | |
Let1627449119LgoSym0KindInference ()) | |
data Let1627449119LgoSym0 l_afop | |
= forall arg_afoq. KindOf (Apply Let1627449119LgoSym0 arg_afoq) ~ KindOf (Let1627449119LgoSym1 arg_afoq) => | |
Let1627449119LgoSym0KindInference | |
type instance Apply Let1627449119LgoSym0 l_afop = Let1627449119LgoSym1 l_afop | |
type family Let1627449119Lgo f_afog | |
z0_afoh | |
xs0_afoi | |
(a_afoJ :: b_afnR) | |
(a_afoK :: [a_afnQ]) :: b_afnR where | |
Let1627449119Lgo f_afog z0_afoh xs0_afoi z_afoL '[] = z_afoL | |
Let1627449119Lgo f_afog z0_afoh xs0_afoi z_afoM ((:) x_afoN xs_afoO) = Apply (Apply (Let1627449119LgoSym3 f_afog z0_afoh xs0_afoi) (Apply (Apply f_afog z_afoM) x_afoN)) xs_afoO | |
type FoldlSym3 (t_afo1 :: TyFun b_afnR (TyFun a_afnQ b_afnR | |
-> Type) | |
-> Type) | |
(t_afo2 :: b_afnR) | |
(t_afo3 :: [a_afnQ]) = | |
Foldl t_afo1 t_afo2 t_afo3 | |
instance SuppressUnusedWarnings FoldlSym2 where | |
suppressUnusedWarnings _ | |
= snd | |
((,) | |
FoldlSym2KindInference ()) | |
data FoldlSym2 (l_afoa :: TyFun b_afnR (TyFun a_afnQ b_afnR | |
-> Type) | |
-> Type) | |
(l_afob :: b_afnR) | |
(l_afo9 :: TyFun [a_afnQ] b_afnR) | |
= forall arg_afoc. KindOf (Apply (FoldlSym2 l_afoa l_afob) arg_afoc) ~ KindOf (FoldlSym3 l_afoa l_afob arg_afoc) => | |
FoldlSym2KindInference | |
type instance Apply (FoldlSym2 l_afoa l_afob) l_afo9 = FoldlSym3 l_afoa l_afob l_afo9 | |
instance SuppressUnusedWarnings FoldlSym1 where | |
suppressUnusedWarnings _ | |
= snd | |
((,) | |
FoldlSym1KindInference ()) | |
data FoldlSym1 (l_afo7 :: TyFun b_afnR (TyFun a_afnQ b_afnR | |
-> Type) | |
-> Type) | |
(l_afo6 :: TyFun b_afnR (TyFun [a_afnQ] b_afnR | |
-> Type)) | |
= forall arg_afo8. KindOf (Apply (FoldlSym1 l_afo7) arg_afo8) ~ KindOf (FoldlSym2 l_afo7 arg_afo8) => | |
FoldlSym1KindInference | |
type instance Apply (FoldlSym1 l_afo7) l_afo6 = FoldlSym2 l_afo7 l_afo6 | |
instance SuppressUnusedWarnings FoldlSym0 where | |
suppressUnusedWarnings _ | |
= snd | |
((,) | |
FoldlSym0KindInference ()) | |
data FoldlSym0 (l_afo4 :: TyFun (TyFun b_afnR (TyFun a_afnQ b_afnR | |
-> Type) | |
-> Type) (TyFun b_afnR (TyFun [a_afnQ] b_afnR | |
-> Type) | |
-> Type)) | |
= forall arg_afo5. KindOf (Apply FoldlSym0 arg_afo5) ~ KindOf (FoldlSym1 arg_afo5) => | |
FoldlSym0KindInference | |
type instance Apply FoldlSym0 l_afo4 = FoldlSym1 l_afo4 | |
type family Foldl (a_afod :: TyFun b_afnR (TyFun a_afnQ b_afnR | |
-> Type) | |
-> Type) | |
(a_afoe :: b_afnR) | |
(a_afof :: [a_afnQ]) :: b_afnR where | |
Foldl f_afog z0_afoh xs0_afoi = Apply (Apply (Let1627449119LgoSym3 f_afog z0_afoh xs0_afoi) z0_afoh) xs0_afoi |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment