Safe Haskell | None |
---|---|
Language | Haskell98 |
All Fay types and instances.
Synopsis
- data JsStmt
- = JsVar JsName JsExp
- | JsMapVar 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
- 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 {
- unCompile :: RWST CompileReader CompileWriter CompileState (ExceptT CompileError (ModuleT (ModuleInfo Compile) IO)) a
- 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 CompileResult = CompileResult {
- resOutput :: String
- resImported :: [(String, FilePath)]
- resSourceMappings :: Maybe [Mapping]
- 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
- data PrintState = PrintState {}
- defaultPrintState :: PrintState
- data PrintReader = PrintReader {}
- defaultPrintReader :: PrintReader
- data PrintWriter = PrintWriter {
- pwMappings :: [Mapping]
- pwOutput :: ShowS
- pwOutputString :: PrintWriter -> String
- newtype Printer = Printer {}
- execPrinter :: Printer -> PrintReader -> PrintWriter
- indented :: Printer -> Printer
- askIf :: (PrintReader -> Bool) -> Printer -> Printer -> Printer
- newline :: Printer
- write :: String -> Printer
- mapping :: SrcSpan -> Printer
- data SerializeContext
- data ModulePath
- mkModulePath :: ModuleName a -> ModulePath
- mkModulePaths :: ModuleName a -> [ModulePath]
- mkModulePathFromQName :: QName a -> ModulePath
Documentation
Statement type.
Expression type.
Literal value type.
A name of some kind.
JsNameVar QName | |
JsThis | |
JsParametrizedType | |
JsThunk | |
JsForce | |
JsApply | |
JsParam Integer | |
JsTmp Integer | |
JsConstructor QName | |
JsBuiltIn Name | |
JsModuleName ModuleName |
data CompileError Source #
Error type.
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
Show CompileError Source # | |
showsPrec :: Int -> CompileError -> ShowS # show :: CompileError -> String # showList :: [CompileError] -> ShowS # | |
MonadError CompileError Compile # | |
throwError :: CompileError -> Compile a # catchError :: Compile a -> (CompileError -> Compile a) -> Compile a # |
Compile monad.
Compile | |
|
Instances
Monad Compile Source # | |
Functor Compile Source # | |
Applicative Compile Source # | |
MonadIO Compile Source # | |
MonadWriter CompileWriter Compile Source # | |
writer :: (a, CompileWriter) -> Compile a # tell :: CompileWriter -> Compile () # listen :: Compile a -> Compile (a, CompileWriter) # pass :: Compile (a, CompileWriter -> CompileWriter) -> Compile a # | |
MonadState CompileState Compile Source # | |
get :: Compile CompileState # put :: CompileState -> Compile () # state :: (CompileState -> (a, CompileState)) -> Compile a # | |
MonadReader CompileReader Compile Source # | |
ask :: Compile CompileReader # local :: (CompileReader -> CompileReader) -> Compile a -> Compile a # reader :: (CompileReader -> a) -> Compile a # | |
MonadError CompileError Compile Source # | |
throwError :: CompileError -> Compile a # catchError :: Compile a -> (CompileError -> Compile a) -> Compile a # |
type CompileModule a = ModuleT Symbols IO (Either CompileError (a, CompileState, CompileWriter)) Source #
class Printable a where Source #
Print some value.
Instances
Printable ModulePath Source # | Print a module path. |
printJS :: ModulePath -> Printer Source # | |
Printable JsLit Source # | Print literals. |
Printable JsName Source # | Print one of the kinds of names. |
Printable JsExp Source # | Print an expression. |
Printable JsStmt Source # | Print a single statement. |
Printable (ModuleName l) Source # | Print module name. |
Printable (Name l) Source # | Print (and properly encode) a name. |
Printable (QName l) Source # | Print (and properly encode to JS) a qualified name. |
Printable (SpecialCon l) Source # | Print special constructors (tuples, list, etc.) |
The JavaScript FFI interfacing monad.
data CompileReader Source #
Configuration and globals for the compiler.
CompileReader | |
|
Instances
MonadReader CompileReader Compile Source # | |
ask :: Compile CompileReader # local :: (CompileReader -> CompileReader) -> Compile a -> Compile a # reader :: (CompileReader -> a) -> Compile a # |
data CompileResult Source #
CompileResult | |
|
Instances
Show CompileResult Source # | |
showsPrec :: Int -> CompileResult -> ShowS # show :: CompileResult -> String # showList :: [CompileResult] -> ShowS # |
data CompileWriter Source #
Things written out by the compiler.
CompileWriter | |
|
Instances
Show CompileWriter Source # | |
showsPrec :: Int -> CompileWriter -> ShowS # show :: CompileWriter -> String # showList :: [CompileWriter] -> ShowS # | |
Semigroup CompileWriter Source # | Simple concatenating instance. |
(<>) :: CompileWriter -> CompileWriter -> CompileWriter # sconcat :: NonEmpty CompileWriter -> CompileWriter # stimes :: Integral b => b -> CompileWriter -> CompileWriter # | |
Monoid CompileWriter Source # | Simple concatenating instance. |
mempty :: CompileWriter # mappend :: CompileWriter -> CompileWriter -> CompileWriter # mconcat :: [CompileWriter] -> CompileWriter # | |
MonadWriter CompileWriter Compile Source # | |
writer :: (a, CompileWriter) -> Compile a # tell :: CompileWriter -> Compile () # listen :: Compile a -> Compile (a, CompileWriter) # pass :: Compile (a, CompileWriter -> CompileWriter) -> Compile a # |
Configuration of the compiler. The fields with a leading underscore
data CompileState Source #
State of the compiler.
CompileState | |
|
Instances
Show CompileState Source # | |
showsPrec :: Int -> CompileState -> ShowS # show :: CompileState -> String # showList :: [CompileState] -> ShowS # | |
MonadState CompileState Compile Source # | |
get :: Compile CompileState # put :: CompileState -> Compile () # state :: (CompileState -> (a, CompileState)) -> Compile a # |
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
Show FundamentalType Source # | |
showsPrec :: Int -> FundamentalType -> ShowS # show :: FundamentalType -> String # showList :: [FundamentalType] -> ShowS # |
defaultPrintState :: PrintState Source #
Default state.
data PrintReader Source #
Global options of the printer
PrintReader | |
|
defaultPrintReader :: PrintReader Source #
default printer options (non-pretty printing)
data PrintWriter Source #
Output of printer
PrintWriter | |
|
Instances
Semigroup PrintWriter Source # | |
(<>) :: PrintWriter -> PrintWriter -> PrintWriter # sconcat :: NonEmpty PrintWriter -> PrintWriter # stimes :: Integral b => b -> PrintWriter -> PrintWriter # | |
Monoid PrintWriter Source # | Output concatenation |
mempty :: PrintWriter # mappend :: PrintWriter -> PrintWriter -> PrintWriter # mconcat :: [PrintWriter] -> PrintWriter # |
pwOutputString :: PrintWriter -> String Source #
The printer.
execPrinter :: Printer -> PrintReader -> PrintWriter Source #
askIf :: (PrintReader -> Bool) -> Printer -> Printer -> Printer Source #
exec one of Printers depending on PrintReader property.
Output a newline and makes next line indented when prPretty is True. Does nothing when prPretty is False
write :: String -> Printer Source #
Write out a raw string, respecting the indentation
Note: if you pass a string with newline characters, it will print them
out even if prPretty is set to False. Also next line won't be indented.
If you want write a smart newline (that is the one which will be written
out only if prPretty is true, and after which the line will be indented)
use newline
)
mapping :: SrcSpan -> Printer Source #
Generate a mapping from the Haskell location to the current point in the output.
data SerializeContext Source #
The serialization context indicates whether we're currently serializing some value or a particular field in a user-defined data type.
Instances
Eq SerializeContext Source # | |
(==) :: SerializeContext -> SerializeContext -> Bool # (/=) :: SerializeContext -> SerializeContext -> Bool # | |
Read SerializeContext Source # | |
Show SerializeContext Source # | |
showsPrec :: Int -> SerializeContext -> ShowS # show :: SerializeContext -> String # showList :: [SerializeContext] -> ShowS # |
data ModulePath Source #
The name of a module split into a list for code generation.
Instances
Eq ModulePath Source # | |
(==) :: ModulePath -> ModulePath -> Bool # (/=) :: ModulePath -> ModulePath -> Bool # | |
Ord ModulePath Source # | |
compare :: ModulePath -> ModulePath -> Ordering # (<) :: ModulePath -> ModulePath -> Bool # (<=) :: ModulePath -> ModulePath -> Bool # (>) :: ModulePath -> ModulePath -> Bool # (>=) :: ModulePath -> ModulePath -> Bool # max :: ModulePath -> ModulePath -> ModulePath # min :: ModulePath -> ModulePath -> ModulePath # | |
Show ModulePath Source # | |
showsPrec :: Int -> ModulePath -> ShowS # show :: ModulePath -> String # showList :: [ModulePath] -> ShowS # | |
Printable ModulePath Source # | Print a module path. |
printJS :: ModulePath -> Printer Source # |
mkModulePath :: ModuleName a -> ModulePath Source #
Construct the complete ModulePath from a ModuleName.
mkModulePaths :: ModuleName a -> [ModulePath] Source #
mkModulePathFromQName :: QName a -> ModulePath Source #
Converting a QName to a ModulePath is only relevant for constructors since they can conflict with module names.