haste-compiler-0.4.2: Haskell To ECMAScript compiler

Safe HaskellNone

Haste.App

Description

Type-safe client-server communication framework for Haste. This module re-exports most of the Haste module for convenience since some functions are exported by both Haste and Haste.App with different definitions. For simplicity, import one or the other, 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

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's arguments *must not* depend on any external IO, or the client and server computations may diverge. Ideally, calling runApp should be the first and only thing that happens in main.

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

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

getSessionID :: Server SessionIDSource

Returns the ID of the current session.

getActiveSessions :: Server SessionsSource

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.

data AppCfg Source

Instances

mkConfig :: String -> Int -> AppCfgSource

Create a default configuration from an URL 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 DoneSource

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

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

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.

type JSAny = Ptr AnySource

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

Javascript alert() function.

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

Javascript prompt() function.

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

Javascript eval() function.

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

Use console.log to write a message.

catJSStr :: JSString -> [JSString] -> JSStringSource

Concatenate a series of JSStrings using the specified separator.

class ClientCallback a Source

Bake a value of type a -> ... -> Client b into a -> ... -> IO b

Instances

data Event m a whereSource

These constructors correspond to their namesake DOM events. Mouse related callbacks receive the coordinates of the mouse pointer at the time the event was fired, relative to the top left corner of the element that fired the event. The click events also receive the mouse button that was pressed.

The key updownpress events receive the character code of the key that was pressed.

Constructors

OnLoad :: Event m (m ()) 
OnUnload :: Event m (m ()) 
OnChange :: Event m (m ()) 
OnFocus :: Event m (m ()) 
OnBlur :: Event m (m ()) 
OnMouseMove :: Event m ((Int, Int) -> m ()) 
OnMouseOver :: Event m ((Int, Int) -> m ()) 
OnMouseOut :: Event m (m ()) 
OnClick :: Event m (Int -> (Int, Int) -> m ()) 
OnDblClick :: Event m (Int -> (Int, Int) -> m ()) 
OnMouseDown :: Event m (Int -> (Int, Int) -> m ()) 
OnMouseUp :: Event m (Int -> (Int, Int) -> m ()) 
OnKeyPress :: Event m (Int -> m ()) 
OnKeyUp :: Event m (Int -> m ()) 
OnKeyDown :: Event m (Int -> m ()) 

Instances

Eq (Event m a) 
Ord (Event m a) 

onEvent :: ClientCallback a => Elem -> Event Client a -> a -> Client ()Source

Set a handler for a given event.

setTimeout :: Int -> Client () -> Client ()Source

Wrapper for window.setTimeout; execute the given computation after a delay given in milliseconds.

evtName :: IsString s => Event m a -> sSource

The name of a given event.

module Haste.DOM

class Random a whereSource

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 -> SeedSource

Generate the next seed in the sequence.

mkSeed :: Int -> SeedSource

Create a new seed from an integer.

newSeed :: MonadIO m => m SeedSource

Generate a new seed using Javascript's PRNG.

class JSNum a whereSource

(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 -> bSource

onHashChange :: (MonadIO m, GenericCallback (m ()) m, CB (m ()) ~ IO ()) => (String -> String -> m ()) -> 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, GenericCallback (m ()) m, CB (m ()) ~ IO ()) => (JSString -> JSString -> m ()) -> m ()Source

JSString version of onHashChange.

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

Set the hash part of the current URL.

getHash :: MonadIO m => m StringSource

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 JSStringSource

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