hfusion-0.0.5.1: A library for fusing a subset of Haskell programs.

HFusion.HFusion

Contents

Description

Functions exported by this module can be used to fuse programs as shown below. The following program reads some Haskell definitions from the standard input and prints the transformed definitions to the standard output.

 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 
    -- Fuse compositions in the program.
    >>= \dfs -> lift (fuseDefinitions dfs dfs) 
    -- Pretty print the result.
    >>= return . hsSyn2HsSourceCode . uncurry (++)

    main = do cs <- getContents
              putStr$ either (("There was an error: "++) . show) id$ fuseProgram cs

For more information on HFusion please visit http://www.fing.edu.uy/inco/proyectos/fusion.

Synopsis

Documentation

hsModule2HsSyn :: HsModule -> FusionState [Def]Source

Converts an HsModule into the abstract syntax tree used by HFusion. The HsModule can be obtained by parsing a Haskell program with Language.Haskell.Parser.parseModule

deriveHylos :: [Def] -> VarGenState ([([Def], FusionError)], [([Def], HyloT)])Source

Obtains hylomorphisms representing functions in the original program.

The hylomorphisms are returned in the second component of the output. If a hylomorphism cannot be derived for some (possibly) mutually recursive function definitions, then they are returned in the first component of the output together with the error obtained when attempting derivation.

fuseDefinitionsSource

Arguments

:: [Def]

Definitions in scope. Hylomorphism will be derived from them.

-> [Def]

Definitions containing compositions which must be eliminated.

-> VarGenState ([Def], [Def])

The transformed definitions without the compositions that were succesfully fused and the additional definitions introduced as a result of fusion.

Eliminates compositions of recursive functions from definitions.

fuse :: String -> Int -> String -> [String] -> [HyloT] -> FusionState [Def]Source

Fuses the composition of two recursive functions producing an equivalent new recursive function.

fuse f 1 g [h_1 .. h_n] dfns yields a set of mutually recursive functions named h_1 .. h_n which are equivalent to f . g. Functions f and g must be hylomorphisms defined in dfns.

fuse f 2 g [h_1 .. h_n] dfns yields a recursive function equivalent to \x y -> f x (g y), fuse f 3 g [h_1 .. h_n] dfns 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], String)Source

Works like fuse but returns also a string resembling the hylomorphism which represents the result of fusion.

hsSyn2HsSourceCode :: [Def] -> StringSource

Pretty prints a set of definitions into Haskell source code.

Auxiliary definitions

runFusionState :: VarGen -> FusionState a -> Either FusionError aSource

Runs a FusionState computation using the given variable generator. The result is either the promised value or a FusionError.

data FusionError Source

Errors that the algorithms in HFusion can produce.

Constructors

NotSaturated Term

Thrown when hylomorphism derivation fails due to the existence of a non-saturated application of the recursive function in its definition.

NotExpected Term

Thrown when hylomorphism derivation fails due to encountering a Term like Thyloapp which is not expected in the input.

NotInF

Thrown when fusion fails due to the inability of the implementation to derive an unfold from the definition at the right of the composition.

NotOutF

Thrown when fusion fails due to the inability of the implementation to derive a fold from the definition at the left of the composition.

NotTau

Thrown when fusion fails due to the inability of the implementation to derive a tau transformer from the algebra of the definition at the right of the composition.

NotSigma

Thrown when fusion fails due to the inability of the implementation to derive a sigma transformer from the coalgebra of the definition at the left of the composition.

NotFound String

When a definition which was requested to be fused is not found among the derived hylomorphisms.

Msg String

A generic error message.

ParserError SrcLoc String

Thrown when translation of a program to a Def values fails.

type FusionState a = ErrorT FusionError VarGenState aSource

An error monad with FusionError errors and a state monad carrying a generator of fresh variables.

type VarGen = Map String IntSource

Data used to generate variables. The map stores for each variable name generated so far which was the index last used to generate a fresh variable with such a name as prefix.

newVarGen :: VarGenSource

Creates a variable generator

parseResult2FusionState :: ParseResult HsModule -> FusionState HsModuleSource

Allows to handle parsing of an HsModule as a FusionState computation.

parseResult2FusionState (Language.Haskell.Parser.parseModule sourceCode)

Abstract syntax tree

data Def Source

Representation for function definitions.

Constructors

Defvalue Variable Term 

Instances

Show Def 
Vars Def 
ShowDoc Def 

data Term Source

Representation for terms in programs handled by HFusion.

Constructors

Tvar Variable

Variables

Tlit Literal

Literals

Ttuple Bool [Term]

Tuples. The boolean argument tells if the tuple must be flattened when nested with others under an hylo application.

Tlamb Boundvar Term

Lambda expressions

Tlet Variable Term Term

Let expressions

Tcase Term [Pattern] [Term]

Case expressions

Tfapp Variable [Term]

Function application (saturated)

Tcapp Constructor [Term]

Constructor application

Tapp Term Term

General term application

Tbottom

Undefined computation

Tif Term Term Term

If expressions, only used for pretty printing

Tpar Term 
Thyloapp Variable Int [Term] (Maybe [Int]) Term

Hylo application, only used for inlining. In Thyloapp name recargsCount non-recargs recarg the argument recarg may be a tuple.

Instances

Eq Term 
Show Term 
AlphaConvertible Term 
VarsB Term 
Vars Term 
ShowDoc Term 
TermWrappable Phii 
WrapTau Term 
Acomp2Term Phii 
ShowDocA Phii 
Inlineable Phii 
ShowRep Term 
WrapHT Term 

data Pattern Source

Representation of patterns

Constructors

Pvar Variable

Variables

Ptuple [Pattern]

Tuple patterns

Pcons Constructor [Pattern]

Constructor application patterns

Plit Literal

Literals

Pas Variable Pattern

@-pattern

Instances

Eq Pattern 
Show Pattern 
AlphaConvertible Pattern 
Vars Pattern 
ShowDoc Pattern 

data Variable Source

Representation of variables.

Constructors

Vuserdef String

Name found in the original program.

Vgen String Int

Generated identifier containing a prefix and an index.

Instances

Eq Variable 
Ord Variable 
Show Variable 
AlphaConvertible Variable 
Vars Variable 
ShowDoc Variable 

type Constructor = StringSource

Representation for constructors.

data Literal Source

Representation for Literals.

Constructors

Lstring String

String literals

Lint String

Integer literals

Lchar Char

Character literals

Lrat String

Rational literals

Instances

data Boundvar Source

Representation of bound variables in lambda expressions.

Constructors

Bvar Variable 
Bvtuple Bool [Boundvar]

Bound variable tuples. Uses the boolean value like in Ttuple. but when bounding input variables of hylomorphisms.

Instances

Eq Boundvar 
Show Boundvar 
AlphaConvertible Boundvar 
Vars Boundvar 
ShowDoc Boundvar