Compare commits

...

2 Commits

Author SHA1 Message Date
5efb2deab6 Something that looks like a form 2019-01-22 23:35:26 +02:00
3e359afcbe Simple routing 2019-01-22 22:40:44 +02:00
2 changed files with 75 additions and 19 deletions

View File

@ -20,9 +20,13 @@ executable frontend
-- other-modules: -- other-modules:
-- other-extensions: -- other-extensions:
build-depends: base >=4.11 && <4.12 build-depends: base >=4.11 && <4.12
, miso
, jsaddle-warp
, mtl
, common , common
, generic-lens
, jsaddle-warp
, lens
, miso
, mtl
, servant
hs-source-dirs: src hs-source-dirs: src
default-language: Haskell2010 default-language: Haskell2010
ghc-options: -Wall

View File

@ -1,41 +1,93 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE GADTs #-}
module Main where module Main where
import Control.Lens (over, set)
import Control.Monad.Trans (liftIO) import Control.Monad.Trans (liftIO)
import Data.Generics.Product
import GHC.Generics (Generic)
import Language.Javascript.JSaddle.Warp import Language.Javascript.JSaddle.Warp
import Miso import Miso hiding (set)
import Miso.String import Miso.String
import Servant.API
import Servant.Links
import Data.Proxy (Proxy(..))
type API = Home :<|> Login :<|> Register
type Home = View Action
type Login = "login" :> View Action
type Register = "register" :> View Action
data Action = Add data Action = Add
| Subtract | Subtract
| SayHello | SayHello
| HandleURI URI
| ChangeURI URI
| NoOp | NoOp
newtype Model = Model Int deriving (Eq, Num, ToMisoString) data Model = Model { counter :: Int
, uri :: URI }
deriving (Eq, Generic)
updateModel :: Action -> Model -> Effect Action Model updateModel :: Model -> Action -> Effect Action Model
updateModel Add m = noEff (m + 1) updateModel m = \case
updateModel Subtract m = noEff (m - 1) Add -> noEff (over (field @"counter") (+1) m)
updateModel SayHello m = m <# (liftIO (putStrLn "Hello world") >> pure NoOp) Subtract -> noEff (over (field @"counter") (\x -> x - 1) m)
updateModel NoOp m = noEff m SayHello -> m <# (liftIO (putStrLn "Hello world") >> pure NoOp)
HandleURI uri -> noEff (set (field @"uri") uri m)
ChangeURI uri -> m <# do
liftIO $ putStrLn $ "Pushing uri " <> show uri
pushURI uri
return $ HandleURI uri
NoOp -> noEff m
viewModel :: Model -> View Action viewModel :: Model -> View Action
viewModel x = viewModel model = view
div_ [] [ button_ [ onClick Add ] [ text "+" ] where
, text (ms x) view = either (const the404) id $ runRoute @API Proxy handlers uri model
, button_ [ onClick Subtract ] [ text "-" ] handlers = home :<|> login :<|> register
] home _ = div_ [] [ button_ [ onClick Add ] [ text "+" ]
, text (ms (counter model))
, button_ [ onClick Subtract ] [ text "-" ]
, button_ [ onClick goLogin ] [ text "go login" ]
, button_ [ onClick goRegister ] [ text "go register" ]
]
login _ = div_ [] []
register _ = div_ [] [
h3_ [] [text "register"]
, label_ [] [text "Username"], input_ [id_ "username", name_ "username"]
, label_ [] [text "Email"], input_ [id_ "email", name_ "email"]
, label_ [] [text "Password"], input_ [id_ "password", name_ "password"]
, label_ [] [text "Password again"], input_ [id_ "passwordAgain", name_ "passwordAgain"]
, button_ [] [text "Register"]
]
the404 = div_ [] []
goLogin, goHome, goRegister :: Action
goLogin = goto @Login @API Proxy Proxy
goHome = goto @Home @API Proxy Proxy
goRegister = goto @Register @API Proxy Proxy
goto :: (IsElem endpoint api, HasLink endpoint, MkLink endpoint Link ~ Link) => Proxy api -> Proxy endpoint -> Action
goto a b = ChangeURI (linkURI (safeLink a b))
main :: IO () main :: IO ()
main = run 8081 $ startApp App{..} main = run 8081 $ do
model <- mkModel
startApp App{..}
where where
model = Model 0 mkModel = Model <$> pure 0 <*> getCurrentURI
initialAction = SayHello initialAction = SayHello
update = updateModel update = flip updateModel
view = viewModel view = viewModel
subs = [] subs = [ uriSub HandleURI ]
events = defaultEvents events = defaultEvents
mountPoint = Nothing mountPoint = Nothing