fay-0.5.1.0: A compiler for Fay, a Haskell subset that compiles to JavaScript.

Safe HaskellSafe-Infered

Language.Fay

Description

The Haskell→Javascript compiler.

Synopsis

Documentation

compile :: CompilesTo from to => CompileConfig -> from -> IO (Either CompileError (to, CompileState))Source

Compile something that compiles to something else.

compileViaStr :: (Show from, Show to, CompilesTo from to) => CompileConfig -> (from -> Compile to) -> String -> IO (Either CompileError (String, CompileState))Source

Compile a Haskell source string to a JavaScript source string.

compileToAst :: (Show from, Show to, CompilesTo from to) => CompileConfig -> (from -> Compile to) -> String -> IO (Either CompileError (to, CompileState))Source

Compile a Haskell source string to a JavaScript source string.

compileFromStr :: (Parseable a, MonadError CompileError m) => (a -> m a1) -> String -> m a1Source

Compile from a string.

printCompile :: (Show from, Show to, CompilesTo from to) => CompileConfig -> (from -> Compile to) -> String -> IO ()Source

printTestCompile :: String -> IO ()Source

Compile a String of Fay and print it as beautified JavaScript.

compileModule :: Module -> Compile [JsStmt]Source

Compile Haskell module.

compileImport :: ImportDecl -> Compile [JsStmt]Source

Compile the given import.

compileDecls :: Bool -> [Decl] -> Compile [JsStmt]Source

Compile Haskell declaration.

compileDecl :: Bool -> Decl -> Compile [JsStmt]Source

Compile a declaration.

compilePatBind :: Bool -> Maybe Type -> Decl -> Compile [JsStmt]Source

Compile a top-level pattern bind.

compileFFISource

Arguments

:: Name

Name of the to-be binding.

-> String

The format string.

-> Type

Type signature.

-> Compile [JsStmt] 

Compile an FFI call.

formatFFISource

Arguments

:: String

The format string.

-> [(JsParam, FundamentalType)]

Arguments.

-> Compile String

The JS code.

Format the FFI format string with the given arguments.

serialize :: FundamentalType -> JsExp -> JsExpSource

Serialize a value to native JS, if possible.

typeRep :: FundamentalType -> JsExpSource

Get a JS-representation of a fundamental type for encoding/decoding.

functionTypeArgs :: Type -> [FundamentalType]Source

Get arg types of a function type.

argType :: Type -> FundamentalTypeSource

Convert a Haskell type to an internal FFI representation.

typeArity :: Type -> IntSource

Get the arity of a type.

compileNormalPatBind :: Bool -> Name -> Exp -> Compile [JsStmt]Source

Compile a normal simple pattern binding.

compileDataDecl :: Bool -> Decl -> [QualConDecl] -> Compile [JsStmt]Source

Compile a data declaration.

qname :: QName -> StringSource

Extract the string from a qname.

unname :: Name -> StringSource

Extra the string from an ident.

compileFunCase :: Bool -> [Match] -> Compile [JsStmt]Source

Compile a function which pattern matches (causing a case analysis).

optimizeTailCallsSource

Arguments

:: [JsParam]

The function parameters.

-> Name

The function name.

-> [JsStmt]

The body of the function.

-> [JsStmt]

A new optimized function body.

Optimize functions in tail-call form.

flatten :: JsExp -> Maybe [JsExp]Source

Flatten an application expression into function : arg : arg : []

expand :: JsExp -> Maybe [JsExp]Source

Expand a forced value into the value.

prettyPrintFile :: String -> IO StringSource

Format a JS file using js-beautify, or return the JS as-is if js-beautify is unavailable

compileRhs :: Rhs -> Compile JsExpSource

Compile a right-hand-side expression.

compileFunMatch :: Bool -> Match -> Compile [JsStmt]Source

Compile a pattern match binding.

compileExp :: Exp -> Compile JsExpSource

Compile Haskell expression.

compileApp :: Exp -> Exp -> Compile JsExpSource

Compile simple application.

compileInfixApp :: Exp -> QOp -> Exp -> Compile JsExpSource

Compile an infix application, optimizing the JS cases.

compileList :: [Exp] -> Compile JsExpSource

Compile a list expression.

compileIf :: Exp -> Exp -> Exp -> Compile JsExpSource

Compile an if.

compileLambda :: [Pat] -> Exp -> Compile JsExpSource

Compile a lambda.

compileCase :: Exp -> [Alt] -> Compile JsExpSource

Compile case expressions.

compileDoBlock :: [Stmt] -> Compile JsExpSource

Compile a do block.

compileStmt :: Maybe Exp -> Stmt -> Compile (Maybe Exp)Source

Compile a statement of a do block.

compilePatAlt :: JsExp -> Alt -> Compile [JsStmt]Source

Compile the given pattern against the given expression.

compilePat :: JsExp -> Pat -> [JsStmt] -> Compile [JsStmt]Source

Compile the given pattern against the given expression.

compilePLit :: JsExp -> Literal -> [JsStmt] -> Compile [JsStmt]Source

Compile a literal value from a pattern match.

compilePAsPat :: JsExp -> Name -> Pat -> [JsStmt] -> Compile [JsStmt]Source

Compile as binding in pattern match

compileRecConstr :: QName -> [FieldUpdate] -> Compile JsExpSource

Compile a record construction with named fields | GHC will warn on uninitialized fields, they will be undefined in JS.

equalExps :: JsExp -> JsExp -> JsExpSource

Equality test for two expressions, with some optimizations.

isConstant :: JsExp -> BoolSource

Is a JS expression a literal (constant)?

compilePApp :: QName -> [Pat] -> JsExp -> [JsStmt] -> Compile [JsStmt]Source

Compile a pattern application.

compilePList :: [Pat] -> [JsStmt] -> JsExp -> Compile [JsStmt]Source

Compile a pattern list.

compileInfixPat :: JsExp -> Pat -> [JsStmt] -> Compile [JsStmt]Source

Compile an infix pattern (e.g. cons and tuples.)

compileGuardedAlt :: GuardedAlts -> Compile JsExpSource

Compile a guarded alt.

compileLet :: [Decl] -> Exp -> Compile JsExpSource

Compile a let expression.

compileLetDecl :: Decl -> Compile [JsStmt]Source

Compile let declaration.

compileLit :: Literal -> Compile JsExpSource

Compile Haskell literal.

uniqueNames :: [JsParam]Source

Generate unique names.

optimizePatConditions :: [[JsStmt]] -> [[JsStmt]]Source

Optimize pattern matching conditions by merging conditions in common.

throw :: String -> JsExp -> JsStmtSource

Throw a JS exception.

throwExp :: String -> JsExp -> JsExpSource

Throw a JS exception (in an expression).

isWildCardAlt :: Alt -> BoolSource

Is an alt a wildcard?

isWildCardPat :: Pat -> BoolSource

Is a pattern a wildcard?

tmpName :: JsExp -> JsNameSource

A temporary name for testing conditions and such.

thunk :: JsExp -> JsExpSource

Wrap an expression in a thunk.

monad :: JsExp -> JsExpSource

Wrap an expression in a thunk.

stmtsThunk :: [JsStmt] -> JsExpSource

Wrap an expression in a thunk.

force :: JsExp -> JsExpSource

Force an expression in a thunk.

forceInlinable :: CompileConfig -> JsExp -> JsExpSource

Force an expression in a thunk.

resolveOpToVar :: QOp -> Compile ExpSource

Resolve operators to only built-in (for now) functions.

hjIdent :: String -> QNameSource

Make an identifier from the built-in HJ module.

bindToplevel :: Bool -> QName -> JsExp -> Compile JsStmtSource

Make a top-level binding.

emitExport :: ExportSpec -> Compile ()Source

Emit exported names.

parseResult :: ((SrcLoc, String) -> b) -> (a -> b) -> ParseResult a -> bSource

Parse result.

config :: (CompileConfig -> a) -> Compile aSource

Get a config option.