haste-compiler-0.5.0.1: Haskell To ECMAScript compiler

Safe HaskellNone
LanguageHaskell98

Haste.Foreign

Description

High level interface for interfacing with JavaScript.

Synopsis

Documentation

class ToAny a where Source

Any type that can be converted into a JavaScript value.

Minimal complete definition

Nothing

Methods

toAny :: a -> JSAny Source

Build a JS object from a Haskell value. The default instance creates an object from any type that derives Generic according to the following rules: * Records turn into plain JS objects, with record names as field names. * Non-record product types turn into objects containing a $data field which contains all of the constructor's unnamed fields. * Values of enum types turn into strings matching their constructors. * Non-enum types with more than one constructor gain an extra field, $tag, which contains the name of the constructor used to create the object.

listToAny :: [a] -> JSAny Source

Instances

ToAny Bool 
ToAny Char 
ToAny Double 
ToAny Float 
ToAny Int 
ToAny Int8 
ToAny Int16 
ToAny Int32 
ToAny Word 
ToAny Word8 
ToAny Word16 
ToAny Word32 
ToAny () 
ToAny JSString 
ToAny JSAny 
ToAny Elem 
ToAny Blob 
ToAny BlobData 
ToAny FrameRequest 
ToAny Canvas 
ToAny Ctx 
ToAny Bitmap 
ToAny WebSocket 
ToAny a => ToAny [a]

Lists are marshalled into arrays, with the exception of String.

ToAny a => ToAny (IO a) 
ToAny (Ptr a) 
ToAny a => ToAny (Maybe a)

Maybe is simply a nullable type. Nothing is equivalent to null, and any non-null value is equivalent to x in Just x.

ToAny (Opaque a) 
(FromAny a, JSFunc b) => ToAny (a -> b) 
(ToAny a, ToAny b) => ToAny (a, b)

Tuples are marshalled into arrays.

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

class FromAny a where Source

Any type that can be converted from a JavaScript value.

Minimal complete definition

fromAny

Methods

fromAny :: JSAny -> IO a Source

Convert a value from JS with a reasonable conversion if an exact match is not possible. Examples of reasonable conversions would be truncating floating point numbers to integers, or turning signed integers into unsigned.

listFromAny :: JSAny -> IO [a] Source

class Generic a

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Minimal complete definition

from, to

Instances

Generic Bool 
Generic Char 
Generic Double 
Generic Float 
Generic Int 
Generic Ordering 
Generic () 
Generic All 
Generic Any 
Generic Arity 
Generic Fixity 
Generic Associativity 
Generic [a] 
Generic (U1 p) 
Generic (Par1 p) 
Generic (Maybe a) 
Generic (ZipList a) 
Generic (Dual a) 
Generic (Endo a) 
Generic (Sum a) 
Generic (Product a) 
Generic (First a) 
Generic (Last a) 
Generic (Either a b) 
Generic (Rec1 f p) 
Generic (a, b) 
Generic (Const a b) 
Generic (WrappedMonad m a) 
Generic (Proxy * t) 
Generic (K1 i c p) 
Generic ((:+:) f g p) 
Generic ((:*:) f g p) 
Generic ((:.:) f g p) 
Generic (a, b, c) 
Generic (WrappedArrow a b c) 
Generic (M1 i c f p) 
Generic (a, b, c, d) 
Generic (a, b, c, d, e) 
Generic (a, b, c, d, e, f) 
Generic (a, b, c, d, e, f, g) 

newtype JSAny Source

Any JS value, with one layer of indirection.

Constructors

JSAny (Ptr Any) 

data Opaque a Source

The Opaque type is inhabited by values that can be passed to JavaScript using their raw Haskell representation. Opaque values are completely useless to JS code, and should not be inspected. This is useful for, for instance, storing data in some JS-native data structure for later retrieval.

Instances

nullValue :: JSAny Source

The JS value null.

toObject :: [(JSString, JSAny)] -> JSAny Source

Build a new JS object from a list of key:value pairs.

has :: JSAny -> JSString -> IO Bool Source

Check if a JS object has a particular member.

get :: FromAny a => JSAny -> JSString -> IO a Source

Read a member from a JS object. Throws an error if the member can not be marshalled into a value of type a.

index :: FromAny a => JSAny -> Int -> IO a Source

Read an element from a JS array. Throws an error if the member can not be marshalled into a value of type a.

class FFI a Source

Any type that can be imported from JavaScript. This means any type which has an instance of FromAny, and any function where all argument types has ToAny instances and the return type is in the IO monad and has a FromAny instance.

Instances

FromAny a => FFI (IO a) 
(ToAny a, FFI b) => FFI (a -> b) 

class JSFunc a Source

Minimal complete definition

mkJSFunc, arity

Instances

(ToAny a, (~) * (JS a) JSAny) => JSFunc a 
ToAny a => JSFunc (IO a) 
(FromAny a, JSFunc b) => JSFunc (a -> b) 

ffi :: FFI a => JSString -> a Source

Creates a Haskell function from the given string of JavaScript code. If this code is not well typed or is otherwise incorrect, your program may crash or misbehave in mystifying ways. Haste makes a best-effort try to save you from poorly typed JS here, but there are no guarantees.

For instance, the following WILL cause crazy behavior due to wrong types: ffi "(function(x) {return x+1;})" :: Int -> Int -> IO Int

In other words, this function is as unsafe as the JS it calls on. You have been warned.

The imported JS is evaluated lazily, unless (a) it is a function object in which case evaluation order does not affect the semantics of the imported code, or if (b) the imported code is explicitly marked as strict:

someFunction = ffi "__strict(someJSFunction)"

Literals which depends on some third party initialization, the existence of a DOM tree or some other condition which is not fulfilled at load time should *not* be marked strict.

constant :: FromAny a => JSString -> a Source

Create a Haskell value from a constant JS expression.

export :: ToAny a => JSString -> a -> IO () Source

Export a symbol. That symbol may then be accessed from JavaScript through Haste.name() as a normal function. Remember, however, that if you are using --with-js to include your JS, in conjunction with --opt-minify or any option that implies it, you will instead need to access your exports through Haste['name'](), or Closure will mangle your function names.