| Safe Haskell | None | 
|---|
Fay.Types
Description
All Fay types and instances.
- data JsStmt
- data  JsExp - = JsName JsName
- | JsRawExp String
- | JsSeq [JsExp]
- | JsFun (Maybe JsName) [JsName] [JsStmt] (Maybe JsExp)
- | JsLit JsLit
- | JsApp JsExp [JsExp]
- | JsNegApp JsExp
- | JsTernaryIf JsExp JsExp JsExp
- | JsNull
- | JsParen JsExp
- | JsGetProp JsExp JsName
- | JsLookup JsExp JsExp
- | JsUpdateProp JsExp JsName JsExp
- | JsGetPropExtern JsExp String
- | JsUpdatePropExtern JsExp JsName JsExp
- | JsList [JsExp]
- | JsNew JsName [JsExp]
- | JsThrowExp JsExp
- | JsInstanceOf JsExp JsName
- | JsIndex Int JsExp
- | JsEq JsExp JsExp
- | JsNeq JsExp JsExp
- | JsInfix String JsExp JsExp
- | JsObj [(String, JsExp)]
- | JsUndefined
 
- data JsLit
- data JsName
- data  CompileError - = ParseError SrcLoc String
- | UnsupportedDeclaration Decl
- | UnsupportedExportSpec ExportSpec
- | UnsupportedMatchSyntax Match
- | UnsupportedWhereInMatch Match
- | UnsupportedExpression Exp
- | UnsupportedLiteral Literal
- | UnsupportedLetBinding Decl
- | UnsupportedOperator QOp
- | UnsupportedPattern Pat
- | UnsupportedFieldPattern PatField
- | UnsupportedRhs Rhs
- | UnsupportedGuardedAlts GuardedAlts
- | UnsupportedWhereInAlt Alt
- | UnsupportedImport ImportDecl
- | UnsupportedQualStmt QualStmt
- | EmptyDoBlock
- | UnsupportedModuleSyntax Module
- | LetUnsupported
- | InvalidDoBlock
- | RecursiveDoUnsupported
- | Couldn'tFindImport ModuleName [FilePath]
- | FfiNeedsTypeSig Decl
- | FfiFormatBadChars SrcLoc String
- | FfiFormatNoSuchArg SrcLoc Int
- | FfiFormatIncompleteArg SrcLoc
- | FfiFormatInvalidJavaScript SrcLoc String String
- | UnableResolveUnqualified Name
- | UnableResolveQualified QName
 
- newtype Compile a = Compile {}
- class (Parseable from, Printable to) => CompilesTo from to | from -> to where
- class Printable a where
- data Fay a
- data  CompileReader  = CompileReader {- readerConfig :: CompileConfig
- readerCompileLit :: Literal -> Compile JsExp
- readerCompileDecls :: Bool -> [Decl] -> Compile [JsStmt]
 
- data  CompileWriter  = CompileWriter {- writerCons :: [JsStmt]
- writerFayToJs :: [(String, JsExp)]
- writerJsToFay :: [(String, JsExp)]
 
- data  CompileConfig  = CompileConfig {- configOptimize :: Bool
- configFlattenApps :: Bool
- configExportBuiltins :: Bool
- configExportRuntime :: Bool
- configExportStdlib :: Bool
- configExportStdlibOnly :: Bool
- configDispatchers :: Bool
- configDispatcherOnly :: Bool
- configNaked :: Bool
- configDirectoryIncludes :: [(Maybe String, FilePath)]
- configPrettyPrint :: Bool
- configHtmlWrapper :: Bool
- configHtmlJSLibs :: [FilePath]
- configLibrary :: Bool
- configWarn :: Bool
- configFilePath :: Maybe FilePath
- configTypecheck :: Bool
- configWall :: Bool
- configGClosure :: Bool
- configPackageConf :: Maybe FilePath
- configPackages :: [String]
- configBasePath :: Maybe FilePath
 
- data  CompileState  = CompileState {- _stateExports :: Map ModuleName (Set QName)
- stateRecordTypes :: [(QName, [QName])]
- stateRecords :: [(QName, [QName])]
- stateNewtypes :: [(QName, Maybe QName, Type)]
- stateImported :: [(ModuleName, FilePath)]
- stateNameDepth :: Integer
- stateLocalScope :: Set Name
- stateModuleScope :: ModuleScope
- stateModuleScopes :: Map ModuleName ModuleScope
- stateModuleName :: ModuleName
 
- addCurrentExport :: QName -> CompileState -> CompileState
- getCurrentExports :: CompileState -> Set QName
- getCurrentExportsWithoutNewtypes :: CompileState -> Set QName
- getExportsFor :: ModuleName -> CompileState -> Set QName
- faySourceDir :: IO FilePath
- data FundamentalType
- data PrintState = PrintState {}
- newtype  Printer a = Printer {- runPrinter :: State PrintState a
 
- data Mapping = Mapping {}
- data SerializeContext
Documentation
Statement type.
Expression type.
Constructors
Literal value type.
A name of some kind.
data CompileError Source
Error type.
Constructors
Compile monad.
Constructors
| Compile | |
| Fields 
 | |
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.
Instances
| CompilesTo Exp JsExp | Compiling instance. | 
| CompilesTo Module [JsStmt] | |
| CompilesTo Decl [JsStmt] | Convenient instance. | 
Print some value.
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 CompileReader Source
Configuration and globals for the compiler.
Constructors
| CompileReader | |
| Fields 
 | |
Instances
data CompileWriter Source
Things written out by the compiler.
Constructors
| CompileWriter | |
| Fields 
 | |
Instances
| Show CompileWriter | |
| Monoid CompileWriter | Simple concatenating instance. | 
| MonadWriter CompileWriter Compile | 
data CompileConfig Source
Configuration of the compiler.
Constructors
| CompileConfig | |
| Fields 
 | |
Instances
| Show CompileConfig | |
| Default CompileConfig | Default configuration. | 
data CompileState Source
State of the compiler.
Constructors
| CompileState | |
| Fields 
 | |
Instances
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.
Constructors
Instances
data PrintState Source
The state of the pretty printer.
Constructors
| PrintState | |
| Fields | |
Instances
| Default PrintState | Default state. | 
| MonadState PrintState Printer | 
The printer monad.
Constructors
| Printer | |
| Fields 
 | |
Instances
| Monad Printer | |
| Functor Printer | |
| MonadState PrintState Printer | |
| Printable (Printer ()) | A printer is a printable. | 
A source mapping.
Constructors
| Mapping | |
| Fields 
 | |
data SerializeContext Source
The serialization context indicates whether we're currently serializing some value or a particular field in a user-defined data type.
Constructors
| SerializeAnywhere | |
| SerializeUserArg Int |