Safe Haskell | None |
---|---|
Language | Haskell98 |
- class WithCommon a => ProgramGenerator a
- data ProgGen
- type ProgGenSF = PGSF CoreExpr
- type ProgGenSFIORef = PGSFIOR CoreExpr
- p :: ExpQ -> ExpQ
- setPrimitives :: [Primitive] -> [Primitive] -> IO ()
- mkPG :: ProgramGenerator pg => [Primitive] -> pg
- mkPGSF :: ProgramGenerator pg => TFGen -> [Int] -> [Primitive] -> [Primitive] -> [Primitive] -> pg
- setPG :: ProgGen -> IO ()
- mkMemo :: ProgramGenerator pg => [Primitive] -> pg
- mkMemoSF :: ProgramGenerator pg => TFGen -> [Int] -> [Primitive] -> [Primitive] -> [Primitive] -> pg
- mkPG075 :: ProgramGenerator pg => [Primitive] -> [Primitive] -> pg
- mkMemo075 :: ProgramGenerator pg => [Primitive] -> [Primitive] -> pg
- mkPGOpt :: ProgramGenerator pg => Options -> [Primitive] -> [Primitive] -> pg
- mkPGX :: ProgramGenerator pg => [Primitive] -> [[Primitive]] -> pg
- mkPGXOpt :: ProgramGenerator pg => Options -> [Primitive] -> [(Primitive, Primitive)] -> [[Primitive]] -> [[(Primitive, Primitive)]] -> pg
- mkPGXOpts :: (Common -> [Typed [CoreExpr]] -> [[Typed [CoreExpr]]] -> [[Typed [CoreExpr]]] -> a) -> Options -> [Primitive] -> [(Primitive, Primitive)] -> [[Primitive]] -> [[(Primitive, Primitive)]] -> a
- updatePGXOpts :: (Common -> [Typed [CoreExpr]] -> [[Typed [CoreExpr]]] -> [[Typed [CoreExpr]]] -> a) -> Maybe [[Primitive]] -> [Dynamic] -> [(Dynamic, Dynamic)] -> [[Dynamic]] -> [[(Dynamic, Dynamic)]] -> Common -> a
- updatePGXOptsFilt :: Int -> (Common -> [Typed [CoreExpr]] -> [[Typed [CoreExpr]]] -> [[Typed [CoreExpr]]] -> a) -> Maybe [[Primitive]] -> [Dynamic] -> [(Dynamic, Dynamic)] -> [[Dynamic]] -> [[(Dynamic, Dynamic)]] -> Common -> a
- type Options = Opt [[Primitive]]
- data Opt a = Opt {
- primopt :: Maybe a
- memodepth :: Int
- memoCondPure :: Type -> Int -> Bool
- memoCond :: MemoCond
- execute :: VarLib -> CoreExpr -> Dynamic
- timeout :: Maybe Int
- forcibleTimeout :: Bool
- guess :: Bool
- contain :: Bool
- constrL :: Bool
- tvndelay :: Int
- tv1 :: Bool
- tv0 :: Bool
- stdgen :: TFGen
- nrands :: [Int]
- fcnrand :: Int -> Int
- options :: Opt a
- data MemoType
- mkPGIO :: ProgramGeneratorIO pg => [Primitive] -> [Primitive] -> IO pg
- mkPGXOptIO :: ProgramGeneratorIO pg => Options -> [Primitive] -> [(Primitive, Primitive)] -> [[Primitive]] -> [[(Primitive, Primitive)]] -> IO pg
- load :: FilePath -> ExpQ
- f :: String -> ExpQ
- setDepth :: Int -> IO ()
- setTimeout :: Int -> IO ()
- unsetTimeout :: IO ()
- define :: Name -> String -> ExpQ -> Q [Dec]
- type Everything = forall a. Typeable a => Every a
- type Filter = forall a. Typeable a => (a -> Bool) -> IO (Every a)
- type Every a = [[(Exp, a)]]
- type EveryIO a = Int -> IO [(Exp, a)]
- findOne :: Typeable a => Bool -> (a -> Bool) -> Exp
- printOne :: Typeable a => Bool -> (a -> Bool) -> IO Exp
- printAll :: Typeable a => Bool -> (a -> Bool) -> IO ()
- printAllF :: (Typeable a, Filtrable a) => Bool -> (a -> Bool) -> IO ()
- io2pred :: Eq b => [(a, b)] -> (a -> b) -> Bool
- filterFirst :: Typeable a => Bool -> (a -> Bool) -> IO (Every a)
- filterFirstF :: (Typeable a, Filtrable a) => Bool -> (a -> Bool) -> IO (Every a)
- filterThen :: Typeable a => (a -> Bool) -> Every a -> IO (Every a)
- filterThenF :: (Filtrable a, Typeable * a) => (a -> Bool) -> Every a -> IO [[(Exp, a)]]
- fp :: Typeable a => Maybe Int -> (a -> Bool) -> [(Exp, a)] -> [(Exp, a)]
- getEverything :: Typeable a => Bool -> IO (Every a)
- everything :: (ProgramGenerator pg, Typeable a) => pg -> Bool -> Every a
- everythingM :: (ProgramGenerator pg, Typeable a, Monad m, Functor m) => pg -> Bool -> Int -> m [(Exp, a)]
- everythingIO :: (ProgramGeneratorIO pg, Typeable a) => pg -> EveryIO a
- unifyable :: ProgramGenerator pg => pg -> Type -> [[Exp]]
- matching :: ProgramGenerator pg => pg -> Type -> [[Exp]]
- getEverythingF :: Typeable a => Bool -> IO (Every a)
- everythingF :: (ProgramGenerator pg, Typeable a) => pg -> Bool -> Every a
- unifyableF :: ProgramGenerator pg => pg -> Type -> [[Exp]]
- matchingF :: ProgramGenerator pg => pg -> Type -> [[Exp]]
- everyACE :: (ProgramGenerator pg, Typeable a) => pg -> Bool -> [[(CoreExpr, a)]]
- everyF :: (Typeable a, Filtrable a) => Opt b -> [[(e, a)]] -> [[(e, a)]]
- stripEvery :: Every a -> a
- pprs :: Every a -> IO ()
- pprsIO :: EveryIO a -> IO ()
- pprsIOn :: Int -> EveryIO a -> IO ()
- lengths :: Every a -> IO ()
- lengthsIO :: EveryIO a -> IO ()
- lengthsIOn :: Int -> EveryIO a -> IO ()
- lengthsIOnLn :: Int -> EveryIO a -> IO ()
- printQ :: (Ppr a, Data a) => Q a -> IO ()
- type Primitive = (HValue, Exp, Type)
- newtype HValue = HV (forall a. a)
- unsafeCoerce# :: a -> b
- exprToTHExp :: VarLib -> CoreExpr -> Exp
- trToTHType :: TypeRep -> Type
- printAny :: Typeable a => Bool -> (a -> Bool) -> IO ()
- p1 :: Exp -> ExpQ
- class Filtrable a
- zipAppend :: [[a]] -> [[a]] -> [[a]]
- mapIO :: (a -> IO b) -> [a] -> IO [b]
- fpIO :: Typeable a => Maybe Int -> (a -> Bool) -> [((Exp, a), (Exp, a))] -> IO [(Exp, a)]
- fIO :: Typeable a => Maybe Int -> (a -> Bool) -> ((Exp, a), (Exp, a)) -> Int -> IO (Maybe (Exp, a))
- fpartial :: Typeable a => Maybe Int -> (a -> Bool) -> [((Exp, a), (Exp, a))] -> [(Exp, a)]
- fpartialIO :: Typeable a => Maybe Int -> (a -> Bool) -> [((e, a), (e, a))] -> IO [(e, a)]
- ftotalIO :: Typeable a => Maybe Int -> (a -> Bool) -> [(e, a)] -> IO [(e, a)]
- etup :: (ProgramGenerator pg, Typeable a) => a -> pg -> Bool -> [[((Exp, a), (Exp, a))]]
- mkCurriedDecls :: String -> ExpQ -> ExpQ -> DecsQ
Re-exported modules
This library implicitly re-exports the entities from
module Language.Haskell.TH as TH
and module Data.Typeable
from the Standard Hierarchical Library of Haskell.
Please refer to their documentations on types from them --- in this documentation, types from TH are all qualified and the only type used from module Typeable
is Typeable.Typeable. Other types you had never seen should be our internal representation.
Setting up your synthesis
Before synthesis, you have to define at least one program generator algorithm (or you may define one once and reuse it for later syntheses).
Other parameters are memoization depth and time out interval, which have default values.
You may elect either to set those values to the 'global variables' using 'set
*' functions (i.e. functions whose names are prefixed by set
), or hand them explicitly as parameters.
Class for program generator algorithms
Please note that ConstrL
and ConstrLSF
are obsoleted and users are expected to use the constrL
option in Option
.
class WithCommon a => ProgramGenerator a Source #
ProgramGenerator is a generalization of the old Memo
type.
ProgramGenerator ProgGen Source # | |
Expression e => ProgramGenerator (PGSF e) Source # | |
The vanilla program generator corresponding to Version 0.7.*
type ProgGenSFIORef = PGSFIOR CoreExpr Source #
Functions for creating your program generator algorithm
You can set your primitives like, e.g.,
,
where the primitive set is consisted of setPrimitives
$(p
[| ( (+) :: Int->Int->Int, 0 :: Int, 'A', [] :: [a] ) |])(+)
specialized to type Int->Int->Int
, 0
specialized to type Int
,
'A'
which has monomorphic type Char
, and []
with polymorphic type [a]
.
As primitive components one can include any variables and constructors within the scope.
However, because currently ad hoc polymorphism is not supported by this library, you may not write
.
Also, you have to specify the type unless you are using a primitive component whose type is monomorphic and instance of setPrimitives
$(p
[| (+) :: Num a => a->a->a |])Typeable
(just like when using the dynamic expression of Concurrent Clean), and thus
you may write
,
while you have to write setPrimitives
$(p
[| 'A' |])
instead of setPrimitives
$(p
[| [] :: [a] |])
.setPrimitives
$(p
[| [] |])
p
is used to convert your primitive component set into the internal form.
setPrimitives :: [Primitive] -> [Primitive] -> IO () Source #
setPrimitives
creates a ProgGen
from the given set of primitives using the current set of options, and sets it as the current program generator.
It used to be equivalent to setPG . mkPG
which overwrites the options with the default, but it is not now.
mkPG :: ProgramGenerator pg => [Primitive] -> pg Source #
:: ProgramGenerator pg | |
=> TFGen | |
-> [Int] | number of random samples at each depth, for each type. |
-> [Primitive] | |
-> [Primitive] | |
-> [Primitive] | |
-> pg |
mkPGSF
and mkMemoSF
are provided mainly for backward compatibility. These functions are defined only for the ProgramGenerator
s whose names end with SF
(i.e., generators with synergetic filtration).
For such generators, they are defined as:
mkPGSF gen nrnds optups tups = mkPGOpt (options{primopt = Just optups, contain = True, stdgen = gen, nrands = nrnds}) tups mkMemoSF gen nrnds optups tups = mkPGOpt (options{primopt = Just optups, contain = False, stdgen = gen, nrands = nrnds}) tups
Older versions prohibited data types holding functions such as [a->b]
, (Int->Char, Bool)
, etc. just for efficiency reasons.
They are still available if you use mkMemo
and mkMemoSF
instead of mkPG
and mkPGSF
respectively, though actually this limitation does not affect the efficiency a lot.
(NB: recently I noticed that use of mkMemo
or mkMemoSF
might not improve the efficiency of generating lambda terms at all, though when I generated combinatory expressions it WAS necessary.
In fact, I mistakenly turned this limitation off, and mkMemo
and mkMemoSF
were equivalent to mkPG
and mkPGSF
, but I did not notice that....)
mkMemo :: ProgramGenerator pg => [Primitive] -> pg Source #
:: ProgramGenerator pg | |
=> TFGen | |
-> [Int] | number of random samples at each depth, for each type. |
-> [Primitive] | |
-> [Primitive] | |
-> [Primitive] | |
-> pg |
mkPGSF
and mkMemoSF
are provided mainly for backward compatibility. These functions are defined only for the ProgramGenerator
s whose names end with SF
(i.e., generators with synergetic filtration).
For such generators, they are defined as:
mkPGSF gen nrnds optups tups = mkPGOpt (options{primopt = Just optups, contain = True, stdgen = gen, nrands = nrnds}) tups mkMemoSF gen nrnds optups tups = mkPGOpt (options{primopt = Just optups, contain = False, stdgen = gen, nrands = nrnds}) tups
mkMemo075
enables some more old good optimization options used until Version 0.7.5, including guess on the primitive functions.
It is for you if you prefer speed, but the result can be non-exhaustive if you use it with your own LibTH.hs.
Also, you need to use the prefixed |(->)| in order for the options to take effect. See LibTH.hs for examples.
mkPGX
and mkPGXOpt
can be used instead of mkPG
and mkPGOpt
if you want to prioritize the primitives.
They take a list of lists of primitives as an argument, whose first element is the list of primitives with the greatest priority,
second element the second greatest priority, and so on.
mkPGX :: ProgramGenerator pg => [Primitive] -> [[Primitive]] -> pg Source #
mkPG
is defined as:
mkPG prims = mkPGSF (mkStdGen 123456) (repeat 5) prims prims
mkPGXOpt :: ProgramGenerator pg => Options -> [Primitive] -> [(Primitive, Primitive)] -> [[Primitive]] -> [[(Primitive, Primitive)]] -> pg Source #
mkPGXOpts :: (Common -> [Typed [CoreExpr]] -> [[Typed [CoreExpr]]] -> [[Typed [CoreExpr]]] -> a) -> Options -> [Primitive] -> [(Primitive, Primitive)] -> [[Primitive]] -> [[(Primitive, Primitive)]] -> a Source #
updatePGXOpts :: (Common -> [Typed [CoreExpr]] -> [[Typed [CoreExpr]]] -> [[Typed [CoreExpr]]] -> a) -> Maybe [[Primitive]] -> [Dynamic] -> [(Dynamic, Dynamic)] -> [[Dynamic]] -> [[(Dynamic, Dynamic)]] -> Common -> a Source #
updatePGXOptsFilt :: Int -> (Common -> [Typed [CoreExpr]] -> [[Typed [CoreExpr]]] -> [[Typed [CoreExpr]]] -> a) -> Maybe [[Primitive]] -> [Dynamic] -> [(Dynamic, Dynamic)] -> [[Dynamic]] -> [[(Dynamic, Dynamic)]] -> Common -> a Source #
options that limit the hypothesis space.
Opt | |
|
default options
options = Opt{ primopt = Nothing , memodepth = 10 , memoCondPure = \ _type depth -> 0<depth , memoCond = \ _type depth -> return $ if depth < 10 then Ram else Recompute , execute = unsafeExecute , timeout = Just 20000 , forcibleTimeout = False , guess = False , contain = True , constrL = False , tv1 = False
These are versions for ProgramGeneratorIO
.
mkPGXOptIO :: ProgramGeneratorIO pg => Options -> [Primitive] -> [(Primitive, Primitive)] -> [[Primitive]] -> [[(Primitive, Primitive)]] -> IO pg Source #
Alternative way to create your program generator algorithm
load
loads a component library file.
Memoization depth
NB: setDepth
will be obsoleted. It is provided for backward compatibility, but
not exactly compatible with the old one in that its result will not affect the behavior of everything
, etc., which explicitly take a ProgramGenerator
as an argument.
Also, in the current implementation, the result of setDepth
will be overwritten by setPrimitives.
Use memodepth
option instead.
:: Int | memoization depth. (Sub)expressions within this size are memoized, while greater expressions will be recomputed (to save the heap space). |
-> IO () |
Currently the default depth is 10. You may want to lower the value if your computer often swaps, or increase it if you have a lot of memory.
Time out
NB: setTimeout
and unsetTimeout
will be obsoleted. They are provided for backward compatibility, but
not exactly compatible with the old ones in that their results will not affect the behavior of everything
, etc., which explicitly take a ProgramGenerator
as an argument.
Also, in the current implementation, the result of setTimeout
and unsetTimeout
will be overwritten by setPrimitives.
Use timeout
option instead.
Because the library generates all the expressions including those with non-linear recursions, you should note that there exist some expressions which take extraordinarily long time. (Imagine a function that takes an integer n and increments 0 for 2^(2^n) times.) For this reason, time out is taken after 0.02 second since each invocation of evaluation by default. This default behavior can be overridden by the following functions.
setTimeout
sets the timeout in microseconds. Also, my implementation of timeout also catches inevitable exceptions like stack space overflow. Note that setting timeout makes the library referentially untransparent. (But currently setTimeout 20000
is the default!)
unsetTimeout :: IO () Source #
unsetTimeout
disables timeout. This is the safe choice.
Defining functions automatically
In this case "automatically" does not mean "inductively" but "deductively using Template Haskell";)
define :: Name -> String -> ExpQ -> Q [Dec] Source #
define
eases use of this library by automating some function definitions. For example,
$( define ''ProgGen "Foo" (p [| (1 :: Int, (+) :: Int -> Int -> Int) |]) )
is equivalent to
memoFoo :: ProgGen memoFoo = mkPG (p [| (1 :: Int, (+) :: Int -> Int -> Int) |]) everyFoo :: Everything everyFoo = everything memoFoo filterFoo :: Filter filterFoo pred = filterThen pred everyFoo
If you do not think this function reduces the number of your keystrokes a lot, you can do without it.
type Everything = forall a. Typeable a => Every a Source #
Generating programs
(There are many variants, but most of the functions here just filter everything
with the predicates you provide.)
Functions suffixed with "F" (like everythingF
, etc.) are filtered versions, where their results are filtered to totally remove semantic duplications. In general they are equivalent to applying everyF
afterwards.
(Note that this is filtration AFTER the program generation, unlike the filtration by using ProgGenSF
is done DURING program generation.)
Quick start
printOne
prints the expression found first.
printAll
prints all the expressions satisfying the given predicate.
io2pred :: Eq b => [(a, b)] -> (a -> b) -> Bool Source #
io2pred
converts a specification given as a set of I/O pairs to the predicate form which other functions accept.
Incremental filtration
Sometimes you may want to filter further after synthesis, because the predicate you previously provided did not specify the function enough. The following functions can be used to filter expressions incrementally.
:: Typeable a | |
=> Bool | whether to include functions with unused arguments |
-> (a -> Bool) | |
-> IO (Every a) |
filterFirst
is like printAll
, but by itself it does not print anything. Instead, it creates a stream of expressions represented in tuples of Exp
and the expressions themselves.
filterThen :: Typeable a => (a -> Bool) -> Every a -> IO (Every a) Source #
filterThen
may be used to further filter the results.
Expression generators
These functions generate all the expressions that have the type you provide.
getEverything
uses the 'global' values set with set*
functions. getEverythingF
is its filtered version
:: (ProgramGenerator pg, Typeable a) | |
=> pg | program generator |
-> Bool | whether to include functions with unused arguments |
-> Every a |
everything
generates all the expressions that fit the inferred type, and their representations in the Exp
form.
It returns a stream of lists, which is equivalent to Spivey's Matrix
data type, i.e., that contains expressions consisted of n primitive components at the n-th element (n = 1,2,...).
everythingF
is its filtered version
:: (ProgramGeneratorIO pg, Typeable a) | |
=> pg | program generator |
-> EveryIO a |
:: ProgramGenerator pg | |
=> pg | program generator |
-> Type | query type |
-> [[Exp]] |
Those functions are like everything
, but take Type
as an argument, which may be polymorphic.
For example,
will print all the expressions using printQ
([t| forall a. a->a->a |] >>= return . unifyable
True 10 memo)memo
whose types unify with forall a. a->a->a
.
(At first I (Susumu) could not find usefulness in finding unifyable expressions, but seemingly Hoogle does something alike, and these functions might enhance it.)
:: ProgramGenerator pg | |
=> pg | program generator |
-> Type | query type |
-> [[Exp]] |
Those functions are like everything
, but take Type
as an argument, which may be polymorphic.
For example,
will print all the expressions using printQ
([t| forall a. a->a->a |] >>= return . unifyable
True 10 memo)memo
whose types unify with forall a. a->a->a
.
(At first I (Susumu) could not find usefulness in finding unifyable expressions, but seemingly Hoogle does something alike, and these functions might enhance it.)
:: (ProgramGenerator pg, Typeable a) | |
=> pg | program generator |
-> Bool | whether to include functions with unused arguments |
-> Every a |
everything
generates all the expressions that fit the inferred type, and their representations in the Exp
form.
It returns a stream of lists, which is equivalent to Spivey's Matrix
data type, i.e., that contains expressions consisted of n primitive components at the n-th element (n = 1,2,...).
everythingF
is its filtered version
:: ProgramGenerator pg | |
=> pg | program generator |
-> Type | query type |
-> [[Exp]] |
Those functions are like everything
, but take Type
as an argument, which may be polymorphic.
For example,
will print all the expressions using printQ
([t| forall a. a->a->a |] >>= return . unifyable
True 10 memo)memo
whose types unify with forall a. a->a->a
.
(At first I (Susumu) could not find usefulness in finding unifyable expressions, but seemingly Hoogle does something alike, and these functions might enhance it.)
:: ProgramGenerator pg | |
=> pg | program generator |
-> Type | query type |
-> [[Exp]] |
Those functions are like everything
, but take Type
as an argument, which may be polymorphic.
For example,
will print all the expressions using printQ
([t| forall a. a->a->a |] >>= return . unifyable
True 10 memo)memo
whose types unify with forall a. a->a->a
.
(At first I (Susumu) could not find usefulness in finding unifyable expressions, but seemingly Hoogle does something alike, and these functions might enhance it.)
:: (ProgramGenerator pg, Typeable a) | |
=> pg | program generator |
-> Bool | whether to include functions with unused arguments |
-> [[(CoreExpr, a)]] |
Utility to filter out equivalent expressions
Unility to get one value easily
stripEvery :: Every a -> a Source #
Pretty printers
pprsIOn :: Int -> EveryIO a -> IO () Source #
pprsIOn depth eio
is the counterpart of pprs (take depth eio)
, while pprsIO eio
is the counterpart of pprs eio
.
Example: pprsIOn 5 (everythingIO (mlist::ProgGen) :: EveryIO ([Char]->[Char]))
Internal data representation
The following types are assigned to our internal data representations.
unsafeCoerce# :: a -> b #
The function unsafeCoerce#
allows you to side-step the typechecker entirely. That
is, it allows you to coerce any type into any other type. If you use this function,
you had better get it right, otherwise segmentation faults await. It is generally
used when you want to write a program that you know is well-typed, but where Haskell's
type system is not expressive enough to prove that it is well typed.
The following uses of unsafeCoerce#
are supposed to work (i.e. not lead to
spurious compile-time or run-time crashes):
- Casting any lifted type to
Any
- Casting
Any
back to the real type - Casting an unboxed type to another unboxed type of the same size (but not coercions between floating-point and integral types)
- Casting between two types that have the same runtime representation. One case is when
the two types differ only in "phantom" type parameters, for example
Ptr Int
toPtr Float
, or[Int]
to[Float]
when the list is known to be empty. Also, anewtype
of a typeT
has the same representation at runtime asT
.
Other uses of unsafeCoerce#
are undefined. In particular, you should not use
unsafeCoerce#
to cast a T to an algebraic data type D, unless T is also
an algebraic data type. For example, do not cast Int->Int
to Bool
, even if
you later cast that Bool
back to Int->Int
before applying it. The reasons
have to do with GHC's internal representation details (for the congnoscenti, data values
can be entered but function closures cannot). If you want a safe type to cast things
to, use Any
, which is not an algebraic data type.
trToTHType :: TypeRep -> Type Source #
printAll
prints all the expressions satisfying the given predicate.
fIO :: Typeable a => Maybe Int -> (a -> Bool) -> ((Exp, a), (Exp, a)) -> Int -> IO (Maybe (Exp, a)) Source #
:: (ProgramGenerator pg, Typeable a) | |
=> a | dummy argument |
-> pg | program generator |
-> Bool | whether to include functions with unused arguments |
-> [[((Exp, a), (Exp, a))]] |