1
1
mirror of https://github.com/aelve/guide.git synced 2024-11-24 05:45:11 +03:00

Add Pux example app for cat-overview (#193)

+ add routes on client-side
This commit is contained in:
Jens Krause 2017-08-27 22:22:13 +02:00
parent afc326c30c
commit b7921a00d2
No known key found for this signature in database
GPG Key ID: 3B2FAFBCEFA5906D
16 changed files with 279 additions and 49 deletions

View File

@ -2,4 +2,8 @@
import '../../shared.js';
// client app
var Client = require('./CategoryOverview.purs');
Client.main();
const app = Client.main(window.location.pathname)(window.__puxLastState || Client.initialState)()
app.state.subscribe(function (state) {
window.__puxLastState = state;
});

View File

@ -1,9 +1,38 @@
module Guide.Client.CategoryOverview where
import Prelude
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE, log)
import DOM (DOM)
import DOM.HTML (window)
import DOM.HTML.Types (HISTORY)
import Guide.CategoryOverview.Events (AppEffects, Event(..), foldp)
import Guide.CategoryOverview.Routes (match)
import Guide.CategoryOverview.State (State, init)
import Guide.CategoryOverview.View.Layout (view)
import Pux (CoreEffects, App, start)
import Pux.DOM.Events (DOMEvent)
import Pux.DOM.History (sampleURL)
import Pux.Renderer.React (renderToDOM)
import Signal ((~>))
main :: forall e. Eff (console :: CONSOLE | e) Unit
main = do
log "Hello category-overview!"
type WebApp = App (DOMEvent -> Event) Event State
type ClientEffects = CoreEffects (AppEffects (history :: HISTORY, dom :: DOM, console :: CONSOLE))
main :: String -> State -> Eff ClientEffects WebApp
main url state = do
urlSignal <- sampleURL =<< window
let routeSignal = urlSignal ~> \r -> PageView (match r)
app <- start { initialState: state
, view
, foldp
, inputs: [routeSignal]
}
renderToDOM "#guide" app.markup app.input
log "Heeeelloooo, here is category-overview page rendered on client-side"
pure app
initialState :: State
initialState = init "/"

View File

@ -1,15 +1,14 @@
module Guide.CategoryDetail.Routes where
import Data.Eq (class Eq)
import Data.Function (($))
import Data.Functor ((<$))
import Prelude
import Data.Generic (class Generic, gEq, gShow)
import Data.Maybe (fromMaybe)
import Data.Show (class Show)
import Pux.Router (end, router)
import Pux.Router (end, lit, router, str)
import Guide.Types (CategoryName(..))
data Route
= Home
= CategoryDetail CategoryName String
| NotFound String
derive instance genericRoute :: Generic Route
@ -18,10 +17,24 @@ instance showRoute :: Show Route where
instance eqRoute :: Eq Route where
eq = gEq
match :: String -> Route
match url = fromMaybe (NotFound url) $ router url $
Home <$ end
CategoryDetail <<< CategoryName <$> (lit categoryLit *> str)
<*> str <* end
toURL :: Route -> String
toURL (NotFound url) = url
toURL (Home) = "/"
toURL (NotFound url) = url
toURL (CategoryDetail catName catId) = categoryDetailUrl catName catId
litUrl :: String -> String
litUrl lit = "/" <> lit
categoryLit :: String
categoryLit = "category"
categoryUrl :: CategoryName -> String
categoryUrl (CategoryName name) = (litUrl categoryLit) <> (litUrl name)
categoryDetailUrl :: CategoryName -> String -> String
categoryDetailUrl catName catId = (categoryUrl catName) <> (litUrl catId)

View File

@ -1,17 +1,14 @@
module Guide.CategoryDetail.View.Homepage where
import Prelude
import Guide.CategoryDetail.Events (Event)
import Guide.CategoryDetail.State (State)
import Control.Bind (discard)
import Data.Function (($))
import Pux.DOM.HTML (HTML)
import Text.Smolder.HTML (a, div, h1)
import Text.Smolder.HTML.Attributes (href, className)
import Text.Smolder.Markup ((!), text)
import Text.Smolder.HTML (div, h1) as S
import Text.Smolder.Markup (text)
view :: State -> HTML Event
view s =
div do
h1 $ text "Pux"
a ! className "guide" ! href "https://www.purescript-pux.org/" $ text "Guide"
a ! className "github" ! href "https://github.com/alexmingoia/purescript-pux/" $ text "GitHub"
S.div do
S.h1 $ text "Category Detail"

View File

@ -2,7 +2,7 @@ module Guide.CategoryDetail.View.Layout where
import Guide.CategoryDetail.View.Homepage as Homepage
import Guide.CategoryDetail.View.NotFound as NotFound
import Guide.CategoryDetail.Routes (Route(NotFound, Home))
import Guide.CategoryDetail.Routes (Route(..))
import Guide.CategoryDetail.State (State(..))
import Guide.CategoryDetail.Events (Event)
import CSS (CSS, fromString, (?), fontSize, display, inlineBlock, marginTop, marginRight, marginLeft, px, value, key, color, backgroundColor, padding, borderRadius)
@ -24,8 +24,8 @@ view (State st) =
style css
case st.route of
(Home) -> Homepage.view (State st)
(NotFound url) -> NotFound.view (State st)
(CategoryDetail _ _)-> Homepage.view (State st)
css :: CSS
css = do
@ -35,7 +35,7 @@ css = do
fromString "body" ? do
backgroundColor (rgb 0 20 30)
key (fromString "font-family") (value "-Guide.CategoryDetail.e-system,BlinkMacSystemFont,\"Segoe UI\",Roboto,Oxygen-Sans,Ubuntu,Cantarell,\"Helvetica Neue\",sans-serif")
key (fromString "font-family") (value "-apple-system,BlinkMacSystemFont,\"Segoe UI\",Roboto,Oxygen-Sans,Ubuntu,Cantarell,\"Helvetica Neue\",sans-serif")
color white
textAlign center

View File

@ -0,0 +1,14 @@
module Guide.CategoryOverview.Events where
import Guide.CategoryOverview.Routes (Route)
import Guide.CategoryOverview.State (State(..))
import Data.Function (($))
import Network.HTTP.Affjax (AJAX)
import Pux (EffModel, noEffects)
data Event = PageView Route
type AppEffects fx = (ajax :: AJAX | fx)
foldp :: ∀ fx. Event -> State -> EffModel State Event (AppEffects fx)
foldp (PageView route) (State st) = noEffects $ State st { route = route, loaded = true }

View File

@ -0,0 +1,35 @@
module Guide.CategoryOverview.Routes where
import Prelude
import Data.Generic (class Generic, gEq, gShow)
import Data.Maybe (fromMaybe)
import Pux.Router (end, lit, router, str)
import Guide.Types (CategoryName(..))
data Route
= CategoryOverview CategoryName
| NotFound String
derive instance genericRoute :: Generic Route
instance showRoute :: Show Route where
show = gShow
instance eqRoute :: Eq Route where
eq = gEq
match :: String -> Route
match url = fromMaybe (NotFound url) $ router url $
CategoryOverview <<< CategoryName <$> (lit categoryLit *> str) <* end
toURL :: Route -> String
toURL (NotFound url) = url
toURL (CategoryOverview catName) = categoryUrl catName
litUrl :: String -> String
litUrl lit = "/" <> lit
categoryLit :: String
categoryLit = "category"
categoryUrl :: CategoryName -> String
categoryUrl (CategoryName name) = (litUrl categoryLit) <> (litUrl name)

View File

@ -0,0 +1,24 @@
module Guide.CategoryOverview.State where
import Data.Generic (class Generic, gShow)
import Data.Newtype (class Newtype)
import Data.Show (class Show)
import Guide.CategoryOverview.Routes (Route, match)
newtype State = State
{ title :: String
, route :: Route
, loaded :: Boolean
}
derive instance gState :: Generic State
derive instance newtypeState :: Newtype State _
instance showState :: Show State where
show = gShow
init :: String -> State
init url = State
{ title: "CategoryDetail page" -- TODO (sectore): Change title
, route: match url
, loaded: false
}

View File

@ -0,0 +1,14 @@
module Guide.CategoryOverview.View.Homepage where
import Prelude
import Guide.CategoryOverview.Events (Event)
import Guide.CategoryOverview.State (State)
import Pux.DOM.HTML (HTML)
import Text.Smolder.HTML (div, h1) as S
import Text.Smolder.Markup (text)
view :: State -> HTML Event
view s =
S.div do
S.h1 $ text "Category Overview"

View File

@ -0,0 +1,70 @@
module Guide.CategoryOverview.View.Layout where
import Guide.CategoryOverview.View.Homepage as Homepage
import Guide.CategoryOverview.View.NotFound as NotFound
import Guide.CategoryOverview.Routes (Route(..))
import Guide.CategoryOverview.State (State(..))
import Guide.CategoryOverview.Events (Event)
import CSS (CSS, fromString, (?), fontSize, display, inlineBlock, marginTop, marginRight, marginLeft, px, value, key, color, backgroundColor, padding, borderRadius)
import CSS.Border (border, solid)
import CSS.TextAlign (center, textAlign)
import CSS.Text (textDecoration, noneTextDecoration, letterSpacing)
import CSS.Text.Transform (textTransform, uppercase)
import Color (rgb)
import Control.Bind (discard)
import Data.Function (($), (#))
import Pux.DOM.HTML (HTML, style)
import Text.Smolder.HTML (div)
import Text.Smolder.HTML.Attributes (className)
import Text.Smolder.Markup ((!))
view :: State -> HTML Event
view (State st) =
div ! className "app" $ do
style css
case st.route of
(NotFound url) -> NotFound.view (State st)
(CategoryOverview name)-> Homepage.view (State st)
css :: CSS
css = do
let green = rgb 14 196 172
blue = rgb 14 154 196
white = rgb 250 250 250
fromString "body" ? do
backgroundColor (rgb 0 20 30)
key (fromString "font-family") (value "-apple-system,BlinkMacSystemFont,\"Segoe UI\",Roboto,Oxygen-Sans,Ubuntu,Cantarell,\"Helvetica Neue\",sans-serif")
color white
textAlign center
fromString "h1" ? do
fontSize (48.0 #px)
marginTop (48.0 #px)
textTransform uppercase
letterSpacing (6.0 #px)
fromString "a" ? do
display inlineBlock
borderRadius (2.0 #px) (2.0 #px) (2.0 #px) (2.0 #px)
padding (6.0 #px) (6.0 #px) (6.0 #px) (6.0 #px)
textDecoration noneTextDecoration
fromString ".guide" ? do
border solid (2.0 #px) green
color green
marginRight (10.0 #px)
fromString ".guide:hover" ? do
backgroundColor green
color white
fromString ".github" ? do
border solid (2.0 #px) blue
color blue
marginLeft (10.0 #px)
fromString ".github:hover" ? do
backgroundColor blue
color white

View File

@ -0,0 +1,9 @@
module Guide.CategoryOverview.View.NotFound where
import Data.Function (($))
import Pux.DOM.HTML (HTML)
import Text.Smolder.HTML (div, h2)
import Text.Smolder.Markup (text)
view :: ∀ st ev. st -> HTML ev
view st = div $ h2 $ text "404 Not Found"

View File

@ -0,0 +1,12 @@
module Guide.Types where
import Prelude
import Data.Generic (class Generic, gShow)
import Data.Newtype (class Newtype)
newtype CategoryName = CategoryName String
derive instance gCategoryName :: Generic CategoryName
derive instance newtypeCategoryName :: Newtype CategoryName _
instance showCategoryName :: Show CategoryName where
show = gShow

View File

@ -1,11 +0,0 @@
module Guide.Server.Common where
import Guide.Server.Types (PageConfig)
import Node.Express.Handler (Handler)
import Node.Express.Response (render)
renderPage :: forall eff . PageConfig -> Handler eff
renderPage config =
-- TODO (sectore) Render a single Pux app for each page
render "layout" config

View File

@ -7,17 +7,18 @@ import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Exception (Error, message)
import Data.Argonaut.Generic.Aeson (options)
import Data.Argonaut.Generic.Encode (genericEncodeJson)
import Data.Maybe (fromMaybe)
import Guide.CategoryOverview.Events (AppEffects, Event(..), foldp) as CO
import Guide.CategoryOverview.Routes (Route(..), match) as CO
import Guide.CategoryOverview.State (State(..), init) as CO
import Guide.CategoryOverview.View.Layout (view) as CO
import Guide.CategoryDetail.Events (AppEffects, Event(..), foldp) as CD
import Guide.CategoryDetail.Routes (Route(..), match) as CD
import Guide.CategoryDetail.State (State(..), init) as CD
import Guide.CategoryDetail.View.Layout (view) as CD
import Guide.Server.Common (renderPage)
import Guide.Server.Constants (defaultCategoryName)
import Guide.Server.HTMLWrapper (htmlWrapper)
import Guide.Server.Types (PageConfig(..))
import Node.Express.Handler (HandlerM, Handler)
import Node.Express.Request (getOriginalUrl, getRouteParam)
import Node.Express.Request (getOriginalUrl)
import Node.Express.Response (redirect, send, sendJson, setStatus)
import Node.Express.Types (EXPRESS)
import Pux (CoreEffects, start, waitState)
@ -63,11 +64,31 @@ categoryDetailHandler = do
send html
categoryOverviewHandler :: forall e. HandlerM (express :: EXPRESS | e) Unit
categoryOverviewHandler :: forall e. Handler (CoreEffects (CO.AppEffects e))
categoryOverviewHandler = do
catName <- fromMaybe defaultCategoryName <$> getRouteParam "name"
renderPage $ PageConfig { contentId: "category-overview"
, title: "Aelve - Guide: Category " <> catName
, catName
, catDetailId: "0"
}
let getState (CO.State st) = st
url <- getOriginalUrl
app <- liftEff $ start
{ initialState: CO.init url
, view: CO.view
, foldp: CO.foldp
, inputs: [constant (CO.PageView (CO.match url))]
}
state <- liftAff $ waitState (\(CO.State st) -> st.loaded) app
case (getState state).route of
(CO.NotFound _) -> setStatus 404
_ -> setStatus 200
html <- liftEff do
let state_json = "window.__puxInitialState = "
<> (show $ genericEncodeJson options state)
<> ";"
app_html <- renderToString app.markup
renderToStaticMarkup $ constant (htmlWrapper app_html state_json "category-overview")
send html

View File

@ -1 +0,0 @@
module Guide.Server.Types where

View File

@ -33,7 +33,7 @@ appSetup = do
get "/" indexHandler
get "/category/:name/" categoryOverviewHandler
get "/category/:name/detail/:id" categoryDetailHandler
get "/category/:name/:id" categoryDetailHandler
useOnError errorHandler