| Safe Haskell | None | 
|---|
Fay
Description
Main library entry point.
- module Fay.Config
 - 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
 
 - 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  CompileResult  = CompileResult {
- resOutput :: String
 - resImported :: [(String, FilePath)]
 - resSourceMappings :: Maybe [Mapping]
 
 - compileFile :: Config -> FilePath -> IO (Either CompileError String)
 - compileFileWithState :: Config -> FilePath -> IO (Either CompileError (String, Maybe [Mapping], CompileState))
 - compileFileWithResult :: Config -> FilePath -> IO (Either CompileError CompileResult)
 - compileFromTo :: Config -> FilePath -> Maybe FilePath -> IO ()
 - compileFromToAndGenerateHtml :: Config -> FilePath -> FilePath -> IO (Either CompileError String)
 - toJsName :: String -> String
 - showCompileError :: CompileError -> String
 - getConfigRuntime :: Config -> IO String
 - getRuntime :: IO String
 
Documentation
module Fay.Config
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 | 
data CompileState Source
State of the compiler.
Constructors
| CompileState | |
Fields 
  | |
Instances
data CompileResult Source
Constructors
| CompileResult | |
Fields 
  | |
Instances
compileFile :: Config -> FilePath -> IO (Either CompileError String)Source
Compile the given file.
compileFileWithState :: Config -> FilePath -> IO (Either CompileError (String, Maybe [Mapping], CompileState))Source
Compile a file returning the resulting internal state of the compiler. Don't use this directly, it's only exposed for the test suite.
compileFileWithResult :: Config -> FilePath -> IO (Either CompileError CompileResult)Source
Compile a file returning additional generated metadata.
compileFromTo :: Config -> FilePath -> Maybe FilePath -> IO ()Source
Compile the given file and write the output to the given path, or if nothing given, stdout.
compileFromToAndGenerateHtml :: Config -> FilePath -> FilePath -> IO (Either CompileError String)Source
Compile the given file and write to the output, also generates HTML and sourcemap files if configured.
showCompileError :: CompileError -> StringSource
Print a compile error for human consumption.
getConfigRuntime :: Config -> IO StringSource
Get the JS runtime source. This will return the user supplied runtime if it exists.
Get the default JS runtime source.