fay-0.24.1.0: A compiler for Fay, a Haskell subset that compiles to JavaScript.
Safe HaskellNone
LanguageHaskell98

Fay.Types

Description

All Fay types and instances.

Synopsis

Documentation

data JsStmt Source #

Statement type.

Instances

Instances details
Eq JsStmt Source # 
Instance details

Defined in Fay.Types.Js

Methods

(==) :: JsStmt -> JsStmt -> Bool #

(/=) :: JsStmt -> JsStmt -> Bool #

Show JsStmt Source # 
Instance details

Defined in Fay.Types.Js

Printable JsStmt Source #

Print a single statement.

Instance details

Defined in Fay.Compiler.Print

data JsLit Source #

Literal value type.

Instances

Instances details
Eq JsLit Source # 
Instance details

Defined in Fay.Types.Js

Methods

(==) :: JsLit -> JsLit -> Bool #

(/=) :: JsLit -> JsLit -> Bool #

Show JsLit Source # 
Instance details

Defined in Fay.Types.Js

Methods

showsPrec :: Int -> JsLit -> ShowS #

show :: JsLit -> String #

showList :: [JsLit] -> ShowS #

IsString JsLit Source #

Just handy to have.

Instance details

Defined in Fay.Types.Js

Methods

fromString :: String -> JsLit #

Printable JsLit Source #

Print literals.

Instance details

Defined in Fay.Compiler.Print

data JsName Source #

A name of some kind.

Instances

Instances details
Eq JsName Source # 
Instance details

Defined in Fay.Types.Js

Methods

(==) :: JsName -> JsName -> Bool #

(/=) :: JsName -> JsName -> Bool #

Show JsName Source # 
Instance details

Defined in Fay.Types.Js

Printable JsName Source #

Print one of the kinds of names.

Instance details

Defined in Fay.Compiler.Print

newtype Compile a Source #

Compile monad.

Constructors

Compile 

Fields

Instances

Instances details
Monad Compile Source # 
Instance details

Defined in Fay.Types

Methods

(>>=) :: Compile a -> (a -> Compile b) -> Compile b #

(>>) :: Compile a -> Compile b -> Compile b #

return :: a -> Compile a #

Functor Compile Source # 
Instance details

Defined in Fay.Types

Methods

fmap :: (a -> b) -> Compile a -> Compile b #

(<$) :: a -> Compile b -> Compile a #

Applicative Compile Source # 
Instance details

Defined in Fay.Types

Methods

pure :: a -> Compile a #

(<*>) :: Compile (a -> b) -> Compile a -> Compile b #

liftA2 :: (a -> b -> c) -> Compile a -> Compile b -> Compile c #

(*>) :: Compile a -> Compile b -> Compile b #

(<*) :: Compile a -> Compile b -> Compile a #

MonadIO Compile Source # 
Instance details

Defined in Fay.Types

Methods

liftIO :: IO a -> Compile a #

MonadWriter CompileWriter Compile Source # 
Instance details

Defined in Fay.Types

MonadState CompileState Compile Source # 
Instance details

Defined in Fay.Types

MonadReader CompileReader Compile Source # 
Instance details

Defined in Fay.Types

MonadError CompileError Compile Source # 
Instance details

Defined in Fay.Types

class Printable a where Source #

Print some value.

Methods

printJS :: a -> Printer Source #

Instances

Instances details
Printable ModulePath Source #

Print a module path.

Instance details

Defined in Fay.Compiler.Print

Printable JsLit Source #

Print literals.

Instance details

Defined in Fay.Compiler.Print

Printable JsName Source #

Print one of the kinds of names.

Instance details

Defined in Fay.Compiler.Print

Printable JsExp Source #

Print an expression.

Instance details

Defined in Fay.Compiler.Print

Printable JsStmt Source #

Print a single statement.

Instance details

Defined in Fay.Compiler.Print

Printable (ModuleName l) Source #

Print module name.

Instance details

Defined in Fay.Compiler.Print

Methods

printJS :: ModuleName l -> Printer Source #

Printable (Name l) Source #

Print (and properly encode) a name.

Instance details

Defined in Fay.Compiler.Print

Methods

printJS :: Name l -> Printer Source #

Printable (QName l) Source #

Print (and properly encode to JS) a qualified name.

Instance details

Defined in Fay.Compiler.Print

Methods

printJS :: QName l -> Printer Source #

Printable (SpecialCon l) Source #

Print special constructors (tuples, list, etc.)

Instance details

Defined in Fay.Compiler.Print

Methods

printJS :: SpecialCon l -> Printer Source #

data Fay a Source #

The JavaScript FFI interfacing monad.

Instances

Instances details
Monad Fay Source # 
Instance details

Defined in Fay.Types

Methods

(>>=) :: Fay a -> (a -> Fay b) -> Fay b #

(>>) :: Fay a -> Fay b -> Fay b #

return :: a -> Fay a #

Functor Fay Source # 
Instance details

Defined in Fay.Types

Methods

fmap :: (a -> b) -> Fay a -> Fay b #

(<$) :: a -> Fay b -> Fay a #

Applicative Fay Source # 
Instance details

Defined in Fay.Types

Methods

pure :: a -> Fay a #

(<*>) :: Fay (a -> b) -> Fay a -> Fay b #

liftA2 :: (a -> b -> c) -> Fay a -> Fay b -> Fay c #

(*>) :: Fay a -> Fay b -> Fay b #

(<*) :: Fay a -> Fay b -> Fay a #

data CompileReader Source #

Configuration and globals for the compiler.

Constructors

CompileReader 

Fields

Instances

Instances details
MonadReader CompileReader Compile Source # 
Instance details

Defined in Fay.Types

data CompileResult Source #

Constructors

CompileResult 

Instances

Instances details
Show CompileResult Source # 
Instance details

Defined in Fay.Types.CompileResult

data CompileWriter Source #

Things written out by the compiler.

Constructors

CompileWriter 

Fields

Instances

Instances details
Show CompileWriter Source # 
Instance details

Defined in Fay.Types

Semigroup CompileWriter Source #

Simple concatenating instance.

Instance details

Defined in Fay.Types

Monoid CompileWriter Source #

Simple concatenating instance.

Instance details

Defined in Fay.Types

MonadWriter CompileWriter Compile Source # 
Instance details

Defined in Fay.Types

data Config Source #

Configuration of the compiler. The fields with a leading underscore

Instances

Instances details
Show Config Source # 
Instance details

Defined in Fay.Config

Default Config Source #

Default configuration.

Instance details

Defined in Fay.Config

Methods

def :: Config

data CompileState Source #

State of the compiler.

Constructors

CompileState 

Fields

Instances

Instances details
Show CompileState Source # 
Instance details

Defined in Fay.Types

MonadState CompileState Compile Source # 
Instance details

Defined in Fay.Types

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

Instances details
Show FundamentalType Source # 
Instance details

Defined in Fay.Types.FFI

data PrintState Source #

The state of the pretty printer.

Constructors

PrintState 

Fields

data PrintReader Source #

Global options of the printer

Constructors

PrintReader 

Fields

defaultPrintReader :: PrintReader Source #

default printer options (non-pretty printing)

data PrintWriter Source #

Output of printer

Constructors

PrintWriter 

Fields

Instances

Instances details
Semigroup PrintWriter Source # 
Instance details

Defined in Fay.Types.Printer

Monoid PrintWriter Source #

Output concatenation

Instance details

Defined in Fay.Types.Printer

newtype Printer Source #

The printer.

Instances

Instances details
IsString Printer Source #

Write out a string, updating the current position information.

Instance details

Defined in Fay.Types.Printer

Methods

fromString :: String -> Printer #

Semigroup Printer Source # 
Instance details

Defined in Fay.Types.Printer

Monoid Printer Source # 
Instance details

Defined in Fay.Types.Printer

indented :: Printer -> Printer Source #

Print the given printer indented.

askIf :: (PrintReader -> Bool) -> Printer -> Printer -> Printer Source #

exec one of Printers depending on PrintReader property.

newline :: Printer Source #

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.

data ModulePath Source #

The name of a module split into a list for code generation.

Instances

Instances details
Eq ModulePath Source # 
Instance details

Defined in Fay.Types.ModulePath

Ord ModulePath Source # 
Instance details

Defined in Fay.Types.ModulePath

Show ModulePath Source # 
Instance details

Defined in Fay.Types.ModulePath

Printable ModulePath Source #

Print a module path.

Instance details

Defined in Fay.Compiler.Print

mkModulePath :: ModuleName a -> ModulePath Source #

Construct the complete ModulePath from a ModuleName.

mkModulePaths :: ModuleName a -> [ModulePath] Source #

Construct intermediate module paths from a ModuleName. mkModulePaths A.B => [[A], [A,B]]

mkModulePathFromQName :: QName a -> ModulePath Source #

Converting a QName to a ModulePath is only relevant for constructors since they can conflict with module names.