Safe Haskell | None |
---|---|
Language | Haskell2010 |
- newtype Widget a = Widget {}
- module Transient.Move.Utils
- runBody :: Widget a -> IO (Maybe a)
- addHeader :: Perch -> IO ()
- render :: Widget a -> TransIO a
- (<<) :: (Perch -> Perch) -> Perch -> Perch
- (<<<) :: (Perch -> Perch) -> Widget a -> Widget a
- (<!) :: Widget a -> [(PropId, JSString)] -> Widget a
- (<++) :: Widget a -> Perch -> Widget a
- (++>) :: Perch -> Widget a -> Widget a
- validate :: Widget a -> (a -> StateIO (Maybe Perch)) -> Widget a
- wcallback :: Widget a -> (a -> Widget b) -> Widget b
- redraw :: JSString -> Widget a -> TransIO a
- option :: (Typeable b, Show b) => b -> String -> Widget b
- wprint :: ToElem a => a -> Widget ()
- getString :: Maybe String -> Widget String
- inputString :: Maybe String -> Widget String
- getInteger :: Maybe Integer -> Widget Integer
- inputInteger :: Maybe Integer -> Widget Integer
- getInt :: Maybe Int -> Widget Int
- inputInt :: Maybe Int -> Widget Int
- inputFloat :: Maybe Float -> Widget Float
- inputDouble :: Maybe Double -> Widget Double
- getPassword :: Widget String
- inputPassword :: Widget String
- setRadio :: (Typeable a, Eq a, Show a, Read a) => Bool -> a -> Widget (Radio a)
- setRadioActive :: (Typeable a, Eq a, Show a, Read a) => Bool -> a -> Widget (Radio a)
- getRadio :: [Widget (Radio a)] -> Widget a
- setCheckBox :: (Typeable a, Show a) => Bool -> a -> Widget (CheckBoxes a)
- getCheckBoxes :: Show a => Widget (CheckBoxes a) -> Widget [a]
- getTextBox :: (Typeable a, Show a, Read a) => Maybe a -> Widget a
- getMultilineText :: JSString -> Widget String
- textArea :: JSString -> Widget String
- getBool :: Bool -> String -> String -> Widget Bool
- getSelect :: (Typeable a, Read a, Show a) => Widget (MFOption a) -> Widget a
- setOption :: (Show a, Eq a, Typeable a) => a -> Perch -> Widget (MFOption a)
- setSelectedOption :: (Show a, Eq a, Typeable a) => a -> Perch -> Widget (MFOption a)
- wlabel :: Perch -> Widget a -> Widget a
- resetButton :: JSString -> Widget ()
- inputReset :: JSString -> Widget ()
- submitButton :: (Read a, Show a, Typeable a) => a -> Widget a
- inputSubmit :: (Read a, Show a, Typeable a) => a -> Widget a
- wbutton :: a -> JSString -> Widget a
- wlink :: (Show a, Typeable a) => a -> Perch -> Widget a
- tlink :: (Show a, Typeable a) => a -> Perch -> Widget a
- staticNav :: TransIO b -> TransIO b
- noWidget :: Widget a
- wraw :: Perch -> Widget ()
- rawHtml :: Perch -> Widget ()
- isEmpty :: Widget a -> Widget Bool
- data BrowserEvent
- data UpdateMethod
- at :: JSString -> UpdateMethod -> Widget a -> Widget a
- at' :: JSString -> UpdateMethod -> Cloud a -> Cloud a
- class Typeable a => IsEvent a where
- data EventData = EventData {}
- data EvData
- resetEventData :: Widget ()
- getEventData :: Widget EventData
- setEventData :: EventData -> Widget ()
- raiseEvent :: IsEvent event => Widget a -> event -> Widget a
- fire :: IsEvent event => Widget a -> event -> Widget a
- wake :: IsEvent event => Widget a -> event -> Widget a
- pass :: IsEvent event => Perch -> event -> Widget EventData
- type ElemID = JSString
- getNextId :: MonadState EventF m => m JSString
- genNewId :: (MonadState EventF m, MonadIO m) => m JSString
- continuePerch :: Widget a -> ElemID -> Widget a
- getParam :: (Typeable a, Show a, Read a) => Maybe JSString -> JSString -> Maybe a -> Widget a
- getCont :: TransIO EventF
- runCont :: EventF -> StateIO (Maybe a)
- elemById :: MonadIO m => JSString -> m (Maybe Elem)
- withElem :: ElemID -> (Elem -> IO a) -> IO a
- getProp :: Elem -> JSString -> IO JSString
- setProp :: Elem -> JSString -> JSString -> IO ()
- alert :: (Show a, MonadIO m) => a -> m ()
- fromJSString :: (Typeable a, Read a) => JSString -> a
- toJSString :: (Show a, Typeable a) => a -> JSString
- getValue :: MonadIO m => Elem -> m (Maybe String)
- module Control.Applicative
- module GHCJS.Perch
- newtype CheckBoxes a = CheckBoxes [a]
- edit :: Cloud a -> Cloud a
- type JSString = String
- pack :: a
- unpack :: a
- data RadioId = RadioId JSString
- newtype Radio a = Radio a
Documentation
Monad Widget Source # | |
Functor Widget Source # | |
Applicative Widget Source # | |
Alternative Widget Source # | |
MonadPlus Widget Source # | |
MonadIO Widget Source # | |
AdditionalOperators Widget Source # | |
MonadState EventF Widget Source # | |
(Eq a, Num a) => Num (Widget a) Source # | |
Monoid a => Monoid (Widget a) Source # | |
Attributable (Widget a) Source # | |
Attributable (Perch -> Widget a) Source # | |
Running it
module Transient.Move.Utils
runBody :: Widget a -> IO (Maybe a) Source #
run the widget as the body of the HTML. It adds the rendering to the body of the document.
Use only for pure client-side applications, like the ones of http://http://tryplayg.herokuapp.com
render :: Widget a -> TransIO a Source #
executes the computation and add the effect of "hanging" the generated rendering from the one generated by the
previous render
sentence, or from the body of the document, if there isn't any. If an event happens within
the render
parameter, it deletes the rendering of all subsequent ones.
so that the sucessive sequence of render
in the code will reconstruct them again.
However the rendering of elements combined with <|>
or <>
or <*>
are independent.
This allows for full dynamic and composable client-side Web apps.
Widget Combinators and Modifiers
(<<) :: (Perch -> Perch) -> Perch -> Perch infixr 7 Source #
A parameter application with lower priority than ($) and direct function application
(<<<) :: (Perch -> Perch) -> Widget a -> Widget a infixr 5 Source #
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.
(<!) :: Widget a -> [(PropId, JSString)] -> Widget a infixl 8 Source #
Add attributes to the topmost tag of a widget
(<++) :: Widget a -> Perch -> Widget a infixr 6 Source #
Append formatting code to a widget
getString "hi" <++ H1 << "hi there"
It has a infix prority: infixr 6
higuer that <<<
and most other operators
(++>) :: Perch -> Widget a -> Widget a infixr 6 Source #
Prepend formatting code to a widget
bold "enter name" ++ getString Nothing
It has a infix prority: infixr 6
higher that <<<
and most other operators
validate :: Widget a -> (a -> StateIO (Maybe Perch)) -> Widget a Source #
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")
wcallback :: Widget a -> (a -> Widget b) -> Widget b Source #
It is a callback in the view monad. The rendering of the second parameter substitutes the rendering of the first paramenter when the latter validates without afecting the rendering of other widgets.
redraw :: JSString -> Widget a -> TransIO a Source #
execute a widget but redraw itself too when some event happens.
The first parameter is the path of the DOM element that hold the widget, used by at
Basic Widgets
option :: (Typeable b, Show b) => b -> String -> Widget b Source #
use this instead of option
when runing in the browser
wprint :: ToElem a => a -> Widget () Source #
show something enclosed in the pre tag, so ASCII formatting chars are honored
getInteger :: Maybe Integer -> Widget Integer Source #
Display a text box and return an Integer (if the value entered is not an Integer, fails the validation)
getInt :: Maybe Int -> Widget Int Source #
Display a text box and return a Int (if the value entered is not an Int, fails the validation)
getPassword :: Widget String Source #
Display a password box
setRadio :: (Typeable a, Eq a, Show a, Read a) => Bool -> a -> Widget (Radio a) Source #
Implement a radio button
getRadio :: [Widget (Radio a)] -> Widget a Source #
encloses a set of Radio boxes. Return the option selected
setCheckBox :: (Typeable a, Show a) => Bool -> a -> Widget (CheckBoxes a) Source #
present a checkbox
getCheckBoxes :: Show a => Widget (CheckBoxes a) -> Widget [a] Source #
getMultilineText :: JSString -> Widget String Source #
Display a multiline text box and return its content
getSelect :: (Typeable a, Read a, Show a) => Widget (MFOption a) -> Widget a Source #
Display a dropdown box with the options in the first parameter is optionally selected . It returns the selected option.
setOption :: (Show a, Eq a, Typeable a) => a -> Perch -> Widget (MFOption a) Source #
Set the option for getSelect. Options are concatenated with <|>
setSelectedOption :: (Show a, Eq a, Typeable a) => a -> Perch -> Widget (MFOption a) Source #
Set the selected option for getSelect. Options are concatenated with <|>
resetButton :: JSString -> Widget () Source #
inputReset :: JSString -> Widget () Source #
wbutton :: a -> JSString -> Widget a Source #
active button. When clicked, return the first parameter
wlink :: (Show a, Typeable a) => a -> Perch -> Widget a Source #
Present a link. It return the first parameter and execute the continuation when it is clicked.
It also update the path in the URL.
tlink :: (Show a, Typeable a) => a -> Perch -> Widget a Source #
template link. Besides the wlink behaviour, it loads the page from the server if there is any
the page may have been saved with edit
staticNav :: TransIO b -> TransIO b Source #
avoid that a recursive widget with links may produce long paths. It is equivalent to tail call elimination
Empty widget that does not validate. May be used as "empty boxes" inside larger widgets.
It returns a non valid value.
wraw :: Perch -> Widget () Source #
Render raw view formatting. It is useful for displaying information.
Events
data BrowserEvent Source #
Out of Flow Updates
at :: JSString -> UpdateMethod -> Widget a -> Widget a Source #
Run the widget as the content of the element with the given path identifier. The content can be appended, prepended to the previous content or it can erase the previous content depending on the update method.
Reactive and Events
resetEventData :: Widget () Source #
setEventData :: EventData -> Widget () Source #
raiseEvent :: IsEvent event => Widget a -> event -> Widget a Source #
triggers the event that happens in a widget. The effects are the following:
1)The event reexecutes the monadic sentence where the widget is, (with no re-rendering)
2) with the result of this reevaluaution of 1), the rest of the monadic computation is executed
3) update the DOM tree with the rendering generated by the reevaluation of 2).
As usual, If one step of the monadic computation return empty
(stop
), the reevaluation finish
So the effect of an event can be restricted as much as you may need.
The part of the monadic expression that is before the event is not evaluated and his rendering is untouched.
(but, at any moment, you can choose the element to be updated in the page using at
)
wake :: IsEvent event => Widget a -> event -> Widget a Source #
A shorter and smoother synonym for raiseEvent
pass :: IsEvent event => Perch -> event -> Widget EventData Source #
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
Low-level and Internals
getNextId :: MonadState EventF m => m JSString Source #
get the next ideitifier that will be created by genNewId
continuePerch :: Widget a -> ElemID -> Widget a Source #
when creating a complex widget with many tags, this call indentifies which tag will receive the attributes of the (!) operator.
getParam :: (Typeable a, Show a, Read a) => Maybe JSString -> JSString -> Maybe a -> Widget a Source #
Get the continuation context: closure, continuation, state, child threads etc
runCont :: EventF -> StateIO (Maybe a) #
Run the closure and the continuation using the state data of the calling thread
Re-exported
module Control.Applicative
module GHCJS.Perch