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

Constructors

JsChar Char 
JsStr String 
JsInt Int 
JsFloating Double 
JsBool Bool 

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.

Constructors

JsNameVar QName 
JsThis 
JsParametrizedType 
JsThunk 
JsForce 
JsApply 
JsParam Integer 
JsTmp Integer 
JsConstructor QName 
JsBuiltIn Name 
JsModuleName ModuleName 

Instances

Eq JsName 
Show JsName 
Printable JsName

Print one of the kinds of names.

class Printable a whereSource

Print some value.

Methods

printJS :: a -> Printer ()Source

Instances

Printable String

Just write out strings.

Printable ModulePath

Print a module path.

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

Monad Fay 
Functor Fay 
Applicative Fay 

data CompileReader Source

Configuration and globals for the compiler.

Constructors

CompileReader 

Fields

readerConfig :: Config

The compilation configuration.

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

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

Configuration of the compiler. The fields with a leading underscore

Instances

Show Config 
Default Config

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

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.

Instances

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?

newtype Printer a Source

The printer monad.

Constructors

Printer 

Instances

Monad Printer 
Functor Printer 
Applicative 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

Eq ModulePath 
Ord ModulePath 
Show ModulePath 
Printable ModulePath

Print a module path.

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.