Safe Haskell | None |
---|---|
Language | Haskell2010 |
Main library entry point.
Synopsis
- 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
- toTsName :: String -> String
- showCompileError :: CompileError -> String
- readConfigRuntime :: Config -> IO String
Documentation
module Fay.Config
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 # | |
Defined in Fay.Types.CompileError showsPrec :: Int -> CompileError -> ShowS # show :: CompileError -> String # showList :: [CompileError] -> ShowS # | |
MonadError CompileError Compile Source # | |
Defined in Fay.Types throwError :: CompileError -> Compile a # catchError :: Compile a -> (CompileError -> Compile a) -> Compile a # |
data CompileState Source #
State of the compiler.
CompileState | |
|
Instances
Show CompileState Source # | |
Defined in Fay.Types showsPrec :: Int -> CompileState -> ShowS # show :: CompileState -> String # showList :: [CompileState] -> ShowS # | |
MonadState CompileState Compile Source # | |
Defined in Fay.Types get :: Compile CompileState # put :: CompileState -> Compile () # state :: (CompileState -> (a, CompileState)) -> Compile a # |
data CompileResult Source #
CompileResult | |
|
Instances
Show CompileResult Source # | |
Defined in Fay.Types.CompileResult showsPrec :: Int -> CompileResult -> ShowS # show :: CompileResult -> String # showList :: [CompileResult] -> ShowS # |
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 -> String Source #
Print a compile error for human consumption.