module Web.Hyperbole.HyperView.Input where
import Data.String.Conversions (cs)
import Data.Text (Text)
import Web.Atomic.Types
import Web.Hyperbole.Data.Param (ParamValue (..), ToParam (..))
import Web.Hyperbole.HyperView.Event (DelayMs, onChange, onClick, onInput)
import Web.Hyperbole.HyperView.Types (HyperView (..))
import Web.Hyperbole.HyperView.ViewAction (ViewAction (..))
import Web.Hyperbole.Route (Route (..), routeUri)
import Web.Hyperbole.View
button :: (ViewAction (Action id)) => Action id -> View id () -> View id ()
button :: forall id.
ViewAction (Action id) =>
Action id -> View id () -> View id ()
button Action id
action View id ()
cnt = do
Text -> View id () -> View id ()
forall c. Text -> View c () -> View c ()
tag Text
"button" View id ()
cnt View id ()
-> (Attributes (View id ()) -> Attributes (View id ()))
-> View id ()
forall h.
Attributable h =>
h -> (Attributes h -> Attributes h) -> h
@ Action id -> Attributes (View id ()) -> Attributes (View id ())
forall id a.
(ViewAction (Action id), ViewContext a ~ id, Attributable a) =>
Action id -> Attributes a -> Attributes a
onClick Action id
action
dropdown
:: (ViewAction (Action id))
=> (opt -> Action id)
-> opt
-> View (Option opt id) ()
-> View id ()
dropdown :: forall id opt.
ViewAction (Action id) =>
(opt -> Action id) -> opt -> View (Option opt id) () -> View id ()
dropdown opt -> Action id
act opt
defOpt View (Option opt id) ()
options = do
Text -> View id () -> View id ()
forall c. Text -> View c () -> View c ()
tag Text
"select" (View id () -> View id ())
-> (Attributes (View id () -> View id ())
-> Attributes (View id () -> View id ()))
-> View id ()
-> View id ()
forall h.
Attributable h =>
h -> (Attributes h -> Attributes h) -> h
@ (opt -> Action id)
-> Attributes (View id () -> View id ())
-> Attributes (View id () -> View id ())
forall id a value.
(ViewAction (Action id), ViewContext a ~ id, Attributable a) =>
(value -> Action id) -> Attributes a -> Attributes a
onChange opt -> Action id
act (View id () -> View id ()) -> View id () -> View id ()
forall a b. (a -> b) -> a -> b
$ do
Option opt id -> View (Option opt id) () -> View id ()
forall ctx c. ctx -> View ctx () -> View c ()
addContext (opt -> Option opt id
forall {k} opt (id :: k). opt -> Option opt id
Option opt
defOpt) View (Option opt id) ()
options
option
:: (ViewAction (Action id), Eq opt, ToParam opt)
=> opt
-> Text
-> View (Option opt id) ()
option :: forall id opt.
(ViewAction (Action id), Eq opt, ToParam opt) =>
opt -> Text -> View (Option opt id) ()
option opt
opt Text
cnt = do
Option opt id
os <- View (Option opt id) (Option opt id)
forall c. View c c
context
Text -> View (Option opt id) () -> View (Option opt id) ()
forall c. Text -> View c () -> View c ()
tag Text
"option" (View (Option opt id) () -> View (Option opt id) ())
-> (Attributes (View (Option opt id) () -> View (Option opt id) ())
-> Attributes (View (Option opt id) () -> View (Option opt id) ()))
-> View (Option opt id) ()
-> View (Option opt id) ()
forall h.
Attributable h =>
h -> (Attributes h -> Attributes h) -> h
@ Text
-> Text
-> Attributes (View (Option opt id) () -> View (Option opt id) ())
-> Attributes (View (Option opt id) () -> View (Option opt id) ())
forall h.
Attributable h =>
Text -> Text -> Attributes h -> Attributes h
att Text
"value" (opt -> ParamValue
forall a. ToParam a => a -> ParamValue
toParam opt
opt).value (View (Option opt id) () -> View (Option opt id) ())
-> (Attributes (View (Option opt id) () -> View (Option opt id) ())
-> Attributes (View (Option opt id) () -> View (Option opt id) ()))
-> View (Option opt id) ()
-> View (Option opt id) ()
forall h.
Attributable h =>
h -> (Attributes h -> Attributes h) -> h
@ Bool
-> Attributes (View (Option opt id) () -> View (Option opt id) ())
-> Attributes (View (Option opt id) () -> View (Option opt id) ())
forall h. Attributable h => Bool -> Attributes h -> Attributes h
selected (Option opt id
os.defaultOption opt -> opt -> Bool
forall a. Eq a => a -> a -> Bool
== opt
opt) (View (Option opt id) () -> View (Option opt id) ())
-> View (Option opt id) () -> View (Option opt id) ()
forall a b. (a -> b) -> a -> b
$ Text -> View (Option opt id) ()
forall c. Text -> View c ()
text Text
cnt
selected :: (Attributable h) => Bool -> Attributes h -> Attributes h
selected :: forall h. Attributable h => Bool -> Attributes h -> Attributes h
selected Bool
b = if Bool
b then Text -> Text -> Attributes h -> Attributes h
forall h.
Attributable h =>
Text -> Text -> Attributes h -> Attributes h
att Text
"selected" Text
"true" else Attributes h -> Attributes h
forall a. a -> a
id
data Option opt id = Option
{ forall {k} opt (id :: k). Option opt id -> opt
defaultOption :: opt
}
search :: (ViewAction (Action id)) => (Text -> Action id) -> DelayMs -> View id ()
search :: forall id.
ViewAction (Action id) =>
(Text -> Action id) -> DelayMs -> View id ()
search Text -> Action id
go DelayMs
delay = do
Text -> View id () -> View id ()
forall c. Text -> View c () -> View c ()
tag Text
"input" View id ()
forall c. View c ()
none View id ()
-> (Attributes (View id ()) -> Attributes (View id ()))
-> View id ()
forall h.
Attributable h =>
h -> (Attributes h -> Attributes h) -> h
@ (Text -> Action id)
-> DelayMs -> Attributes (View id ()) -> Attributes (View id ())
forall id a.
(ViewAction (Action id), ViewContext a ~ id, Attributable a) =>
(Text -> Action id) -> DelayMs -> Attributes a -> Attributes a
onInput Text -> Action id
go DelayMs
delay
checked :: (Attributable a) => Bool -> Attributes a -> Attributes a
checked :: forall h. Attributable h => Bool -> Attributes h -> Attributes h
checked Bool
c =
Text -> Text -> Attributes a -> Attributes a
forall h.
Attributable h =>
Text -> Text -> Attributes h -> Attributes h
att Text
"data-checked" (String -> Text
forall a b. ConvertibleStrings a b => a -> b
cs (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Bool -> String
forall a. Show a => a -> String
show Bool
c)
(Attributes a -> Attributes a)
-> (Attributes a -> Attributes a) -> Attributes a -> Attributes a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. if Bool
c then Text -> Text -> Attributes a -> Attributes a
forall h.
Attributable h =>
Text -> Text -> Attributes h -> Attributes h
att Text
"checked" Text
"" else Attributes a -> Attributes a
forall a. a -> a
id
route :: (Route a) => a -> View c () -> View c ()
route :: forall a c. Route a => a -> View c () -> View c ()
route a
r = URI -> View c () -> View c ()
forall c. URI -> View c () -> View c ()
link (a -> URI
forall a. Route a => a -> URI
routeUri a
r)