| Safe Haskell | Trustworthy |
|---|---|
| Language | Haskell2010 |
Elm
Synopsis
- bool :: Bool -> Expr
- string :: String -> Expr
- int :: Int -> Expr
- float :: Float -> Expr
- under :: Expr
- var :: String -> Expr
- app :: [Expr] -> Expr
- list :: [Expr] -> Expr
- op :: String -> Expr -> Expr -> Expr
- let_ :: Expr -> [(Expr, Expr)] -> Expr
- case_ :: Expr -> [(Expr, Expr)] -> Expr
- parens :: Expr -> Expr
- tvar :: String -> Type
- tparam :: String -> Type -> Type
- tparams :: String -> [Type] -> Type
- tapp :: [Type] -> Type
- tunit :: Type
- ttuple :: [Type] -> Type
- trecord :: [(String, Type)] -> Type
- trecordParam :: String -> [(String, Type)] -> Type
- decVariable :: String -> Type -> Expr -> Dec
- decFunction :: String -> Type -> [Expr] -> Expr -> Dec
- decType :: String -> [String] -> [(String, [Type])] -> Dec
- decTypeAlias :: String -> [String] -> Type -> Dec
- select :: String -> ImportItem
- subSelect :: String -> [String] -> ImportItem
- subSelectEvery :: String -> ImportItem
- importSome :: [ImportItem] -> ImportExpr
- importEvery :: ImportExpr
- import_ :: String -> Maybe String -> Maybe ImportExpr -> Import
- module_ :: String -> ImportExpr -> [Import] -> [Dec] -> Module
- renderModule :: Module -> (String, GenError)
- render :: Module -> String
Expressions
app :: [Expr] -> Expr Source #
Function application
>>>genStr (app [var "a", var "b", var "c"])"a b c"
op :: String -> Expr -> Expr -> Expr Source #
Apply an operator to two sub expressions
>>>genStr (op "+" (int 5) (int 6))"5 + 6"
let_ :: Expr -> [(Expr, Expr)] -> Expr Source #
A let...in block
>>>putStrLn $ genStr (let_ (var "a") [(var "a", int 5)])let a = 5 in a
case_ :: Expr -> [(Expr, Expr)] -> Expr Source #
A case...of block
>>>:{putStrLn $ genStr (case_ (var "m") [ (app [var "Just", var "x"], var "x") , (var "Nothing", var "default") ]) :} case m of Just x -> x Nothing -> default
Types
tvar :: String -> Type Source #
A type or type variable
>>>genStr (tvar "Nothing")"Nothing"
>>>genStr (tvar "a")"a"
tparam :: String -> Type -> Type Source #
A type with a single paramater
>>>genStr (tparam "Just" (tvar "a"))"Just a"
tparams :: String -> [Type] -> Type Source #
A type with multiple paramaters
>>>genStr (tparams "Result" [tvar "String", tvar "Int"])"Result String Int"
tapp :: [Type] -> Type Source #
Type application
>>>genStr (tapp [tvar "a", tvar "b", tvar "c"])"a -> b -> c"
ttuple :: [Type] -> Type Source #
A multiple item tuple
>>>genStr (ttuple [tvar "a", tvar "b"])"(a, b)"
trecord :: [(String, Type)] -> Type Source #
A record type
>>>genStr (trecord [("a", tvar "Int"), ("b", tvar "String")])"{ a : Int, b : String }"
trecordParam :: String -> [(String, Type)] -> Type Source #
A paramaterized record type
>>>genStr (trecordParam "a" [("b", tvar "Int")])"{ a | b : Int }"
Declarations
Declare a variable
Arguments
| :: String | The function name |
| -> Type | The function's type |
| -> [Expr] | The fuction's paramaters |
| -> Expr | The function's value |
| -> Dec |
Declare a function
Arguments
| :: String | The type name |
| -> [String] | The type's type paramaters |
| -> [(String, [Type])] | The type's constructors |
| -> Dec |
Declare a type
Arguments
| :: String | The type alias' name |
| -> [String] | The type alias's type paramaters |
| -> Type | The type alias's type |
| -> Dec |
Declare a type alias
Imports
select :: String -> ImportItem Source #
Import an item
subSelectEvery :: String -> ImportItem Source #
Import an item and all constructors
importSome :: [ImportItem] -> ImportExpr Source #
Import all exports of a module
importEvery :: ImportExpr Source #
Import some exports of a module
Arguments
| :: String | The name of the module to import |
| -> Maybe String | A possible alias to import the module as |
| -> Maybe ImportExpr | A possible set of items to expose |
| -> Import |
Import a module
Module
Arguments
| :: String | The module name |
| -> ImportExpr | The module exports |
| -> [Import] | The module imports |
| -> [Dec] | The module decleration |
| -> Module |
Generate a full module