MagicHaskeller-0.9.6.6.1: Automatic inductive functional programmer by systematic search

Safe HaskellNone
LanguageHaskell98

MagicHaskeller.Expression

Documentation

data AnnExpr Source #

Constructors

AE CoreExpr Dynamic 

Instances

Eq AnnExpr Source # 

Methods

(==) :: AnnExpr -> AnnExpr -> Bool #

(/=) :: AnnExpr -> AnnExpr -> Bool #

Ord AnnExpr Source # 
Show AnnExpr Source # 
Expression AnnExpr Source # 

Methods

mkHead :: (Integral i, Integral j) => (CoreExpr -> Dynamic) -> i -> j -> j -> CoreExpr -> AnnExpr Source #

toCE :: AnnExpr -> CoreExpr Source #

fromCE :: (CoreExpr -> Dynamic) -> CoreExpr -> AnnExpr Source #

mapCE :: (CoreExpr -> CoreExpr) -> AnnExpr -> AnnExpr Source #

aeAppErr :: String -> AnnExpr -> AnnExpr -> AnnExpr Source #

appEnv :: Int8 -> AnnExpr -> AnnExpr -> AnnExpr Source #

toAnnExpr :: (CoreExpr -> Dynamic) -> AnnExpr -> AnnExpr Source #

toAnnExprWind :: (CoreExpr -> Dynamic) -> Type -> AnnExpr -> AnnExpr Source #

toAnnExprWindWind :: (CoreExpr -> Dynamic) -> Type -> AnnExpr -> AnnExpr Source #

fromAnnExpr :: AnnExpr -> AnnExpr Source #

reorganize :: Monad m => ([Type] -> m [AnnExpr]) -> [Type] -> m [AnnExpr] Source #

reorganize' :: Monad m => ([Type] -> m [AnnExpr]) -> [Type] -> m [AnnExpr] Source #

reorganizeId :: ([Type] -> [AnnExpr]) -> [Type] -> [AnnExpr] Source #

replaceVars' :: Int8 -> AnnExpr -> [Int8] -> AnnExpr Source #

reorganizeId' :: Functor m => ([Type] -> m AnnExpr) -> [Type] -> m AnnExpr Source #

decodeVars :: Int -> [Int8] -> AnnExpr -> AnnExpr Source #

data MemoExpr Source #

Constructors

ME CoreExpr Dynamic Dynamic 

aeToME :: TyConLib -> RTrie -> Type -> AnnExpr -> MemoExpr Source #

class (Ord e, Show e) => Expression e where Source #

Methods

mkHead :: (Integral i, Integral j) => (CoreExpr -> Dynamic) -> i -> j -> j -> CoreExpr -> e Source #

toCE :: e -> CoreExpr Source #

fromCE :: (CoreExpr -> Dynamic) -> CoreExpr -> e Source #

mapCE :: (CoreExpr -> CoreExpr) -> e -> e Source #

aeAppErr :: String -> e -> e -> e Source #

appEnv :: Int8 -> e -> e -> e Source #

toAnnExpr :: (CoreExpr -> Dynamic) -> e -> AnnExpr Source #

toAnnExprWind :: (CoreExpr -> Dynamic) -> Type -> e -> AnnExpr Source #

toAnnExprWindWind :: (CoreExpr -> Dynamic) -> Type -> e -> AnnExpr Source #

fromAnnExpr :: AnnExpr -> e Source #

reorganize :: Monad m => ([Type] -> m [e]) -> [Type] -> m [e] Source #

reorganize' :: Monad m => ([Type] -> m [e]) -> [Type] -> m [e] Source #

reorganizeId :: ([Type] -> [e]) -> [Type] -> [e] Source #

replaceVars' :: Int8 -> e -> [Int8] -> e Source #

reorganizeId' :: Functor m => ([Type] -> m e) -> [Type] -> m e Source #

decodeVars :: Int -> [Int8] -> e -> e Source #

Instances

Expression CoreExpr Source # 

Methods

mkHead :: (Integral i, Integral j) => (CoreExpr -> Dynamic) -> i -> j -> j -> CoreExpr -> CoreExpr Source #

toCE :: CoreExpr -> CoreExpr Source #

fromCE :: (CoreExpr -> Dynamic) -> CoreExpr -> CoreExpr Source #

mapCE :: (CoreExpr -> CoreExpr) -> CoreExpr -> CoreExpr Source #

aeAppErr :: String -> CoreExpr -> CoreExpr -> CoreExpr Source #

appEnv :: Int8 -> CoreExpr -> CoreExpr -> CoreExpr Source #

toAnnExpr :: (CoreExpr -> Dynamic) -> CoreExpr -> AnnExpr Source #

toAnnExprWind :: (CoreExpr -> Dynamic) -> Type -> CoreExpr -> AnnExpr Source #

toAnnExprWindWind :: (CoreExpr -> Dynamic) -> Type -> CoreExpr -> AnnExpr Source #

fromAnnExpr :: AnnExpr -> CoreExpr Source #

reorganize :: Monad m => ([Type] -> m [CoreExpr]) -> [Type] -> m [CoreExpr] Source #

reorganize' :: Monad m => ([Type] -> m [CoreExpr]) -> [Type] -> m [CoreExpr] Source #

reorganizeId :: ([Type] -> [CoreExpr]) -> [Type] -> [CoreExpr] Source #

replaceVars' :: Int8 -> CoreExpr -> [Int8] -> CoreExpr Source #

reorganizeId' :: Functor m => ([Type] -> m CoreExpr) -> [Type] -> m CoreExpr Source #

decodeVars :: Int -> [Int8] -> CoreExpr -> CoreExpr Source #

Expression AnnExpr Source # 

Methods

mkHead :: (Integral i, Integral j) => (CoreExpr -> Dynamic) -> i -> j -> j -> CoreExpr -> AnnExpr Source #

toCE :: AnnExpr -> CoreExpr Source #

fromCE :: (CoreExpr -> Dynamic) -> CoreExpr -> AnnExpr Source #

mapCE :: (CoreExpr -> CoreExpr) -> AnnExpr -> AnnExpr Source #

aeAppErr :: String -> AnnExpr -> AnnExpr -> AnnExpr Source #

appEnv :: Int8 -> AnnExpr -> AnnExpr -> AnnExpr Source #

toAnnExpr :: (CoreExpr -> Dynamic) -> AnnExpr -> AnnExpr Source #

toAnnExprWind :: (CoreExpr -> Dynamic) -> Type -> AnnExpr -> AnnExpr Source #

toAnnExprWindWind :: (CoreExpr -> Dynamic) -> Type -> AnnExpr -> AnnExpr Source #

fromAnnExpr :: AnnExpr -> AnnExpr Source #

reorganize :: Monad m => ([Type] -> m [AnnExpr]) -> [Type] -> m [AnnExpr] Source #

reorganize' :: Monad m => ([Type] -> m [AnnExpr]) -> [Type] -> m [AnnExpr] Source #

reorganizeId :: ([Type] -> [AnnExpr]) -> [Type] -> [AnnExpr] Source #

replaceVars' :: Int8 -> AnnExpr -> [Int8] -> AnnExpr Source #

reorganizeId' :: Functor m => ([Type] -> m AnnExpr) -> [Type] -> m AnnExpr Source #

decodeVars :: Int -> [Int8] -> AnnExpr -> AnnExpr Source #

mapFst3 :: (t3 -> t2) -> (t3, t1, t) -> (t2, t1, t) Source #

decodeVarsPos :: [Int8] -> ([CoreExpr], t1, t) -> ([CoreExpr], t1, t) Source #

decodeVarsDyn :: Int -> [Int8] -> Dynamic -> Dynamic Source #

insAbsents :: Int8 -> [Int8] -> Dynamic Source #

(<$>) :: Expression e => e -> e -> e Source #

mkHeadAE :: (CoreExpr -> Dynamic) -> Int8 -> Int -> Int8 -> CoreExpr -> AnnExpr Source #

dynSn :: Int8 -> Dynamic Source #

getDyn :: Int8 -> Int8 -> Dynamic Source #

mkDyn :: Int8 -> Int8 -> Dynamic Source #

dynss :: [[Dynamic]] Source #

x :: Integral t => t -> Dynamic Source #

finiteDynss :: [[Dynamic]] Source #

finiteDynsss :: [[[Dynamic]]] Source #

dynsss :: [[[Dynamic]]] Source #

dynBK :: Dynamic Source #

reorganizer :: Monad m => ([Type] -> m [CoreExpr]) -> [Type] -> m [CoreExpr] Source #

reorganizerId :: ([Type] -> [CoreExpr]) -> [Type] -> [CoreExpr] Source #

cvtAvails :: [Type] -> ([Type], [[Int8]]) Source #

tkr10 :: [(Type, a)] -> [(Type, [a])] Source #

annotate :: [Type] -> [(Type, Int8)] Source #

reorganizeCE' :: Monad m => ([Type] -> m [CoreExpr]) -> [Type] -> m [CoreExpr] Source #

cvtAvails' :: [Type] -> ([Int8], [Type]) Source #

uniqSorter :: Expression e => [(e, Int)] -> [(e, Int)] Source #

uniqSortPatAVL :: Expression e => [(e, Int)] -> [(e, Int)] Source #

uniqSort :: Ord a => [a] -> [a] Source #

uniqSortAVL :: Ord a => [a] -> [a] Source #

swapUniqSort :: (Ord a, Ord b) => [(a, b)] -> [(a, b)] Source #

mkEs :: Int -> Q [Name] Source #

mkAs :: Int -> Q [Name] Source #

mkXs :: Int -> Q [Name] Source #

hdmnty :: Int8 -> Int8 -> Type Source #

aimnty :: Int8 -> Int8 -> Int8 -> Type Source #

mkTV :: TyVar -> Type Source #

tvrs :: [Type] Source #

tvas :: [Type] Source #

tvr :: Type Source #

mkCE Source #

Arguments

:: Int8

length of avails

-> Int8

arity of the head function

-> CoreExpr 

data CoreExpr Source #

Instances

Eq CoreExpr Source # 
Ord CoreExpr Source # 
Show CoreExpr Source # 
Expression CoreExpr Source # 

Methods

mkHead :: (Integral i, Integral j) => (CoreExpr -> Dynamic) -> i -> j -> j -> CoreExpr -> CoreExpr Source #

toCE :: CoreExpr -> CoreExpr Source #

fromCE :: (CoreExpr -> Dynamic) -> CoreExpr -> CoreExpr Source #

mapCE :: (CoreExpr -> CoreExpr) -> CoreExpr -> CoreExpr Source #

aeAppErr :: String -> CoreExpr -> CoreExpr -> CoreExpr Source #

appEnv :: Int8 -> CoreExpr -> CoreExpr -> CoreExpr Source #

toAnnExpr :: (CoreExpr -> Dynamic) -> CoreExpr -> AnnExpr Source #

toAnnExprWind :: (CoreExpr -> Dynamic) -> Type -> CoreExpr -> AnnExpr Source #

toAnnExprWindWind :: (CoreExpr -> Dynamic) -> Type -> CoreExpr -> AnnExpr Source #

fromAnnExpr :: AnnExpr -> CoreExpr Source #

reorganize :: Monad m => ([Type] -> m [CoreExpr]) -> [Type] -> m [CoreExpr] Source #

reorganize' :: Monad m => ([Type] -> m [CoreExpr]) -> [Type] -> m [CoreExpr] Source #

reorganizeId :: ([Type] -> [CoreExpr]) -> [Type] -> [CoreExpr] Source #

replaceVars' :: Int8 -> CoreExpr -> [Int8] -> CoreExpr Source #

reorganizeId' :: Functor m => ([Type] -> m CoreExpr) -> [Type] -> m CoreExpr Source #

decodeVars :: Int -> [Int8] -> CoreExpr -> CoreExpr Source #