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

Safe HaskellNone

Fay.Types

Description

All Fay types and instances.

Synopsis

Documentation

data JsLit Source

Literal value type.

Instances

Eq JsLit 
Show JsLit 
IsString JsLit

Just handy to have.

Printable JsLit

Print literals. These need some special encoding for JS-format literals. Could use the Text.JSON library.

data JsName Source

A name of some kind.

Instances

Eq JsName 
Show JsName 
Printable JsName

Print one of the kinds of names.

class (Parseable from, Printable to) => CompilesTo from to | from -> to whereSource

Just a convenience class to generalize the parsing/printing of various types of syntax.

Methods

compileTo :: from -> Compile toSource

Instances

CompilesTo Exp JsExp

Compiling instance.

CompilesTo Module [JsStmt] 
CompilesTo Decl [JsStmt]

Convenient instance.

class Printable a whereSource

Print some value.

Methods

printJS :: a -> Printer ()Source

Instances

Printable String

Just write out strings.

Printable ModuleName

Print module name.

Printable SpecialCon

Print special constructors (tuples, list, etc.)

Printable QName

Print (and properly encode to JS) a qualified name.

Printable Name

Print (and properly encode) a name.

Printable JsLit

Print literals. These need some special encoding for JS-format literals. Could use the Text.JSON library.

Printable JsName

Print one of the kinds of names.

Printable JsExp

Print an expression.

Printable JsStmt

Print a single statement.

Printable [JsStmt]

Print a list of statements.

Printable (Printer ())

A printer is a printable.

data Fay a Source

The JavaScript FFI interfacing monad.

Instances

data CompileReader Source

Configuration and globals for the compiler.

Constructors

CompileReader 

Fields

readerConfig :: CompileConfig

The compilation configuration.

readerCompileLit :: Literal -> Compile JsExp
 
readerCompileDecls :: Bool -> [Decl] -> Compile [JsStmt]
 

data CompileWriter Source

Things written out by the compiler.

Constructors

CompileWriter 

Fields

writerCons :: [JsStmt]

Constructors.

writerFayToJs :: [JsStmt]

Fay to JS dispatchers.

writerJsToFay :: [JsStmt]

JS to Fay dispatchers.

Instances

data CompileConfig Source

Configuration of the compiler.

Constructors

CompileConfig 

Fields

configOptimize :: Bool

Run optimizations

configFlattenApps :: Bool

Flatten function application?

configExportBuiltins :: Bool

Export built-in functions?

configExportRuntime :: Bool

Export the runtime?

configExportStdlib :: Bool

Export the stdlib?

configExportStdlibOnly :: Bool

Export only the stdlib?

configDispatchers :: Bool

Export dispatchers?

configDispatcherOnly :: Bool

Export only the dispatcher?

configNaked :: Bool

Export without a module wrapper?

configDirectoryIncludes :: [(Maybe String, FilePath)]

Possibly a fay package name, and a include directory.

configPrettyPrint :: Bool

Pretty print the JS output?

configHtmlWrapper :: Bool

Output a HTML file including the produced JS.

configHtmlJSLibs :: [FilePath]

Any JS files to link to in the HTML.

configLibrary :: Bool

Don't invoke main in the produced JS.

configWarn :: Bool

Warn on dubious stuff, not related to typechecking.

configFilePath :: Maybe FilePath

File path to output to. TODO: This flag is not used thoroughly, decide if it's needed.

configTypecheck :: Bool

Typecheck with GHC.

configWall :: Bool

Typecheck with -Wall.

configGClosure :: Bool

Run Google Closure on the produced JS.

configPackageConf :: Maybe FilePath

The package config e.g. packages-6.12.3.

configPackages :: [String]

Included Fay packages.

Instances

Show CompileConfig 
Default CompileConfig

Default configuration.

data CompileState Source

State of the compiler.

Constructors

CompileState 

Fields

_stateExports :: Map ModuleName (Set QName)

Collects exports from modules

stateRecordTypes :: [(QName, [QName])]

Map types to constructors

stateRecords :: [(QName, [QName])]

Map constructors to fields

stateImported :: [(ModuleName, FilePath)]

Map of all imported modules and their source locations.

stateNameDepth :: Integer

Depth of the current lexical scope.

stateLocalScope :: Set Name

Names in the current lexical scope.

stateModuleScope :: ModuleScope

Names in the module scope.

stateModuleName :: ModuleName

Name of the module currently being compiled.

addCurrentExport :: QName -> CompileState -> CompileStateSource

Adds a new export to _stateExports for the module specified by stateModuleName.

getCurrentExports :: CompileState -> Set QNameSource

Get all of the exported identifiers for the current module.

getExportsFor :: ModuleName -> CompileState -> Set QNameSource

Get all of the exported identifiers for the given module.

faySourceDir :: IO FilePathSource

The data-files source directory.

data FundamentalType Source

These are the data types that are serializable directly to native JS data types. Strings, floating points and arrays. The others are: actions in the JS monad, which are thunks that shouldn't be forced when serialized but wrapped up as JS zero-arg functions, and unknown types can't be converted but should at least be forced.

data PrintState Source

The state of the pretty printer.

Constructors

PrintState 

Fields

psPretty :: Bool

Are we to pretty print?

psLine :: Int

The current line.

psColumn :: Int

Current column.

psMapping :: [Mapping]

Source mappings.

psIndentLevel :: Int

Current indentation level.

psOutput :: [String]

The current output. TODO: Make more efficient.

psNewline :: Bool

Just outputted a newline?

newtype Printer a Source

The printer monad.

Constructors

Printer 

Instances

data Mapping Source

A source mapping.

Constructors

Mapping 

Fields

mappingName :: String

The name of the mapping.

mappingFrom :: SrcLoc

The original source location.

mappingTo :: SrcLoc

The new source location.

Instances

data SerializeContext Source

The serialization context indicates whether we're currently serializing some value or a particular field in a user-defined data type.