haste-compiler-0.5.0: Haskell To ECMAScript compiler

Safe HaskellNone
LanguageHaskell98

Haste.App

Description

Type-safe client-server communication framework for Haste.

In addition to the Haste.App extras, this module exports the same API as Haste, modified slightly to work better with the automatic program slicing Haste.App provides. This means that you should import either this module *or* Haste, but *not* both.

Synopsis

Documentation

class Monad m => MonadIO m where

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Methods

liftIO :: IO a -> m a

Lift a computation from the IO monad.

class Remotable a Source

An exportable function is of the type (Serialize a, ..., Serialize result) => a -> ... -> IO result

Minimal complete definition

serializify

Instances

Binary a => Remotable (Server a) 
(Binary a, Remotable b) => Remotable (a -> b) 

data App a Source

Application monad; allows for exporting functions, limited liftIO, forkIO and launching the client.

data Server a Source

Server monad for Haste.App. Allows redeeming remote values, lifting IO actions, and not much more.

data Remote a Source

liftServerIO :: IO a -> App (Server a) Source

Lift an IO action into the Server monad, the result of which can only be used server-side.

forkServerIO :: Server () -> App (Server ThreadId) Source

Fork off a Server computation not bound an API call. This may be useful for any tasks that will keep running for as long as the server is running.

Calling getSessionID inside this computation will return 0, which will never be generated for an actual session. getActiveSessions works as expected.

remote :: Remotable a => a -> App (Remote a) Source

Make a function available to the client as an API call.

runApp :: AppCfg -> App Done -> IO () Source

Run a Haste.App application. runApp never returns before the program terminates.

Note that runApp is single-entry, and that its argument must not depend on any external IO. It is *strongly* recommended that the main function of any Haste.App program *only* consists of a single call to runApp.

(<.>) :: Binary a => Remote (a -> b) -> a -> Remote b Source

Apply an exported function to an argument. TODO: look into making this Applicative.

getSessionID :: Server SessionID Source

Returns the ID of the current session.

getActiveSessions :: Server Sessions Source

Return all currently active sessions.

onSessionEnd :: (SessionID -> Server ()) -> App () Source

Register a handler to be run whenever a session terminates. Several handlers can be registered at the same time; they will be run in the order they were registered.

mkConfig :: String -> Int -> AppCfg Source

Create a default configuration from a host name and a port number.

data Client a Source

A client-side computation. See it as Haste.App's version of the IO monad.

runClient :: Client () -> App Done Source

Launch a client from a Server computation. runClient never returns before the program terminates.

onServer :: Binary a => Remote (Server a) -> Client a Source

Perform a server-side computation, blocking the client thread until said computation returns.

liftIO :: MonadIO m => forall a. IO a -> m a

Lift a computation from the IO monad.

data JSString Source

JSStrings are represented as normal strings server-side; should probably be changed to ByteString or Text.

data JSAny Source

Any JS value, with one layer of indirection.

alert :: MonadIO m => String -> m () Source

Javascript alert() function.

prompt :: MonadIO m => String -> m String Source

Javascript prompt() function.

eval :: MonadIO m => JSString -> m JSString Source

Javascript eval() function.

writeLog :: MonadIO m => String -> m () Source

Use console.log to write a message.

catJSStr :: JSString -> [JSString] -> JSString Source

Concatenate a series of JSStrings using the specified separator.

newtype Elem Source

A DOM node.

Constructors

Elem JSAny 

class IsElem a where Source

The class of types backed by DOM elements.

Minimal complete definition

elemOf

Methods

elemOf :: a -> Elem Source

Get the element representing the object.

fromElem :: Elem -> IO (Maybe a) Source

Attempt to create an object from an Elem.

data Attribute Source

A key/value pair representing the value of an attribute. May represent a property, an HTML attribute, a style attribute or a list of child elements.

data AttrName Source

The name of an attribute. May be either a common property, an HTML attribute or a style attribute.

Instances

set :: (IsElem e, MonadIO m) => e -> [Attribute] -> m () Source

Set a number of Attributes on an element.

with :: (IsElem e, MonadIO m) => m e -> [Attribute] -> m e Source

Set a number of Attributes on the element produced by an IO action. Gives more convenient syntax when creating elements:

newElem "div" with [ style "border" =: "1px solid black", ... ]

children :: [Elem] -> Attribute Source

Attribute adding a list of child nodes to an element.

click :: (IsElem e, MonadIO m) => e -> m () Source

Generate a click event on an element.

focus :: (IsElem e, MonadIO m) => e -> m () Source

Generate a focus event on an element.

blur :: (IsElem e, MonadIO m) => e -> m () Source

Generate a blur event on an element.

document :: Elem Source

The DOM node corresponding to document.

documentBody :: Elem Source

The DOM node corresponding to document.body.

deleteChild :: (IsElem parent, IsElem child, MonadIO m) => parent -> child -> m () Source

Remove the second element from the first's children.

clearChildren :: (IsElem e, MonadIO m) => e -> m () Source

Remove all children from the given element.

setChildren :: (IsElem parent, IsElem child, MonadIO m) => parent -> [child] -> m () Source

Clear the given element's list of children, and append all given children to it.

getChildren :: (IsElem e, MonadIO m) => e -> m [Elem] Source

Get a list of all children belonging to a certain element.

getLastChild :: (IsElem e, MonadIO m) => e -> m (Maybe Elem) Source

Get the last of an element's children.

getFirstChild :: (IsElem e, MonadIO m) => e -> m (Maybe Elem) Source

Get the first of an element's children.

getChildBefore :: (IsElem e, MonadIO m) => e -> m (Maybe Elem) Source

Get the sibling before the given one, if any.

insertChildBefore :: (IsElem parent, IsElem before, IsElem child, MonadIO m) => parent -> before -> child -> m () Source

Insert an element into a container, before another element. For instance: insertChildBefore theContainer olderChild childToAdd

appendChild :: (IsElem parent, IsElem child, MonadIO m) => parent -> child -> m () Source

Append the first element as a child of the second element.

removeChild :: (IsElem parent, IsElem child, MonadIO m) => child -> parent -> m () Source

Deprecated: Use deleteChild instead

DEPRECATED: use deleteChild instead!

addChild :: (IsElem parent, IsElem child, MonadIO m) => child -> parent -> m () Source

Deprecated: Use appendChild instead

DEPRECATED: use appendChild instead!

addChildBefore :: (IsElem parent, IsElem child, MonadIO m) => child -> parent -> child -> m () Source

Deprecated: Use insertChildBefore instead

DEPRECATED: use insertChildBefore instead!

class Random a where Source

Minimal complete definition

randomR

Methods

randomR :: (a, a) -> Seed -> (a, Seed) Source

Generate a pseudo random number between a lower (inclusive) and higher (exclusive) bound.

randomRs :: (a, a) -> Seed -> [a] Source

next :: Seed -> Seed Source

Generate the next seed in the sequence.

mkSeed :: Int -> Seed Source

Create a new seed from an integer.

newSeed :: MonadIO m => m Seed Source

Generate a new seed using Javascript's PRNG.

class JSNum a where Source

(Almost) all numeric types can be efficiently converted to and from Double, which is the internal representation for most of them.

convert :: (JSNum a, JSNum b) => a -> b Source

onHashChange :: MonadIO m => (String -> String -> IO ()) -> m () Source

Register a callback to be run whenever the URL hash changes. The two arguments of the callback are the new and old hash respectively.

onHashChange' :: MonadIO m => (JSString -> JSString -> IO ()) -> m () Source

JSString version of onHashChange.

setHash :: MonadIO m => String -> m () Source

Set the hash part of the current URL.

getHash :: MonadIO m => m String Source

Read the hash part of the currunt URL.

setHash' :: MonadIO m => JSString -> m () Source

Set the hash part of the current URL - JSString version.

getHash' :: MonadIO m => m JSString Source

Read the hash part of the currunt URL - JSString version.