MagicHaskeller-0.9.6.7: Automatic inductive functional programmer by systematic search

Safe HaskellNone
LanguageHaskell98

MagicHaskeller.ProgramGenerator

Synopsis

Documentation

type Prim = (Int, Int, Type, TyVar, Typed [CoreExpr]) Source #

annotated 'Typed [CoreExpr]'

class WithCommon a where Source #

Minimal complete definition

extractCommon

Methods

extractCommon :: a -> Common Source #

class WithCommon a => ProgramGenerator a where Source #

ProgramGenerator is a generalization of the old Memo type.

Minimal complete definition

unifyingPrograms

Methods

mkTrie :: Common -> [Typed [CoreExpr]] -> [[Typed [CoreExpr]]] -> a Source #

|mkTrie| creates the generator with the default parameters.

mkTrieOpt :: Common -> [Typed [CoreExpr]] -> [[Typed [CoreExpr]]] -> [[Typed [CoreExpr]]] -> a Source #

matchingPrograms, matchingProgramsWOAbsents, unifyingPrograms :: Search m => Type -> a -> m AnnExpr Source #

Instances

ProgramGenerator ProgGen Source # 

Methods

mkTrie :: Common -> [Typed [CoreExpr]] -> [[Typed [CoreExpr]]] -> ProgGen Source #

mkTrieOpt :: Common -> [Typed [CoreExpr]] -> [[Typed [CoreExpr]]] -> [[Typed [CoreExpr]]] -> ProgGen Source #

matchingPrograms :: Search m => Type -> ProgGen -> m AnnExpr Source #

matchingProgramsWOAbsents :: Search m => Type -> ProgGen -> m AnnExpr Source #

unifyingPrograms :: Search m => Type -> ProgGen -> m AnnExpr Source #

Expression e => ProgramGenerator (PGSF e) Source # 

Methods

mkTrie :: Common -> [Typed [CoreExpr]] -> [[Typed [CoreExpr]]] -> PGSF e Source #

mkTrieOpt :: Common -> [Typed [CoreExpr]] -> [[Typed [CoreExpr]]] -> [[Typed [CoreExpr]]] -> PGSF e Source #

matchingPrograms :: Search m => Type -> PGSF e -> m AnnExpr Source #

matchingProgramsWOAbsents :: Search m => Type -> PGSF e -> m AnnExpr Source #

unifyingPrograms :: Search m => Type -> PGSF e -> m AnnExpr Source #

class WithCommon a => ProgramGeneratorIO a where Source #

Minimal complete definition

unifyingProgramsIO

Methods

mkTrieIO :: Common -> [Typed [CoreExpr]] -> [[Typed [CoreExpr]]] -> IO a Source #

|mkTrie| creates the generator with the default parameters.

mkTrieOptIO :: Common -> [Typed [CoreExpr]] -> [[Typed [CoreExpr]]] -> [[Typed [CoreExpr]]] -> IO a Source #

matchingProgramsIO, unifyingProgramsIO :: Type -> a -> RecompT IO AnnExpr Source #

Use memoization requiring IO

extractTCL :: WithCommon a => a -> TyConLib Source #

reducer :: Common -> CoreExpr -> Dynamic Source #

data Common Source #

Constructors

Cmn 

Fields

updateCommon :: [Dynamic] -> [Dynamic] -> [Int] -> Common -> Common Source #

updateCommon can be used for incremetal learning

type Options = Opt [[Primitive]] Source #

options for limiting the hypothesis space.

retsTVar :: (t3, t2, Type, t1, t) -> Bool Source #

splitPrims :: [Typed [CoreExpr]] -> ([Prim], [Prim]) Source #

splitPrimss :: [[Typed [CoreExpr]]] -> ([[Prim]], [[Prim]]) Source #

mapSum :: (MonadPlus m, Delay m) => (a -> m b) -> [[a]] -> m b Source #

applyDo :: (Functor m, Monad m) => ([Type] -> Type -> PriorSubsts m a) -> [Type] -> Type -> PriorSubsts m a Source #

wind :: (a -> a) -> ([Type] -> Type -> a) -> [Type] -> Type -> a Source #

wind_ :: ([Type] -> Type -> a) -> [Type] -> Type -> a Source #

fromAssumptions :: (Search m, Expression e) => Common -> Int -> (Type -> PriorSubsts m [e]) -> (Type -> Type -> PriorSubsts m ()) -> Type -> [Type] -> PriorSubsts m [e] Source #

retMono :: (Search m, Expression e) => Common -> Int -> (Type -> PriorSubsts m [e]) -> (Type -> PriorSubsts m ()) -> (Int8, (Int, [Type], Type)) -> PriorSubsts m [e] Source #

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

mguAssumptions :: (Functor m, MonadPlus m) => Type -> [Type] -> PriorSubsts m [CoreExpr] Source #

mguAssumptions' :: MonadPlus m => [Type] -> Type -> PriorSubsts m [CoreExpr] Source #

matchAssumptions :: (Functor m, MonadPlus m, Expression e) => Common -> Int -> Type -> [Type] -> PriorSubsts m [e] Source #

mguAssumptions_ :: (Functor m, MonadPlus m) => Type -> [Type] -> PriorSubsts m () Source #

mguAssumptions_' :: MonadPlus m => [Type] -> Type -> PriorSubsts m () Source #

retPrimMono :: (Search m, Expression e) => Common -> Int -> (Type -> PriorSubsts m [e]) -> (Type -> PriorSubsts m [e]) -> (Type -> PriorSubsts m [e]) -> (Type -> Type -> PriorSubsts m ()) -> Type -> Prim -> PriorSubsts m [e] Source #

funApSub :: (Search m, Expression e) => (Type -> PriorSubsts m [e]) -> (Type -> PriorSubsts m [e]) -> (Type -> PriorSubsts m [e]) -> Type -> [e] -> PriorSubsts m [e] Source #

funApSubOp :: (Monad m, Monad m1) => (r -> a2 -> r) -> (Type -> m1 (m a2)) -> (Type -> m1 (m a2)) -> (Type -> m1 (m a2)) -> Type -> m r -> m1 (m r) Source #

fap :: (Expression r, Monad m, Monad m1, Foldable t) => (t1 -> m1 (m r)) -> t t1 -> m r -> m1 (m r) Source #

mapAndFoldM :: Monad m => (t2 -> t1 -> t2) -> t2 -> (t -> m t1) -> [t] -> m t2 Source #

retGen :: (Search m, Expression e) => Common -> Int -> (Type -> Type -> [e] -> [e]) -> (Type -> PriorSubsts m [e]) -> (Type -> PriorSubsts m [e]) -> (Type -> PriorSubsts m [e]) -> Type -> Prim -> PriorSubsts m [e] Source #

retGenOrd :: (Search m, Expression e) => Common -> Int -> (Type -> Type -> [e] -> [e]) -> (Type -> PriorSubsts m [e]) -> (Type -> PriorSubsts m [e]) -> (Type -> PriorSubsts m [e]) -> Type -> Prim -> PriorSubsts m [e] Source #

retGenTV1 :: (Search m, Expression e) => Common -> Int -> (Type -> Type -> [e] -> [e]) -> (Type -> PriorSubsts m [e]) -> (Type -> PriorSubsts m [e]) -> (Type -> PriorSubsts m [e]) -> Type -> Prim -> PriorSubsts m [e] Source #

retGen' :: (Integral i, Expression e, Search n) => (Type -> t1 -> PriorSubsts n b) -> Common -> i -> (Type -> Type -> [e] -> t1) -> (Type -> PriorSubsts n [e]) -> (Type -> PriorSubsts n [e]) -> (Type -> PriorSubsts n [e]) -> Type -> (Int, Int, t, TyVar, Typed [CoreExpr]) -> PriorSubsts n b Source #

usedArg :: TyVar -> Type -> Bool Source #

retGenTV0 :: (Integral i, Integral j, Expression e, Search n) => Common -> i -> (Type -> Type -> [e] -> b) -> (Type -> PriorSubsts n [e]) -> (Type -> PriorSubsts n [e]) -> (Type -> PriorSubsts n [e]) -> Type -> (j, j, t, TyVar, Typed [CoreExpr]) -> PriorSubsts n b Source #

filtExprs :: Expression e => Bool -> Type -> Type -> [e] -> [e] Source #

filterExprs :: Expression e => Type -> Type -> [e] -> [e] Source #

constEq :: Type -> [CoreExpr] -> Bool Source #

ceq :: CoreExpr -> Type -> [CoreExpr] -> Bool Source #

recHead :: Type -> CoreExpr -> Bool Source #

retSameVal :: Type -> [CoreExpr] -> Bool Source #

rsv :: Type -> [CoreExpr] -> Bool Source #

rsv' :: CoreExpr -> Type -> [CoreExpr] -> Bool Source #

rv :: Type -> Int8 -> CoreExpr -> CoreExpr Source #

anyRec :: Type -> [CoreExpr] -> Bool Source #

mkSubsts :: Search m => Int -> TyVar -> Type -> PriorSubsts m Int Source #

mkSubst :: Search m => Int -> TyVar -> Type -> PriorSubsts m Int Source #

mkRetty :: Type -> (Type, Type) Source #

reorganizer_ :: ([Type] -> a) -> [Type] -> a Source #

hit :: Type -> [Type] -> Bool Source #

combs :: (Num t1, Eq t1) => t1 -> [t] -> [[t]] Source #

tails :: [t] -> [[t]] Source #