seanhess / hyperbole

Haskell interactive serverside web framework inspired by HTMX
Other
95 stars 6 forks source link

Feedback Requested: Typed Handlers #16

Closed seanhess closed 4 months ago

seanhess commented 4 months ago

On smaller pages, it's easy to remember to add handle myview to the top of the page. But on complicated pages, which may re-use other views, it's easy to get mixed up and forget.

This PR uses type-level lists to require a Page to handle all the views used, and any of their descendents.

Here is the old monadic interface and type signature:

simplePage :: (Hyperbole :> es) => Page es Response
simplePage = do
  handle message
  load $ do
    pure $ col (pad 20) $ do
      el bold "My Page"
      hyper (Message 1) $ messageView "Hello"
      hyper (Message 2) $ messageView "World!"

This PR requires us to specify which views we support in the page.

simplePage :: (Hyperbole :> es) => Page es '[Message]
simplePage = do
  handle message $ load $ do
    pure $ col (pad 20) $ do
      el bold "My Page"
      hyper (Message 1) $ messageView "Hello"
      hyper (Message 2) $ messageView "World!"

If we forget to add Message to the type of Page we get this error:

    • Message not handled by Page: '[]

If we do add the type to Page, but forget to add handle message $ ...

    • Could not deduce (Handler Message :> es)
        arising from a use of ‘load’

HyperViews may also specify which children views they support with the new Children associated type:

instance HyperView Status where
  type Action Status = CheckStatus
  type Children Status = '[]   -- This line can be omitted if set to an empty list

If we try to embed another hyperview but forget to add it to the the Children type, we get this error:

    • HyperView MainView not found in (Children Status)
        '[]
      Try adding it to the HyperView instance:
        type Children Status = [MainView]

The compiler also checks that all descendents of a view are handled in the page.

Any feedback? There are a few things to improve, but it seems like a step forward

seanhess commented 4 months ago

Here is a full example using the new syntax:

{-# LANGUAGE LambdaCase #-}

module Simple where

import Data.Text (pack)
import Effectful
import Web.Hyperbole

main = do
  run 3000 $ do
    liveApp (basicDocument "Example") (page simplePage)

simplePage :: (Hyperbole :> es, IOE :> es) => Page es '[MainView, Status]
simplePage = do
  handle main' $ handle status $ load $ do
    liftIO $ putStrLn "MAIN LOAD"
    pure $ col (pad 20) $ do
      el bold "My Page"
      hyper MainView $ do
        row (gap 10) $ do
          button GoBegin (border 1) "Start"

-- MAIN ----------------------------------------

data MainView = MainView
  deriving (Show, Read, ViewId)

data MainAction
  = GoBegin
  | GoMid
  | GoEnd
  deriving (Show, Read, ViewAction)

instance HyperView MainView where
  type Action MainView = MainAction
  type Children MainView = '[Status]

main' :: MainView -> MainAction -> Eff es (View MainView ())
main' _ = \case
  GoBegin -> pure beginStep
  GoMid -> pure middleStep
  GoEnd -> pure endStep

beginStep :: View MainView ()
beginStep = do
  el_ "BEGIN"
  button GoMid (border 1) " Mid"

middleStep :: View MainView ()
middleStep = do
  el_ "MIDDLE: running"
  button GoBegin (border 1) "Back"
  hyper Status $ statusView 0

endStep :: View MainView ()
endStep = do
  el_ "END"
  button GoMid (border 1) "Back"

-- Status ---------------------------------------

data Status = Status
  deriving (Show, Read, ViewId)

data CheckStatus
  = CheckStatus Int
  deriving (Show, Read, ViewAction)

instance HyperView Status where
  type Action Status = CheckStatus
  type Children Status = '[]

status :: Status -> CheckStatus -> Eff es (View Status ())
status _ = \case
  CheckStatus n ->
    if n >= 5
      then pure lazyEnd
      else pure $ statusView (n + 1)

statusView :: Int -> View Status ()
statusView n = do
  onLoad (CheckStatus n) 1000 $ do
    el_ $ text $ "Checking Status" <> pack (show n)

lazyEnd :: View Status ()
lazyEnd = do
  el_ "Lazy End"
  hyper MainView $ do
    button GoEnd (border 1) "Go End"
cgeorgii commented 4 months ago

Overall I really like the idea, even though I find the new pattern a tiny bit less ergonomic:

page :: forall es . (Hyperbole :> es, Users :> es, Debug :> es) => Page es [Contacts, Contact]
page =
  handle contacts . handle contact . load $ do
    us <- usersAll
    pure $ do
      col (pad 10 . gap 10) $ do

The benefit of having the page not compile unless everything has been handled outweighs this small cost, though.

seanhess commented 4 months ago

Overall I really like the idea, even though I find the new pattern a tiny bit less ergonomic:

Yeah, I'm a little grumpy about it too. A monadic interface isn't possible (without threading return values or using the bind operator). So we're stuck with function chaining or operators. I haven't finished experimenting with operators, but I haven't found a better pattern yet. Any other ideas?

I'm also sad how fourmolu formats the chain when split across multiple lines.

handle contacts
  $ handle contact
  $ load
  $ do
       ...
seanhess commented 4 months ago

I've spent days trying to slightly improve the interface and can't come up with anything better. I'll merge this, but if we can come up with a better option before releasing the next version, let's do it.