Safe Haskell | None |
---|---|
Language | Haskell2010 |
Various SharedRep instances for common html input elements.
Synopsis
- repInput :: (Monad m, ToHtml a) => Parser a -> (a -> Text) -> Input a -> a -> SharedRep m a
- repMessage :: (Monad m, ToHtml a) => Parser a -> (a -> Text) -> Input a -> a -> a -> SharedRep m a
- sliderI :: (Monad m, ToHtml a, Integral a, Show a) => Maybe Text -> a -> a -> a -> a -> SharedRep m a
- slider :: Monad m => Maybe Text -> Double -> Double -> Double -> Double -> SharedRep m Double
- dropdown :: (Monad m, ToHtml a) => Parser a -> (a -> Text) -> Maybe Text -> [Text] -> a -> SharedRep m a
- datalist :: Monad m => Maybe Text -> [Text] -> Text -> Text -> SharedRep m Text
- dropdownSum :: (Monad m, ToHtml a) => Parser a -> (a -> Text) -> Maybe Text -> [Text] -> a -> SharedRep m a
- colorPicker :: Monad m => Maybe Text -> Text -> SharedRep m Text
- textbox :: Monad m => Maybe Text -> Text -> SharedRep m Text
- textarea :: Monad m => Int -> Maybe Text -> Text -> SharedRep m Text
- checkbox :: Monad m => Maybe Text -> Bool -> SharedRep m Bool
- toggle :: Monad m => Maybe Text -> Bool -> SharedRep m Bool
- button :: Monad m => Maybe Text -> SharedRep m Bool
- chooseFile :: Monad m => Maybe Text -> Text -> SharedRep m Text
- maybeRep :: Monad m => Maybe Text -> Bool -> SharedRep m a -> SharedRep m (Maybe a)
- fiddle :: Monad m => Concerns Text -> SharedRep m (Concerns Text, Bool)
- viaFiddle :: Monad m => SharedRep m a -> SharedRep m (Bool, Concerns Text, a)
- accordionList :: Monad m => Maybe Text -> Text -> Maybe Text -> (Text -> a -> SharedRep m a) -> [Text] -> [a] -> SharedRep m [a]
- listMaybeRep :: Monad m => Maybe Text -> Text -> (Text -> Maybe a -> SharedRep m (Maybe a)) -> Int -> [a] -> SharedRep m [Maybe a]
- listRep :: Monad m => Maybe Text -> Text -> (Bool -> SharedRep m Bool) -> (a -> SharedRep m a) -> Int -> a -> [a] -> SharedRep m [a]
- readTextbox :: (Monad m, Read a, Show a) => Maybe Text -> a -> SharedRep m (Either Text a)
- defaultListLabels :: Int -> [Text]
Documentation
:: (Monad m, ToHtml a) | |
=> Parser a | Parser |
-> (a -> Text) | Printer |
-> Input a |
|
-> a | initial value |
-> SharedRep m a |
Create a sharedRep from an Input.
repMessage :: (Monad m, ToHtml a) => Parser a -> (a -> Text) -> Input a -> a -> a -> SharedRep m a Source #
Like repInput
, but does not put a value into the HashMap on instantiation, consumes the value when found in the HashMap, and substitutes a default on lookup failure
sliderI :: (Monad m, ToHtml a, Integral a, Show a) => Maybe Text -> a -> a -> a -> a -> SharedRep m a Source #
integral slider
For Example, a slider between 0 and 1000 with a step of 10 and a default value of 300 is:
>>>
:t sliderI (Just "label") 0 1000 10 300
sliderI (Just "label") 0 1000 10 300 :: (Monad m, ToHtml a, Integral a, Show a) => SharedRep m a
slider :: Monad m => Maybe Text -> Double -> Double -> Double -> Double -> SharedRep m Double Source #
double slider
For Example, a slider between 0 and 1 with a step of 0.01 and a default value of 0.3 is:
>>>
:t slider (Just "label") 0 1 0.01 0.3
slider (Just "label") 0 1 0.01 0.3 :: Monad m => SharedRep m Double
:: (Monad m, ToHtml a) | |
=> Parser a | parse an a from Text |
-> (a -> Text) | print an a to Text |
-> Maybe Text | label suggestion |
-> [Text] | list of dropbox elements (as text) |
-> a | initial value |
-> SharedRep m a |
dropdown box
datalist :: Monad m => Maybe Text -> [Text] -> Text -> Text -> SharedRep m Text Source #
a datalist input
dropdownSum :: (Monad m, ToHtml a) => Parser a -> (a -> Text) -> Maybe Text -> [Text] -> a -> SharedRep m a Source #
A dropdown box designed to help represent a haskell sum type.
textbox :: Monad m => Maybe Text -> Text -> SharedRep m Text Source #
textbox classique
>>>
:t textbox (Just "label") "some text"
textbox (Just "label") "some text" :: Monad m => SharedRep m Text
textarea :: Monad m => Int -> Maybe Text -> Text -> SharedRep m Text Source #
textarea input element, specifying number of rows.
maybeRep :: Monad m => Maybe Text -> Bool -> SharedRep m a -> SharedRep m (Maybe a) Source #
Represent a Maybe using a checkbox.
Hides the underlying content on Nothing
fiddle :: Monad m => Concerns Text -> SharedRep m (Concerns Text, Bool) Source #
Representation of web concerns (css, js & html).
viaFiddle :: Monad m => SharedRep m a -> SharedRep m (Bool, Concerns Text, a) Source #
turns a SharedRep into a fiddle
accordionList :: Monad m => Maybe Text -> Text -> Maybe Text -> (Text -> a -> SharedRep m a) -> [Text] -> [a] -> SharedRep m [a] Source #
A (fixed-size) list represented in html as an accordion card
A major restriction of the library is that a SharedRepF
does not have a Monad instance. In practice, this means that the external representation of lists cannot have a dynamic size.
listMaybeRep :: Monad m => Maybe Text -> Text -> (Text -> Maybe a -> SharedRep m (Maybe a)) -> Int -> [a] -> SharedRep m [Maybe a] Source #
A fixed-sized list of Maybe a's
:: Monad m | |
=> Maybe Text | |
-> Text | |
-> (Bool -> SharedRep m Bool) | name prefix (should be unique) |
-> (a -> SharedRep m a) | Bool Rep |
-> Int | a Rep |
-> a | maximum length of list |
-> [a] | default value for new rows |
-> SharedRep m [a] | initial values |
A SharedRep of [a]. Due to the applicative nature of the bridge, the size of lists has to be fixed on construction. listRep is a workaround for this, to enable some form of dynamic sizing.
readTextbox :: (Monad m, Read a, Show a) => Maybe Text -> a -> SharedRep m (Either Text a) Source #
Parse from a textbox
defaultListLabels :: Int -> [Text] Source #