hplayground-0.1.0.3: a client-side haskell framework that compiles to javascript with the haste compiler

Safe HaskellNone

Haste.HPlay.View

Contents

Description

 

Synopsis

Documentation

widget combinators and modifiers

wcallback :: Widget a -> (a -> Widget b) -> Widget bSource

It is a callback in the view monad. The callback rendering substitutes the widget rendering when the latter is validated, without afecting the rendering of other widgets. This allow the simultaneous execution of different behaviours in different widgets in the same page.

(<+>) :: (Monad m, FormInput view) => View view m a -> View view m b -> View view m (Maybe a, Maybe b)Source

Join two widgets in the same page the resulting widget, when asked with it, return a 2 tuple of their validation results if both return Noting, the widget return Nothing (invalid).

it has a low infix priority: infixr 2

 r <- ask  widget1 <+>  widget2
 case r of (Just x, Nothing) -> ..

(**>) :: (Functor m, Monad m, FormInput view) => View view m a -> View view m b -> View view m bSource

The first elem result (even if it is not validated) is discarded, and the secod is returned . This contrast with the applicative operator *> which fails the whole validation if the validation of the first elem fails.

The first element is displayed however, as happens in the case of *> .

Here w's are widgets and r's are returned values

(w1 <* w2) will return Just r1 only if w1 and w2 are validated

(w1 <** w2) will return Just r1 even if w2 is not validated

it has a low infix priority: infixr 1

(<**) :: (Functor m, Monad m, FormInput view) => View view m a -> View view m b -> View view m aSource

The second elem result (even if it is not validated) is discarded, and the first is returned . This contrast with the applicative operator *> which fails the whole validation if the validation of the second elem fails. The second element is displayed however, as in the case of <*. see the <** examples

it has a low infix priority: infixr 1

validate :: (FormInput view, Monad m, Monad (View view m)) => View view m a -> (a -> WState view m (Maybe view)) -> View view m aSource

Validates a form or widget result against a validating procedure

getOdd= getInt Nothing validate (x -> return $ if mod x 2==0 then  Nothing else Just only odd numbers, please)

firstOf :: (FormInput view, Monad m, Functor m) => [View view m a] -> View view m aSource

Concat a list of widgets of the same type, return a the first validated result

manyOf :: (FormInput view, MonadIO m, Functor m) => [View view m a] -> View view m [a]Source

from a list of widgets, it return the validated ones.

allOf :: (Monad (View view m), Functor m, MonadIO m, FormInput view) => [View view m a] -> View view m [a]Source

like manyOf, but does not validate if one or more of the widgets does not validate

(<<<) :: (Monad m, Monoid view) => (view -> view) -> View view m a -> View view m aSource

Enclose Widgets within some formating. view is intended to be instantiated to a particular format

NOTE: It has a infix priority : infixr 5 less than the one of ++> and <++ of the operators, so use parentheses when appropriate, unless the we want to enclose all the widgets in the right side. Most of the type errors in the DSL are due to the low priority of this operator.

(<<) :: (t1 -> t) -> t1 -> tSource

A parameter application with lower priority than ($) and direct function application

(<++) :: (Monad m, Monoid v) => View v m a -> v -> View v m aSource

Append formatting code to a widget

 getString hi <++ H1 << hi there

It has a infix prority: infixr 6 higuer that <<< and most other operators

(++>) :: (Monad m, Monoid view) => view -> View view m a -> View view m aSource

Prepend formatting code to a widget

bold "enter name" ++ getString Nothing

It has a infix prority: infixr 6 higuer that <<< and most other operators

(<!) :: (Monad m, FormInput v) => View v m a -> Attribs -> View v m aSource

Add attributes to the topmost tag of a widget

it has a fixity infix 8

basic widgets

getString :: (StateType (View view m) ~ MFlowState, FormInput view, Monad (View view m), MonadIO m) => Maybe String -> View view m StringSource

Display a text box and return a non empty String

inputString :: (StateType (View view m) ~ MFlowState, FormInput view, Monad (View view m), MonadIO m) => Maybe String -> View view m StringSource

getInteger :: (StateType (View view m) ~ MFlowState, FormInput view, MonadIO m) => Maybe Integer -> View view m IntegerSource

Display a text box and return an Integer (if the value entered is not an Integer, fails the validation)

inputInteger :: (StateType (View view m) ~ MFlowState, FormInput view, MonadIO m) => Maybe Integer -> View view m IntegerSource

getInt :: (StateType (View view m) ~ MFlowState, FormInput view, MonadIO m) => Maybe Int -> View view m IntSource

Display a text box and return a Int (if the value entered is not an Int, fails the validation)

inputInt :: (StateType (View view m) ~ MFlowState, FormInput view, MonadIO m) => Maybe Int -> View view m IntSource

getPassword :: (FormInput view, StateType (View view m) ~ MFlowState, MonadIO m) => View view m StringSource

Display a password box

inputPassword :: (StateType (View view m) ~ MFlowState, FormInput view, MonadIO m) => View view m StringSource

setRadio :: (FormInput view, MonadIO m, Typeable a, Eq a, Show a) => a -> String -> View view m (Radio a)Source

Implement a radio button the parameter is the name of the radio group

setRadioActive :: (Eq a, Show a, Typeable a) => a -> String -> Widget (Radio a)Source

getRadio :: (Monad (View view m), Monad m, Functor m, FormInput view) => [String -> View view m (Radio a)] -> View view m aSource

encloses a set of Radio boxes. Return the option selected

setCheckBox :: (FormInput view, MonadIO m) => Bool -> String -> View view m CheckBoxesSource

Display a text box and return the value entered if it is readable( Otherwise, fail the validation)

getCheckBoxes :: (Monad m, FormInput view) => View view m CheckBoxes -> View view m [String]Source

getTextBox :: (FormInput view, StateType (View view m) ~ MFlowState, MonadIO m, Typeable a, Show a, Read a) => Maybe a -> View view m aSource

getMultilineText :: (FormInput view, MonadIO m) => String -> View view m StringSource

Display a multiline text box and return its content

textArea :: (FormInput view, MonadIO m) => String -> View view m StringSource

A synonim of getMultilineText

getBool :: (Monad (View view m), Functor m, MonadIO m, FormInput view) => Bool -> String -> String -> View view m BoolSource

getSelect :: (FormInput view, MonadIO m, Typeable a, Read a) => View view m (MFOption a) -> View view m aSource

Display a dropdown box with the options in the first parameter is optionally selected . It returns the selected option.

setOption :: (Monad m, Monad (View view m), Show a, Eq a, Typeable a, FormInput view) => a -> view -> View view m (MFOption a)Source

Set the option for getSelect. Options are concatenated with <|>

setSelectedOption :: (Monad m, Monad (View view m), Show a, Eq a, Typeable a, FormInput view) => a -> view -> View view m (MFOption a)Source

Set the selected option for getSelect. Options are concatenated with <|>

wlabel :: (Monad m, FormInput view) => view -> View view m a -> View view m aSource

resetButton :: (FormInput view, Monad m) => String -> View view m ()Source

inputReset :: (FormInput view, Monad m) => String -> View view m ()Source

submitButton :: (StateType (View view m) ~ MFlowState, FormInput view, MonadIO m) => String -> View view m StringSource

inputSubmit :: (StateType (View view m) ~ MFlowState, FormInput view, MonadIO m) => String -> View view m StringSource

wlink :: (Show a, Typeable a) => a -> Perch -> Widget aSource

noWidget :: (FormInput view, Monad m, Functor m) => View view m aSource

Empty widget that does not validate. May be used as "empty boxes" inside larger widgets.

It returns a non valid value.

stop :: (FormInput view, Monad m, Functor m) => View view m aSource

a sinonym of noWidget that can be used in a monadic expression in the View monad does not continue

wraw :: Monad m => view -> View view m ()Source

Render a Show-able value and return it wrender :: (Monad m, Functor m, Show a,Monad (View view m), FormInput view) => a -> View view m a wrender x = (fromStr $ show x) ++> return x

Render raw view formatting. It is useful for displaying information.

isEmpty :: Widget a -> Widget BoolSource

True if the widget has no valid input

out of flow updates

at :: ElemID -> UpdateMethod -> Widget a -> Widget aSource

run the widget as the content of the element with the given id. The content can be appended, prepended to the previous content or it can be the only content depending on the update method.

data UpdateMethod Source

Constructors

Append 
Prepend 
Insert 

Instances

Session data storage

getSessionData :: (StateType m ~ MFlowState, MonadState m, Typeable a) => m (Maybe a)Source

Get the session data of the desired type if there is any.

getSData :: Typeable a => Widget aSource

getSessionData specialized for the View monad. if Nothing, the monadic computation does not continue. getSData is a widget that does not validate when there is no data of that type in the session.

setSessionData :: (Typeable a, MonadState m, ~ * (StateType m) MFlowState) => a -> m ()Source

setSData :: (StateType m ~ MFlowState, MonadState m, Typeable a) => a -> m ()Source

a shorter name for setSessionData

delSessionData :: (Typeable a, MonadState m, ~ * (StateType m) MFlowState) => a -> m ()Source

delSData :: (StateType m ~ MFlowState, MonadState m, Typeable a) => a -> m ()Source

reactive and events

data EventData Source

Constructors

EventData 

Fields

evName :: String
 
evData :: EvData
 

Instances

data EvData Source

Constructors

NoData 
Click Int (Int, Int) 
Mouse (Int, Int) 
Key Int 

Instances

pass :: Perch -> Event IO b -> Widget EventDataSource

pass trough only if the event is fired in this DOM element. Otherwise, if the code is executing from a previous event, the computation will stop

continueIf :: Bool -> a -> Widget aSource

return empty and the monadic computation stop if the condition is false. If true, return the second parameter.

wtimeout :: Int -> Widget () -> Widget ()Source

executes a widget each t milliseconds until it validates and return ()

data Event m a where

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) 

running it

runBody :: Widget a -> IO (Maybe a)Source

run the widget as the body of the HTML

Perch is reexported

low level and internals

getNextId :: (StateType m ~ MFlowState, MonadState m) => m StringSource

get the next ideitifier that will be created by genNewId

genNewId :: (StateType m ~ MFlowState, MonadState m) => m StringSource

Generate a new string. Useful for creating tag identifiers and other attributes.

if the page is refreshed, the identifiers generated are the same.

getParam :: (FormInput view, StateType (View view m) ~ MFlowState, MonadIO m, Typeable a, Show a, Read a) => Maybe String -> String -> Maybe a -> View view m aSource

class (Monoid view, Typeable view) => FormInput view whereSource

Minimal interface for defining the basic form and link elements. The core of MFlow is agnostic about the rendering package used. Every formatting (either HTML or not) used with MFlow must have an instance of this class. See MFlow.Forms.Blaze.Html for the instance for blaze-html MFlow.Forms.XHtml for the instance for Text.XHtml and MFlow.Forms.HSP for the instance for Haskell Server Pages.

Methods

fromStr :: String -> viewSource

fromStrNoEncode :: String -> viewSource

ftag :: String -> view -> viewSource

inred :: view -> viewSource

flink :: String -> view -> viewSource

flink1 :: String -> viewSource

finput :: Name -> Type -> Value -> Checked -> OnClick -> viewSource

ftextarea :: String -> String -> viewSource

fselect :: String -> view -> viewSource

foption :: String -> view -> Bool -> viewSource

foption1 :: String -> Bool -> viewSource

formAction :: String -> String -> view -> viewSource

attrs :: view -> Attribs -> viewSource

Instances

newtype View v m a Source

Constructors

View 

Fields

runView :: WState v m (FormElm v a)
 

Instances

Attributable (Widget a) 
Monoid view => MonadTrans (View view) 
Monad (View Perch IO) 
(Monad m, Functor m) => Functor (View view m) 
(Monoid view, Functor m, Monad m) => Applicative (View view m) 
(Monoid view, Functor m, Monad m) => Alternative (View view m) 
(FormInput view, Monad (View view m), MonadIO m) => MonadIO (View view m) 
(FormInput view, Monad m, Monad (View view m)) => MonadState (View view m) 
(FormInput v, Monad (View v m), Monad m, Functor m, Monoid a) => Monoid (View v m a) 

data FormElm view a Source

Constructors

FormElm view (Maybe a) 

Instances

Functor (FormElm view) 
Monoid view => Monoid (FormElm view a)