haskell-generate-0.2.4: Typesafe generation of haskell source code

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Generate.Monad

Synopsis

Documentation

newtype Generate a Source

This monad keeps track of a counter for generating unique names and the set of modules that are needed for the expression.

Constructors

Generate 

type ExpG t = Generate (Expression t) Source

This is a type alias for a Generate action that returns an expression of type t.

runGenerate :: Generate a -> (a, Set ModuleName) Source

Extract the set of modules and the value from a Generate action.

newName :: String -> Generate Name Source

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.

returnE :: Exp -> ExpG t Source

Use a haskell-src-exts Exp as the result of a Generate action.

useValue :: String -> Name -> ExpG a Source

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 -> Generate QName Source

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

useVar :: Name -> ExpG t Source

Use the value of a variable with the given name.

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

Generate a case expression.

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

Apply a function in a haskell expression to a value.

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

ApplyE for 2 arguments

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

Apply a function to 3 arguments

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

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 f Source

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 g Source

Apply a function to 6 arguments

(<>$) :: ExpG (a -> b) -> ExpG a -> ExpG b infixl 1 Source

Operator for applyE.

class GenExp t where Source

Generate a expression from a haskell value. This can for example be used to create lambdas:

>>> putStrLn $ generateExp $ expr (\x f -> f <>$ x)
\ pvar_0 -> \ pvar_1 -> pvar_1 pvar_0

Or string literals:

>>> putStrLn $ generateExp $ expr "I'm a string!"
['I', '\'', 'm', ' ', 'a', ' ', 's', 't', 'r', 'i', 'n', 'g', '!']

Associated Types

type GenExpType t :: * Source

Methods

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

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

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

Instances

Eq Name 
Data Name 
Ord Name 
Show Name 
Generic Name 
Pretty Name 
type Rep Name = D1 D1Name ((:+:) (C1 C1_0Name (S1 NoSelector (Rec0 String))) (C1 C1_1Name (S1 NoSelector (Rec0 String)))) 

exportFun :: FunRef t -> ExportSpec Source

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 -> Module Source

Extract the Module from a module generator.

generateModule :: ModuleG -> String -> String Source

Generate the source code for a module.

generateExp :: ExpG t -> String Source

Pretty print the expression generated by a given action.