haskell-generate-0.1: haskell-generate

Safe HaskellNone

Language.Haskell.Generate.Base

Synopsis

Documentation

newtype ExpM t a Source

A ExpM is a monad used to track the imports that are needed for a given expression. Usually, you don't have to use this type directly, but use combinators to combine several ExpM into bigger expressions. The t type parameter tracks the type of the expression, so you don't accidently build expression that don't type check.

Constructors

ExpM 

Instances

Monad (ExpM t) 
Functor (ExpM t) 
Num t => Num (ExpG t) 
Applicative (ExpM t) 
GenExp (ExpG a) 
GenExp x => GenExp (ExpG a -> x) 

type ExpG t = ExpM t ExpSource

The ExpG type is a ExpM computation that returns an expression. Usually, this is the end result of a function generating a haskell expression

type family ExpType a :: *Source

This type family can be used to get the type associated with some expression.

runExpM :: ExpM t a -> (a, Set ModuleName)Source

Evaluate a ExpM action, returning the needed modules and the value.

newName :: String -> ExpM t NameSource

Generate a new unique variable name with the given prefix. Note that this new variable name is only unique relative to other variable names generated by this function.

useValue :: String -> Name -> ExpG aSource

Import a function from a module. This function is polymorphic in the type of the resulting expression, you should probably only use this function to define type-restricted specializations.

Example:

 addInt :: ExpG (Int -> Int -> Int) -- Here we restricted the type to something sensible
 addInt = useValue "Prelude" $ Symbol "+"

useCon :: String -> Name -> ExpM t QNameSource

Import a value constructor from a module. Returns the qualified name of the constructor.

useVar :: Name -> ExpG tSource

Use the value of a variable with the given name.

caseE :: ExpG x -> [(Pat, ExpG t)] -> ExpG tSource

Generate a case expression.

applyE :: ExpG (a -> b) -> ExpG a -> ExpG bSource

Apply a function in a haskell expression to a value.

applyE2 :: ExpG (a -> b -> c) -> ExpG a -> ExpG b -> ExpG cSource

ApplyE for 2 arguments

applyE3 :: ExpG (a -> b -> c -> d) -> ExpG a -> ExpG b -> ExpG c -> ExpG dSource

Apply a function to 3 arguments

applyE4 :: ExpG (a -> b -> c -> d -> e) -> ExpG a -> ExpG b -> ExpG c -> ExpG d -> ExpG eSource

Apply a function to 4 arguments

applyE5 :: ExpG (a -> b -> c -> d -> e -> f) -> ExpG a -> ExpG b -> ExpG c -> ExpG d -> ExpG e -> ExpG fSource

Apply a function to 5 arguments

applyE6 :: ExpG (a -> b -> c -> d -> e -> f -> g) -> ExpG a -> ExpG b -> ExpG c -> ExpG d -> ExpG e -> ExpG f -> ExpG gSource

Apply a function to 6 arguments

(<>$) :: ExpG (a -> b) -> ExpG a -> ExpG bSource

Operator for applyE.

class GenExp t whereSource

Generate a expression from a haskell value.

Associated Types

type GenExpType t :: *Source

Methods

expr :: t -> ExpG (GenExpType t)Source

This function generates the haskell expression from the given haskell value.

Instances

newtype ModuleM a Source

A module keeps track of the needed imports, but also has a list of declarations in it.

Constructors

ModuleM (Writer (Set ModuleName, [Decl]) a) 

type ModuleG = ModuleM (Maybe [ExportSpec])Source

This is the resulting type of a function generating a module. It is a ModuleM action returning the export list.

data FunRef t Source

A reference to a function. With a reference to a function, you can apply it (by lifting it into ExprT using expr) to some value or export it using exportFun.

Constructors

FunRef Name 

Instances

data Name

This type is used to represent variables, and also constructors.

Constructors

Ident String

varid or conid.

Symbol String

varsym or consym

exportFun :: FunRef t -> ExportSpecSource

Generate a ExportSpec for a given function item.

addDecl :: Name -> ExpG t -> ModuleM (FunRef t)Source

Add a declaration to the module. Return a reference to it that can be used to either apply the function to some values or export it.

runModuleM :: ModuleG -> String -> ModuleSource

Extract the Module from a module generator.

generateModule :: ModuleG -> String -> StringSource

Generate the source code for a module.