-- Please, see the file LICENSE for copyright and license information. -- | Functions exported by this module can be used to fuse programs as follows: -- -- > import HFusion.HFusion -- > import Control.Monad.Trans(lift) -- > import Language.Haskell.Parser(parseModule) -- > -- > fuseProgram :: String -> Either FusionError String -- > fuseProgram sourceCode = runFusionState newVarGen$ -- > -- Parse input with a Haskell parser. -- > parseResult2FusionState (Language.Haskell.Parser.parseModule sourceCode) -- > -- Convert the haskell AST to the AST used by HFusion. -- > >>= hsModule2HsSyn -- > -- Derive hylomorphisms for the definitions in the program. -- > >>= lift . fmap snd . deriveHylos -- > -- Fuse functions "zip" and "filter" composing "filter" on the second -- > -- argument of "zip" and name "h" the resulting recursive definition. -- > >>= fuse "zip" 2 "filter" ["zf"] -- > -- Translate the result from HFusion AST to Haskell source code. -- > >>= return . hsSyn2HsSourceCode -- > -- > main = do cs <- readFile "examples.hs" -- > putStr$ either (("There was an error: "++) . show) id$ fuseProgram cs -- -- For more information on HFusion please visit . module HFusion.HFusion ( hsModule2HsSyn -- :: HsModule -> FusionState [Def] ,deriveHylos -- :: [Def] -> IntState (([Def],FusionError),[HyloT]) ,fuse -- :: [HyloT] -> String -> Int -> String -> String -> FusionState [Def] ,fuse' -- :: String -> Int -> String -> [String] -> [HyloT] -> FusionState ([Def],String) ,hsSyn2HsSourceCode -- :: [Def] -> String -- * Auxiliary definitions ,runFusionState -- :: VarGen -> FusionState a -> Either FusionError a ,FusionError(..) ,FusionState(..) ,VarGen,newVarGen ,parseResult2FusionState -- :: ParseResult HsModule -> FusionState HsModule -- * Abstract syntax tree ,Def(..),Term(..),Pattern(..),Variable(..),Constructor(..),Literal(..),Boundvar(..) ) where import HFusion.Internal.HsSyn hiding (Vars,VarsB,AlphaConvertible) import HFusion.Internal.Parsing.Translator import HFusion.Internal.Parsing.HyloParser import HFusion.Internal.FuseEnvironment import HFusion.Internal.FuseFace import HFusion.Internal.HyloFace import HFusion.Internal.Utils import Control.Monad.Trans(lift) import Control.Monad(liftM2) import Control.Arrow(first,(&&&)) -- | Transforms a composition of two recursive functions into an equivalent -- recursive function. -- -- @fuse "f" 1 "g" [h_1 .. h_n] dfs@ yields a recursive function equivalent to @f . g@ and calls -- the resulting (possibly mutually) recursive definitions @h_1 .. h_n@. Functions @f@ and @g@ -- must be hylomorphisms defined in @dfs@. -- -- @fuse "f" 2 "g" [h_1 .. h_n] dfs@ yields a recursive function equivalent to @\x y -> f x (g y)@, -- @fuse "f" 3 "g" [h_1 .. h_n] dfs@ yields a recursive function equivalent to @\x y z -> f x y (g z)@, -- and so on ... fuse :: String -> Int -> String -> [String] -> [HyloT] -> FusionState [Def] fuse nombre1 inArg nombre2 resultNames hylos = env2FusionState fuseHylos >>= lift . inline >>= return . map polishDef where fuseHylos :: Env HyloT fuseHylos = do mapM_ insertFuseEnv hylos fuseFuseEnv (map str2var resultNames) (str2var nombre1) inArg (str2var nombre2) -- | Works like 'fuse' but returns also a string resembling the hylomorphism which represents -- the result of fusion. fuse' :: String -> Int -> String -> [String] -> [HyloT] -> FusionState ([Def],String) fuse' nombre1 inArg nombre2 resultNames hylos = env2FusionState fuseHylos >>= lift . uncurry (liftM2 (,)) . (inline &&& showHT) >>= return . first (map polishDef) where fuseHylos :: Env HyloT fuseHylos = do mapM_ insertFuseEnv hylos fuseFuseEnv (map str2var resultNames) (str2var nombre1) inArg (str2var nombre2) -- | Pretty prints a set of definitions into Haskell source code. hsSyn2HsSourceCode :: [Def] -> String hsSyn2HsSourceCode = unlines . map ((++"\n").show)