Closed benjaminweb closed 3 weeks ago
See #15
But this might be easily solvable by triggering an action on a parent view. Can you give me a specific example?
Below is an example that actually solves my requirement: Updating multiple other hyper views that are no descendants of the one that triggers the update.
Don't reload the full parent but only another hyper view that is child of that parent.
Does that solve the original requirement of #15?
What would be the benefit of simplifying this?
module Main where
import qualified Data.Text as T
import Data.Text (Text)
import Web.Hyperbole
import Data.Maybe (fromMaybe)
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wno-missing-signatures #-}
main = do
run 3000 $ do
liveApp (basicDocument "Skeleton") (page $ centralPage)
data Central = Central
deriving (Show, Read, ViewId)
data CentralAction = ChangeSelectedTo Selected
deriving (Show, Read, ViewAction)
data Selected = A | B | C deriving (Show, Eq, Read)
instance HyperView Central where
type Action Central = CentralAction
type Require Central = '[Presets, Results, Sidebar]
central :: Central -> CentralAction -> Eff es (View Central ())
central _ (ChangeSelectedTo x) = pure $ centralView x
centralPage :: (Hyperbole :> es) => Page es '[Central, Presets, Results, Sidebar]
centralPage = do
-- message listens for any actions that the centralView triggers
handle central $ handle presets $ handle results $ handle sidebar $ load $ do
pure $ do
el bold "Message Page"
row (border 3 . pad 10 . gap 10) $ do
hyper (Sidebar 1) $ sidebarView Nothing
hyper Central $ centralView A
hyper (Sidebar 2) $ sidebarView Nothing
centralView :: Selected -> View Central ()
centralView s = do
col (border 3 . pad 10) $ do
el_ $ text ("Selected: " `T.append` T.pack (show s))
button (ChangeSelectedTo A) id "A"
button (ChangeSelectedTo B) id "B"
button (ChangeSelectedTo C) id "C"
col (border 3 . pad 10 . gap 10) $ do
hyper Presets $ presetsView s
hyper Results $ resultsView Nothing
data Presets = Presets
deriving (Show, Read, ViewId)
data PresetsAction = View Selected deriving (Show, Read, ViewAction)
instance HyperView Presets where
type Action Presets = PresetsAction
presets :: (Hyperbole :> es) => Presets -> PresetsAction -> Eff es (View Presets ())
presets _ (View s) = pure $ presetsView s
presetsView :: Selected -> View Presets ()
presetsView s = do
col (border 3 . pad 10) $ do
text $ "viewing details for " `T.append` T.pack (show s)
let variant x t = target Results $ button (ViewResults $ Just x) id t
case s of
A -> col id $ variant Result1 "Result1"
B -> col id $ do
variant Result2 "Result2"
variant Result3 "Result3"
C -> col id $ do
variant Result4 "Result4"
variant Result5 "Result5"
variant Result6 "Result6"
data Results = Results
deriving (Show, Read, ViewId)
data ResultVariant = Result1 | Result2 | Result3 | Result4 | Result5 | Result6 | Result7 | Result8 deriving (Show, Eq, Read)
data ResultsAction = ViewResults (Maybe ResultVariant) deriving (Show, Read, ViewAction)
instance HyperView Results where
type Action Results = ResultsAction
results :: (Hyperbole :> es) => Results -> ResultsAction -> Eff es (View Results ())
results _ (ViewResults x) = pure $ col (border 3 . pad 10) $ resultsView x
resultsView :: Maybe ResultVariant -> View Results ()
resultsView Nothing = col (border 3 . pad 10) $ el_ $ text "no results!"
resultsView (Just x) = col (border 3 . pad 10) $
case x of
Result1 -> text "one short result"
Result2 -> text "a different result"
Result3 -> text "this is a special result"
Result4 -> text "THIS IS NUUMBER FOOOUR!"
Result5 -> text "give me a high five"
Result6 -> do
target (Sidebar 1) $ button (UpdateSidebar (Just "surprise!!")) id "click me to get surprise in sidebar"
Result7 -> do
target Results $ onLoad (ViewResults (Just Result8)) 0 (el_ "loading…")
target (Sidebar 2) $ onLoad (UpdateSidebar (Just "unlocking secret chamber…")) 0 (el_ "loading…")
target (Sidebar 1) $ onLoad (UpdateSidebar (Just "wohoo! you did it!")) 0 (el_ "loading…")
Result8 -> text "you unlocked the secret chamber"
data Sidebar = Sidebar Int
deriving (Show, Read, ViewId)
data SidebarAction = UpdateSidebar (Maybe Text)
deriving (Show, Read, ViewAction)
instance HyperView Sidebar where
type Action Sidebar = SidebarAction
sidebar :: Sidebar -> SidebarAction -> Eff es (View Sidebar ())
sidebar _ (UpdateSidebar x) = pure $ sidebarView x
sidebarView :: Maybe Text -> View Sidebar ()
sidebarView x = col (border 3 . pad 10) $ do
text $ fromMaybe "N/A" x
case x of
Just "surprise!!" -> target Results $ button (ViewResults (Just Result7)) id "set to Result7"
Just x -> none
Nothing -> none
Thanks for sending that! I assume that you're using lazy loading and extra hyper views just to try things out, but your example can be greatly simplified by getting rid of the presets and results view:
https://gist.github.com/seanhess/37355f9b5b02adae335fd7c8cdc42b29
Take note that you can create view functions, which accept different parameters for rendering, without making them HyperViews. They are all View Central ()
, but you can pass a bunch of different state parameters into them to control the. page.
HyperViews are intended to update more independently. So the simple answer to this is to use larger views. Use functions for code reuse. Only reach for a HyperView if you need it to update independently, or that paradigm makes it easy.
Closing for now, but feel free to respond with further thoughts or clarifications. We can reopen if we can discover a motivating example
Also, if I understand what you were going for, it would be solveable with #15
Yup, it was simply a setup / example for #15.
Key takeaways:
View Central ()
with different input types and can combine them together freely to enhance code reuse; can’t be updated independentlyWhat do you mean with larger views specifically?
I can create multiple functions with same return type like View Central () with different input types and can combine them together freely to enhance code reuse; can’t be updated independently
Yep!
only hyperviews can be updated independently but are not variable in input arguments, correct?
I'm not 100% sure what you mean by "variable in input arguments", but this probably isn't correct. You can add arguments to the main view function, like any haskell function. You can also pass arguments to handlers from the top-level page. See https://github.com/seanhess/hyperbole/blob/main/example/Example/Counter.hs for an example.
By larger views, I mean, putting more things into a single hyperview. It's tempted to make everything into a "component" if you've done web development before, but you're going to have an easier time if you try to use plain old function arguments first, and only use independent hyperviews only when you need things to update independetly.
You can push the funciton arguments technique pretty far. You can even create view functions that expect an action as an argument.
Something like:
chooseOne :: Action id -> Action id -> View id ()
chooseOne onChooseA onChooseB = do
el_ "Choose One"
button onChooseA id "A"
button onChooseB id "B"
That's a silly example, but hopefully you get the idea.
Common pattern I've encountered is one button click should trigger update of multiple views. Button targets implicitly. Workaround: I currently solve this by nesting the second action view under the first triggered one. Limitation: However if triggers might originate from different views, this would not be practical.
How can I update two or more independent views with one button action at once (chaining or in parallel)?
…or am I solving the wrong problem?