sunroof-compiler-0.2: Monadic Javascript Compiler

Safe HaskellNone

Language.Sunroof.Classes

Description

Provides the central type classes used by Sunroof.

Synopsis

Documentation

class Sunroof a whereSource

Central type class of Sunroof. Every type that can be translated into Javascript with Sunroof has to implement this type class.

Methods

box :: Expr -> aSource

Create a Sunroof value from a plain Javascript expression.

unbox :: a -> ExprSource

Reveal the plain Javascript expression that represents this Sunroof value.

typeOf :: Proxy a -> TypeSource

Returns the type of Javascript expression this Sunroof value represents. The default implementation returns Base as type.

Instances

Sunroof ()

Unit is a Sunroof value. It can be viewed as a representation of null or void.

Sunroof JSBool 
Sunroof JSObject 
Sunroof JSNumber

First-class values in Javascript.

Sunroof JSString

First-class Javascript value.

Sunroof JSConsole

First-class values in Javascript.

Sunroof JSDate

First-class values in Javascript.

Sunroof JSCanvas

First-class values in Javascript.

SunroofArgument a => Sunroof (JSContinuation a)

Functions are first-class citizens of Javascript. Therefore they are Sunroof values.

Sunroof a => Sunroof (JSRef a) 
Sunroof a => Sunroof (JSArray a)

Arrays are first-class Javascript values.

SunroofArgument o0 => Sunroof (JSChan o0) 
SunroofArgument o0 => Sunroof (JSMVar o0) 
(SunroofArgument a, Sunroof r) => Sunroof (JSFunction a r)

Functions are first-class citizens of Javascript. Therefore they are Sunroof values.

(SunroofKey k, Sunroof a) => Sunroof (JSMap k a) 

class SunroofValue a whereSource

All Haskell values that have a Sunroof representation implement this class.

Associated Types

type ValueOf a :: *Source

The Sunroot type that is equivalent to the implementing Haskell type.

Methods

js :: a -> ValueOf aSource

Convert the Haskell value to its Sunroof equivalent.

Instances

SunroofValue Bool 
SunroofValue Char

Create a single character JSString from a Char.

SunroofValue Double 
SunroofValue Float 
SunroofValue Int 
SunroofValue Integer 
SunroofValue ()

Unit is unit.

SunroofValue [Char]

Create a JSString from a String.

Integral a => SunroofValue (Ratio a) 
SunroofArgument a => SunroofValue (a -> JS B ())

JSFunctions may be created from Haskell functions if they have the right form.

(SunroofArgument a, Sunroof b) => SunroofValue (a -> JS A b)

JSFunctions may be created from Haskell functions if they have the right form.

class SunroofArgument args whereSource

Everything that can be used as argument to a function is Javascript/Sunroof.

Methods

jsArgs :: args -> [Expr]Source

Turn the argument into a list of expressions.

jsValue :: UniqM m => m argsSource

Create a list of fresh variables for the arguments.

typesOf :: Proxy args -> [Type]Source

Get the type of the argument values.

Instances

SunroofArgument ()

Unit is the empty argument list.

Sunroof a => SunroofArgument a

Every Sunroof value can be an argument to a function.

(Sunroof a, Sunroof b) => SunroofArgument (a, b)

Two arguments.

(Sunroof a, Sunroof b, Sunroof c) => SunroofArgument (a, b, c)

Three arguments.

(Sunroof a, Sunroof b, Sunroof c, Sunroof d) => SunroofArgument (a, b, c, d)

Four arguments.

(Sunroof a, Sunroof b, Sunroof c, Sunroof d, Sunroof e) => SunroofArgument (a, b, c, d, e)

Five arguments.

(Sunroof a, Sunroof b, Sunroof c, Sunroof d, Sunroof e, Sunroof f) => SunroofArgument (a, b, c, d, e, f)

Six arguments.

(Sunroof a, Sunroof b, Sunroof c, Sunroof d, Sunroof e, Sunroof f, Sunroof g) => SunroofArgument (a, b, c, d, e, f, g)

Seven arguments.

(Sunroof a, Sunroof b, Sunroof c, Sunroof d, Sunroof e, Sunroof f, Sunroof g, Sunroof h) => SunroofArgument (a, b, c, d, e, f, g, h)

Eight arguments.

(Sunroof a, Sunroof b, Sunroof c, Sunroof d, Sunroof e, Sunroof f, Sunroof g, Sunroof h, Sunroof i) => SunroofArgument (a, b, c, d, e, f, g, h, i)

Nine arguments.

class Monad m => UniqM m whereSource

Implemented if a monad supports unique number generation.

Methods

uniqM :: m UniqSource

Generate a unique number.

type Uniq = IntSource

Used for unique number generation.

mkVar :: Sunroof a => Uniq -> aSource

Creates a Javascript variable of any Sunroof type.

jsVar :: (Sunroof a, UniqM m) => m aSource

Create a unique Javascript variable of any Sunroof type.