fay-0.18.0.2: 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.

newtype Compile a Source

Compile monad.

Constructors

Compile 

class Printable a whereSource

Print some value.

Methods

printJS :: a -> Printer ()Source

Instances

Printable String

Just write out strings.

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 ModuleName

Print module 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 ModulePath

Print a module path.

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]
 

Instances

MonadReader CompileReader Compile 

data CompileWriter Source

Things written out by the compiler.

Constructors

CompileWriter 

Fields

writerCons :: [JsStmt]

Constructors.

writerFayToJs :: [(String, JsExp)]

Fay to JS dispatchers.

writerJsToFay :: [(String, JsExp)]

JS to Fay dispatchers.

Instances

Show CompileWriter 
Monoid CompileWriter

Simple concatenating instance.

MonadWriter CompileWriter Compile 

data CompileConfig Source

Configuration of the compiler.

Constructors

CompileConfig 

Fields

configOptimize :: Bool

Run optimizations

configFlattenApps :: Bool

Flatten function application?

configExportRuntime :: Bool

Export the runtime?

configExportStdlib :: Bool

Export the stdlib?

configExportStdlibOnly :: Bool

Export only the stdlib?

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.

configSourceMap :: Bool

Output a source map file as outfile.map.

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.

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.

configBasePath :: Maybe FilePath

Custom source location for fay-base

configStrict :: [String]

Produce strict and uncurried wrappers for all functions with type signatures in the given module

configTypecheckOnly :: Bool

Only invoke GHC for typechecking, don't produce any output

configRuntimePath :: Maybe FilePath
 

Instances

Show CompileConfig 
Default CompileConfig

Default configuration.

data CompileState Source

State of the compiler.

Constructors

CompileState 

Fields

stateInterfaces :: Map ModuleName Symbols

Exported identifiers for all modules

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

Map types to constructors

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

Map constructors to fields

stateNewtypes :: [(QName, Maybe QName, Type)]

Newtype constructor, destructor, wrapped type tuple

stateImported :: [(ModuleName, FilePath)]

Map of all imported modules and their source locations.

stateNameDepth :: Integer

Depth of the current lexical scope, used for creating unshadowing variables.

stateModuleName :: ModuleName

Name of the module currently being compiled.

stateJsModulePaths :: Set ModulePath

Module paths that have code generated for them.

stateUseFromString :: Bool

Use JS Strings instead of [Char] for string literals?

stateTypeSigs :: Map QName Type

Module level declarations having explicit type signatures

Instances

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.

psMappings :: [Mapping]

Source mappings.

psIndentLevel :: Int

Current indentation level.

psOutput :: [String]

The current output. TODO: Make more efficient.

psNewline :: Bool

Just outputted a newline?

Instances

Default PrintState

Default state.

MonadState PrintState Printer 

newtype Printer a Source

The printer monad.

Constructors

Printer 

Fields

runPrinter :: State PrintState a
 

Instances

Monad Printer 
Functor Printer 
MonadState PrintState Printer 
Printable (Printer ())

A printer is a printable.

data SerializeContext Source

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

data ModulePath Source

The name of a module split into a list for code generation.

Instances

mkModulePath :: ModuleName a -> ModulePathSource

Construct the complete ModulePath from a ModuleName.

mkModulePaths :: ModuleName a -> [ModulePath]Source

Construct intermediate module paths from a ModuleName. mkModulePaths A.B => [[A], [A,B]]

mkModulePathFromQName :: QName a -> ModulePathSource

Converting a QName to a ModulePath is only relevant for constructors since they can conflict with module names.