| Safe Haskell | None |
|---|
Fay.Types
Description
All Fay types and instances.
- data JsStmt
- = JsVar JsName JsExp
- | JsIf JsExp [JsStmt] [JsStmt]
- | JsEarlyReturn JsExp
- | JsThrow JsExp
- | JsWhile JsExp [JsStmt]
- | JsUpdate JsName JsExp
- | JsSetProp JsName JsName JsExp
- | JsSetQName (Maybe SrcSpan) QName JsExp
- | JsSetModule ModulePath JsExp
- | JsSetConstructor QName JsExp
- | JsSetPropExtern JsName JsName JsExp
- | JsContinue
- | JsBlock [JsStmt]
- | JsExpStmt JsExp
- 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)]
- | JsLitObj [(Name, JsExp)]
- | JsUndefined
- | JsAnd JsExp JsExp
- | JsOr JsExp JsExp
- data JsLit
- = JsChar Char
- | JsStr String
- | JsInt Int
- | JsFloating Double
- | JsBool Bool
- data JsName
- = JsNameVar QName
- | JsThis
- | JsParametrizedType
- | JsThunk
- | JsForce
- | JsApply
- | JsParam Integer
- | JsTmp Integer
- | JsConstructor QName
- | JsBuiltIn Name
- | JsModuleName ModuleName
- data CompileError
- = Couldn'tFindImport ModuleName [FilePath]
- | EmptyDoBlock
- | FfiFormatBadChars SrcSpanInfo String
- | FfiFormatIncompleteArg SrcSpanInfo
- | FfiFormatInvalidJavaScript SrcSpanInfo String String
- | FfiFormatNoSuchArg SrcSpanInfo Int
- | FfiNeedsTypeSig Exp
- | GHCError String
- | InvalidDoBlock
- | ParseError SrcLoc String
- | ShouldBeDesugared String
- | UnableResolveQualified QName
- | UnsupportedDeclaration Decl
- | UnsupportedEnum Exp
- | UnsupportedExportSpec ExportSpec
- | UnsupportedExpression Exp
- | UnsupportedFieldPattern PatField
- | UnsupportedImport ImportDecl
- | UnsupportedLet
- | UnsupportedLetBinding Decl
- | UnsupportedLiteral Literal
- | UnsupportedModuleSyntax String Module
- | UnsupportedPattern Pat
- | UnsupportedQualStmt QualStmt
- | UnsupportedRecursiveDo
- | UnsupportedRhs Rhs
- | UnsupportedWhereInAlt Alt
- | UnsupportedWhereInMatch Match
- newtype Compile a = Compile {}
- type CompileModule a = ModuleT Symbols IO (Either CompileError (a, CompileState, CompileWriter))
- class Printable a where
- data Fay a
- data CompileReader = CompileReader {
- readerConfig :: Config
- readerCompileLit :: Sign -> Literal -> Compile JsExp
- readerCompileDecls :: Bool -> [Decl] -> Compile [JsStmt]
- data CompileWriter = CompileWriter {
- writerCons :: [JsStmt]
- writerFayToJs :: [(String, JsExp)]
- writerJsToFay :: [(String, JsExp)]
- data Config
- data CompileState = CompileState {
- stateInterfaces :: Map ModuleName Symbols
- stateRecordTypes :: [(QName, [QName])]
- stateRecords :: [(QName, [Name])]
- stateNewtypes :: [(QName, Maybe QName, Type)]
- stateImported :: [(ModuleName, FilePath)]
- stateNameDepth :: Integer
- stateModuleName :: ModuleName
- stateJsModulePaths :: Set ModulePath
- stateUseFromString :: Bool
- stateTypeSigs :: Map QName Type
- data FundamentalType
- = FunctionType [FundamentalType]
- | JsType FundamentalType
- | ListType FundamentalType
- | TupleType [FundamentalType]
- | UserDefined Name [FundamentalType]
- | Defined FundamentalType
- | Nullable FundamentalType
- | DateType
- | StringType
- | DoubleType
- | IntType
- | BoolType
- | PtrType
- | Automatic
- | UnknownType
- data PrintState = PrintState {
- psPretty :: Bool
- psLine :: Int
- psColumn :: Int
- psMappings :: [Mapping]
- psIndentLevel :: Int
- psOutput :: [String]
- psNewline :: Bool
- defaultPrintState :: PrintState
- newtype Printer a = Printer {
- runPrinter :: State PrintState a
- data SerializeContext
- = SerializeAnywhere
- | SerializeUserArg Int
- data ModulePath
- mkModulePath :: ModuleName a -> ModulePath
- mkModulePaths :: ModuleName a -> [ModulePath]
- mkModulePathFromQName :: QName a -> ModulePath
Documentation
Statement type.
Constructors
Expression type.
Constructors
| 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)] | |
| JsLitObj [(Name, JsExp)] | |
| JsUndefined | |
| JsAnd JsExp JsExp | |
| JsOr JsExp JsExp |
Literal value type.
Constructors
| JsChar Char | |
| JsStr String | |
| JsInt Int | |
| JsFloating Double | |
| JsBool Bool |
A name of some kind.
Constructors
| JsNameVar QName | |
| JsThis | |
| JsParametrizedType | |
| JsThunk | |
| JsForce | |
| JsApply | |
| JsParam Integer | |
| JsTmp Integer | |
| JsConstructor QName | |
| JsBuiltIn Name | |
| JsModuleName ModuleName |
data CompileError Source
Error type.
Constructors
| Couldn'tFindImport ModuleName [FilePath] | |
| EmptyDoBlock | |
| FfiFormatBadChars SrcSpanInfo String | |
| FfiFormatIncompleteArg SrcSpanInfo | |
| FfiFormatInvalidJavaScript SrcSpanInfo String String | |
| FfiFormatNoSuchArg SrcSpanInfo Int | |
| FfiNeedsTypeSig Exp | |
| GHCError String | |
| InvalidDoBlock | |
| ParseError SrcLoc String | |
| ShouldBeDesugared String | |
| UnableResolveQualified QName | |
| UnsupportedDeclaration Decl | |
| UnsupportedEnum Exp | |
| UnsupportedExportSpec ExportSpec | |
| UnsupportedExpression Exp | |
| UnsupportedFieldPattern PatField | |
| UnsupportedImport ImportDecl | |
| UnsupportedLet | |
| UnsupportedLetBinding Decl | |
| UnsupportedLiteral Literal | |
| UnsupportedModuleSyntax String Module | |
| UnsupportedPattern Pat | |
| UnsupportedQualStmt QualStmt | |
| UnsupportedRecursiveDo | |
| UnsupportedRhs Rhs | |
| UnsupportedWhereInAlt Alt | |
| UnsupportedWhereInMatch Match |
Instances
Compile monad.
Constructors
| Compile | |
Fields
| |
Instances
| Monad Compile | |
| Functor Compile | |
| Applicative Compile | |
| MonadIO Compile | |
| MonadModule Compile | |
| MonadError CompileError Compile | |
| MonadReader CompileReader Compile | |
| MonadState CompileState Compile | |
| MonadWriter CompileWriter Compile |
type CompileModule a = ModuleT Symbols IO (Either CompileError (a, CompileState, CompileWriter))Source
Print some value.
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. |
The JavaScript FFI interfacing monad.
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 |
Configuration of the compiler. The fields with a leading underscore
data CompileState Source
State of the compiler.
Constructors
| CompileState | |
Fields
| |
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.
Constructors
Instances
| Show FundamentalType |
data PrintState Source
The state of the pretty printer.
Constructors
| PrintState | |
Fields
| |
Instances
defaultPrintState :: PrintStateSource
Default state.
The printer monad.
Constructors
| Printer | |
Fields
| |
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.
Constructors
| SerializeAnywhere | |
| SerializeUserArg Int |
Instances
| Eq SerializeContext | |
| Read SerializeContext | |
| Show SerializeContext |
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
mkModulePathFromQName :: QName a -> ModulePathSource
Converting a QName to a ModulePath is only relevant for constructors since they can conflict with module names.