Safe Haskell | None |
---|---|
Language | Haskell98 |
- module MagicHaskeller
- module MagicHaskeller.ExecuteAPI610
- module MagicHaskeller.Analytical
- quickStart :: Typeable a => Q [Dec] -> Q [Dec] -> (a -> Bool) -> IO ()
- quickStartF :: (Filtrable a, Typeable a) => Q [Dec] -> Q [Dec] -> (a -> Bool) -> IO ()
- filterGetOne_ :: Typeable * a => HscEnv -> Q [Dec] -> (a -> Bool) -> IO ()
- filterGetOne :: Typeable a => HscEnv -> Q [Dec] -> (a -> Bool) -> IO (Every a)
- filterGetOneBK :: Typeable a => HscEnv -> Q [Dec] -> Q [Dec] -> (a -> Bool) -> IO (Every a)
- synthFilt :: Typeable a => HscEnv -> Q [Dec] -> Q [Dec] -> (a -> Bool) -> IO (Every a)
- synthFiltF :: (Filtrable a, Typeable a) => HscEnv -> Q [Dec] -> Q [Dec] -> (a -> Bool) -> IO (Every a)
- synthAll :: Typeable a => HscEnv -> Q [Dec] -> Q [Dec] -> IO (Every a)
- noBKQ :: Q [Dec]
Documentation
This module provides analytically-generate-and-test synthesis, i.e. synthesis by filtration of analytically generated (many) expressions.
Actions whose name ends with F use random testing filter (like filterThenF
) in order to reduce the number of expressions.
ATTENTION: This module is supposed to be used under GHCi environment. Currently it is known not to work when executed as an a.out.
Also, this module is tested only on Linux, and does not work with Windows. Another point is that currently functions in this module only
work with known types appearing in defaultPrimitives
.
Re-exported modules
module MagicHaskeller
module MagicHaskeller.ExecuteAPI610
module MagicHaskeller.Analytical
All in one actions
:: Typeable a | |
=> Q [Dec] | target I/O pairs |
-> Q [Dec] | I/O pairs for background knowledge functions |
-> (a -> Bool) | test function |
-> IO () |
Example of quickStart
>>>
quickStart [d| f [] = 0; f [a] = 1 |] noBKQ (\f -> f "12345" == 5)
> \a -> let fa (b@([])) = 0 > fa (b@(c : d)) = succ (fa d) > in fa a :: forall t2 . [t2] -> Int > ^CInterrupted.
filterGet1
and its friends can be used to synthesize one expression satisfying the given condition. For example,
Unlike filterGetOne
and its friends, the following three functions do not print anything but only return results silently.
noBKQ
can be used as the background knowledge for showing that no background knowledge functions are used.