Safe Haskell | None |
---|---|
Language | Haskell98 |
- get1 :: SplicedPrims -> SplicedPrims -> Exp
- getMany :: SplicedPrims -> SplicedPrims -> [[Exp]]
- getManyM :: Search m => SplicedPrims -> SplicedPrims -> m Exp
- getManyTyped :: SplicedPrims -> SplicedPrims -> [[Exp]]
- noBK :: SplicedPrims
- c :: Q [Dec] -> ExpQ
- type SplicedPrims = ([Dec], [Primitive])
- getOne :: [Dec] -> [Dec] -> Exp
- synth :: [Dec] -> [Dec] -> [[Exp]]
- synthM :: Search m => [Dec] -> [Dec] -> m Exp
- synthTyped :: [Dec] -> [Dec] -> [[Exp]]
Analytical synthesizer
This module provides with analytical synthesis, that only generates expressions without testing. (So this alone may not be very useful, and for this reason this is not very well-documented.) In order to generate-and-test over the result of this module, use MagicHaskeller.RunAnalytical.
Synthesizers which can be used with any types.
:: SplicedPrims | target function definition by example |
-> SplicedPrims | background knowledge function definitions by example |
-> Exp |
get1 can be used to synthesize one expression. For example,
>>>
putStrLn $ pprint $ get1 $(c [d| f [] = 0; f [a] = 1; f [a,b] = 2 |]) noBK
> \a -> let fa (b@([])) = 0 > fa (b@(_ : d)) = succ (fa d) > in fa a
:: SplicedPrims | target function definition by example |
-> SplicedPrims | background knowledge function definitions by example |
-> [[Exp]] |
getMany does what you expect from its name.
:: Search m | |
=> SplicedPrims | target function definition by example |
-> SplicedPrims | background knowledge function definitions by example |
-> m Exp |
:: SplicedPrims | target function definition by example |
-> SplicedPrims | background knowledge function definitions by example |
-> [[Exp]] |
getManyTyped is a variant of getMany
that generates typed expressions.
This alone is not very useful, but the type info is required when compiling the expression and is used in MagicHaskeller.RunAnalytical.
noBK :: SplicedPrims Source #
Also, $(c [d| ... |]) :: SplicedPrims
c
is a helper function for extracting some info from the quoted declarations.
type SplicedPrims = ([Dec], [Primitive]) Source #
Synthesizers which are easier to use that can be used only with types appearing defaultPrimitives
getOne :: [Dec] -> [Dec] -> Exp Source #
Example:
>>>
runQ [d| f [] = 0; f [a] = 1; f [a,b] = 2 |] >>= \iops -> putStrLn $ pprint $ getOne iops []
> \a -> let fa (b@([])) = 0 > fa (b@(_ : d)) = succ (fa d) > in fa a
synthTyped :: [Dec] -> [Dec] -> [[Exp]] Source #
synthTyped
is like synth, but adds the infered type signature to each expression. This is useful for executing the expression at runtime using GHC API.