render conditional html in lazy thunks

This commit is contained in:
Jon Schoning 2019-03-07 21:43:47 -06:00
parent cbf90cdbb6
commit 33eaa42628
8 changed files with 121 additions and 116 deletions

View file

@ -15,11 +15,11 @@ import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Globals (app', closeWindow, mmoment8601) import Globals (app', closeWindow, mmoment8601)
import Halogen as H import Halogen as H
import Halogen.HTML (HTML, br_, button, div, div_, form, input, label, p, span, table, tbody_, td, td_, text, textarea, tr_) import Halogen.HTML (HTML, br_, button, div, form, input, label, p, span, table, tbody_, td, td_, text, textarea, tr_)
import Halogen.HTML.Events (onSubmit, onValueChange, onChecked, onClick) import Halogen.HTML.Events (onSubmit, onValueChange, onChecked, onClick)
import Halogen.HTML.Properties (autofocus, ButtonType(..), InputType(..), autocomplete, checked, for, id_, name, required, rows, title, type_, value) import Halogen.HTML.Properties (autofocus, ButtonType(..), InputType(..), autocomplete, checked, for, id_, name, required, rows, title, type_, value)
import Model (Bookmark) import Model (Bookmark)
import Util (_curQuerystring, _loc, _lookupQueryStringValue, attr, class_) import Util (_curQuerystring, _loc, _lookupQueryStringValue, attr, class_, ifElseH, whenH)
import Web.Event.Event (Event, preventDefault) import Web.Event.Event (Event, preventDefault)
import Web.HTML (window) import Web.HTML (window)
import Web.HTML.Location (setHref) import Web.HTML.Location (setHref)
@ -70,15 +70,19 @@ addbmark b' =
render :: forall m. BState -> H.ComponentHTML BAction () m render :: forall m. BState -> H.ComponentHTML BAction () m
render s@{ bm, edit_bm } = render s@{ bm, edit_bm } =
div_ [ if not s.destroyed then display_edit else display_destroyed ] ifElseH (not s.destroyed)
display_edit
display_destroyed
where where
display_edit = display_edit _ =
form [ onSubmit (Just <<< BEditSubmit) ] form [ onSubmit (Just <<< BEditSubmit) ]
[ table [ class_ "w-100" ] [ table [ class_ "w-100" ]
[ tbody_ [ tbody_
[ tr_ [ tr_
[ td [ class_ "w1" ] [ ] [ td [ class_ "w1" ] [ ]
, td_ $ guard (bm.bid > 0) [ display_exists ] , td_ [ whenH (bm.bid > 0)
display_exists
]
] ]
, tr_ , tr_
[ td_ [ label [ for "url" ] [ text "URL" ] ] [ td_ [ label [ for "url" ] [ text "URL" ] ]
@ -119,7 +123,7 @@ addbmark b' =
] ]
] ]
display_exists = display_exists _ =
div [ class_ "alert" ] div [ class_ "alert" ]
[ text "previously saved " [ text "previously saved "
, span [ class_ "link f7 dib gray pr3" , title (maybe bm.time snd mmoment) ] , span [ class_ "link f7 dib gray pr3" , title (maybe bm.time snd mmoment) ]
@ -135,7 +139,7 @@ addbmark b' =
] ]
] ]
display_destroyed = p [ class_ "red"] [text "you killed this bookmark"] display_destroyed _ = p [ class_ "red"] [text "you killed this bookmark"]
editField :: forall a. (a -> EditField) -> a -> Maybe BAction editField :: forall a. (a -> EditField) -> a -> Maybe BAction
editField f = Just <<< BEditField <<< f editField f = Just <<< BEditField <<< f

View file

@ -5,25 +5,25 @@ import Prelude hiding (div)
import App (StarAction(..), destroy, editBookmark, markRead, toggleStar) import App (StarAction(..), destroy, editBookmark, markRead, toggleStar)
import Component.Markdown as Markdown import Component.Markdown as Markdown
import Data.Array (drop, foldMap) import Data.Array (drop, foldMap)
import Data.Const (Const)
import Data.Lens (Lens', lens, use, (%=), (.=)) import Data.Lens (Lens', lens, use, (%=), (.=))
import Data.Maybe (Maybe(..), fromMaybe, isJust, maybe) import Data.Maybe (Maybe(..), fromMaybe, isJust, maybe)
import Data.Monoid (guard) import Data.Monoid (guard)
import Data.Nullable (toMaybe) import Data.Nullable (toMaybe)
import Data.String (null, split, take) as S import Data.String (null, split, take) as S
import Data.String.Pattern (Pattern(..)) import Data.String.Pattern (Pattern(..))
import Data.Symbol (SProxy(..))
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Globals (app', mmoment8601) import Globals (app', mmoment8601)
import Halogen as H import Halogen as H
import Halogen.HTML as HH
import Halogen.HTML (HTML, a, br_, button, div, div_, form, input, label, span, text, textarea) import Halogen.HTML (HTML, a, br_, button, div, div_, form, input, label, span, text, textarea)
import Halogen.HTML as HH
import Halogen.HTML.Events (onSubmit, onValueChange, onChecked, onClick) import Halogen.HTML.Events (onSubmit, onValueChange, onChecked, onClick)
import Halogen.HTML.Properties (ButtonType(..), InputType(..), autocomplete, checked, for, href, id_, name, required, rows, target, title, type_, value) import Halogen.HTML.Properties (ButtonType(..), InputType(..), autocomplete, checked, for, href, id_, name, required, rows, target, title, type_, value)
import Model (Bookmark) import Model (Bookmark)
import Data.Symbol (SProxy(..)) import Util (attr, class_, fromNullableStr, ifElseH, whenH, whenA)
import Util (class_, attr, fromNullableStr)
import Web.Event.Event (Event, preventDefault) import Web.Event.Event (Event, preventDefault)
import Data.Const (Const)
-- | UI Events -- | UI Events
data BAction data BAction
@ -55,7 +55,6 @@ type BState =
, edit_bm :: Bookmark , edit_bm :: Bookmark
, deleteAsk:: Boolean , deleteAsk:: Boolean
, edit :: Boolean , edit :: Boolean
, isMarkdown :: Boolean
} }
_bm :: Lens' BState Bookmark _bm :: Lens' BState Bookmark
@ -88,26 +87,26 @@ bmark b' =
, edit_bm: b , edit_bm: b
, deleteAsk: false , deleteAsk: false
, edit: false , edit: false
, isMarkdown: true
} }
render :: BState -> H.ComponentHTML BAction ChildSlots Aff render :: BState -> H.ComponentHTML BAction ChildSlots Aff
render s@{ bm, edit_bm } = render s@{ bm, edit_bm } =
div [ id_ (show bm.bid) , class_ ("bookmark w-100 mw7 pa1 mb3" <> guard bm.private " private")] $ div [ id_ (show bm.bid) , class_ ("bookmark w-100 mw7 pa1 mb3" <> guard bm.private " private")] $
star <> [ whenH app.dat.isowner
if s.edit star
then display_edit , ifElseH s.edit
else display display_edit
where display
star =
guard app.dat.isowner
[ div [ class_ ("star fl pointer" <> guard bm.selected " selected") ]
[ button [ class_ "moon-gray", onClick \_ -> Just (BStar (not bm.selected)) ] [ text "✭" ] ]
] ]
display = where
[ div [ class_ "display" ] $
star _ =
div [ class_ ("star fl pointer" <> guard bm.selected " selected") ]
[ button [ class_ "moon-gray", onClick \_ -> Just (BStar (not bm.selected)) ] [ text "✭" ] ]
display _ =
div [ class_ "display" ] $
[ a [ href bm.url, target "_blank", class_ ("link f5 lh-title" <> guard bm.toread " unread")] [ a [ href bm.url, target "_blank", class_ ("link f5 lh-title" <> guard bm.toread " unread")]
[ text $ if S.null bm.title then "[no title]" else bm.title ] [ text $ if S.null bm.title then "[no title]" else bm.title ]
, br_ , br_
@ -117,24 +116,40 @@ bmark b' =
, target "_blank", title "archive link"] , target "_blank", title "archive link"]
[ if isJust (toMaybe bm.archiveUrl) then text "☑" else text "☐" ] [ if isJust (toMaybe bm.archiveUrl) then text "☑" else text "☐" ]
, br_ , br_
-- , div [ class_ "description mt1 mid-gray" ] [ HH.slot _markdown unit Markdown.component bm.description absurd ]
, if s.isMarkdown
then div [ class_ "description mt1 mid-gray" ] [ HH.slot _markdown unit Markdown.component bm.description absurd ]
else div [ class_ "description mt1 mid-gray" ] (toTextarea bm.description)
, div [ class_ "tags" ] $ , div [ class_ "tags" ] $
guard (not (S.null bm.tags)) whenA (not (S.null bm.tags)) $ \_ ->
map (\tag -> a [ class_ ("link tag mr1" <> guard (S.take 1 tag == ".") " private") map (\tag -> a [ class_ ("link tag mr1" <> guard (S.take 1 tag == ".") " private")
, href (linkToFilterTag tag) ] , href (linkToFilterTag tag) ]
[ text tag ]) [ text tag ])
(S.split (Pattern " ") bm.tags) (S.split (Pattern " ") bm.tags)
, a [ class_ "link f7 dib gray w4", title (maybe bm.time snd mmoment) , href (linkToFilterSingle bm.slug) ] , a [ class_ "link f7 dib gray w4", title (maybe bm.time snd mmoment) , href (linkToFilterSingle bm.slug) ]
[ text (maybe " " fst mmoment) ] [ text (maybe " " fst mmoment) ]
-- links
, whenH app.dat.isowner $ \_ ->
div [ class_ "edit_links di" ]
[ button [ type_ ButtonButton, onClick \_ -> Just (BEdit true), class_ "edit light-silver hover-blue" ] [ text "edit  " ]
, div [ class_ "delete_link di" ]
[ button [ type_ ButtonButton, onClick \_ -> Just (BDeleteAsk true), class_ ("delete light-silver hover-blue" <> guard s.deleteAsk " dn") ] [ text "delete" ]
, span ([ class_ ("confirm red" <> guard (not s.deleteAsk) " dn") ] )
[ button [ type_ ButtonButton, onClick \_ -> Just (BDeleteAsk false)] [ text "cancel / " ]
, button [ type_ ButtonButton, onClick \_ -> Just BDestroy, class_ "red" ] [ text "destroy" ]
]
]
]
, whenH app.dat.isowner $ \_ ->
div [ class_ "read di" ] $
guard bm.toread
[ text "  "
, button [ onClick \_ -> Just BMarkRead, class_ "mark_read" ] [ text "mark as read"]
] ]
<> links
] ]
display_edit =
[ div [ class_ "edit_bookmark_form pa2 pt0 bg-white" ] $ display_edit _ =
div [ class_ "edit_bookmark_form pa2 pt0 bg-white" ] $
[ form [ onSubmit (Just <<< BEditSubmit) ] [ form [ onSubmit (Just <<< BEditSubmit) ]
[ div_ [ text "url" ] [ div_ [ text "url" ]
, input [ type_ InputUrl , class_ "url w-100 mb2 pt1 f7 edit_form_input" , required true , name "url" , input [ type_ InputUrl , class_ "url w-100 mb2 pt1 f7 edit_form_input" , required true , name "url"
@ -173,26 +188,7 @@ bmark b' =
, onClick \_ -> Just (BEdit false) ] , onClick \_ -> Just (BEdit false) ]
] ]
] ]
]
links =
guard app.dat.isowner
[ div [ class_ "edit_links di" ]
[ button [ type_ ButtonButton, onClick \_ -> Just (BEdit true), class_ "edit light-silver hover-blue" ] [ text "edit  " ]
, div [ class_ "delete_link di" ]
[ button [ type_ ButtonButton, onClick \_ -> Just (BDeleteAsk true), class_ ("delete light-silver hover-blue" <> guard s.deleteAsk " dn") ] [ text "delete" ]
, span ([ class_ ("confirm red" <> guard (not s.deleteAsk) " dn") ] )
[ button [ type_ ButtonButton, onClick \_ -> Just (BDeleteAsk false)] [ text "cancel / " ]
, button [ type_ ButtonButton, onClick \_ -> Just BDestroy, class_ "red" ] [ text "destroy" ]
]
]
]
, div [ class_ "read di" ] $
guard bm.toread
[ text "  "
, button [ onClick \_ -> Just BMarkRead, class_ "mark_read" ] [ text "mark as read"]
]
]
editField :: forall a. (a -> EditField) -> a -> Maybe BAction editField :: forall a. (a -> EditField) -> a -> Maybe BAction
editField f = Just <<< BEditField <<< f editField f = Just <<< BEditField <<< f

View file

@ -21,7 +21,7 @@ import Halogen.HTML as HH
import Halogen.HTML.Events (onChecked, onClick, onSubmit, onValueChange) import Halogen.HTML.Events (onChecked, onClick, onSubmit, onValueChange)
import Halogen.HTML.Properties (ButtonType(..), InputType(..), checked, for, id_, name, rows, title, type_, value) import Halogen.HTML.Properties (ButtonType(..), InputType(..), checked, for, id_, name, rows, title, type_, value)
import Model (Note) import Model (Note)
import Util (_loc, class_, fromNullableStr) import Util (_loc, class_, fromNullableStr, ifElseH)
import Web.Event.Event (Event, preventDefault) import Web.Event.Event (Event, preventDefault)
import Web.HTML.Location (setHref) import Web.HTML.Location (setHref)
import Data.Symbol (SProxy(..)) import Data.Symbol (SProxy(..))
@ -83,15 +83,14 @@ nnote st' =
render :: NState -> H.ComponentHTML NAction ChildSlots Aff render :: NState -> H.ComponentHTML NAction ChildSlots Aff
render st@{ note, edit_note } = render st@{ note, edit_note } =
if st.destroyed ifElseH st.destroyed
then display_destroyed display_destroyed
else (const (ifElseH st.edit
if st.edit renderNote_edit
then renderNote_edit renderNote))
else renderNote
where where
renderNote = renderNote _ =
div [ id_ (show note.id) , class_ ("note w-100 mw7 pa1 mb2")] $ div [ id_ (show note.id) , class_ ("note w-100 mw7 pa1 mb2")] $
[ div [ class_ "display" ] $ [ div [ class_ "display" ] $
[ div [ class_ ("link f5 lh-title")] [ div [ class_ ("link f5 lh-title")]
@ -117,7 +116,7 @@ nnote st' =
] ]
] ]
renderNote_edit = renderNote_edit _ =
form [ onSubmit (Just <<< NEditSubmit) ] form [ onSubmit (Just <<< NEditSubmit) ]
[ p [ class_ "mt2 mb1"] [ text "title:" ] [ p [ class_ "mt2 mb1"] [ text "title:" ]
, input [ type_ InputText , class_ "title w-100 mb1 pt1 f7 edit_form_input" , name "title" , input [ type_ InputText , class_ "title w-100 mb1 pt1 f7 edit_form_input" , name "title"
@ -142,7 +141,7 @@ nnote st' =
] ]
] ]
display_destroyed = p [ class_ "red"] [text "you killed this note"] display_destroyed _ = p [ class_ "red"] [text "you killed this note"]
mmoment n = mmoment8601 n.created mmoment n = mmoment8601 n.created
editField :: forall a. (a -> EditField) -> a -> Maybe NAction editField :: forall a. (a -> EditField) -> a -> Maybe NAction

View file

@ -129,6 +129,12 @@ whenC b c = if b then c else ClassName ""
whenH :: forall p i. Boolean -> (Unit -> HH.HTML p i) -> HH.HTML p i whenH :: forall p i. Boolean -> (Unit -> HH.HTML p i) -> HH.HTML p i
whenH b k = if b then k unit else HH.text "" whenH b k = if b then k unit else HH.text ""
whenA :: forall t. Boolean -> (Unit -> Array t) -> Array t
whenA b k = if b then k unit else []
ifElseH :: forall p i. Boolean -> (Unit -> HH.HTML p i) -> (Unit -> HH.HTML p i) -> HH.HTML p i
ifElseH b f k = if b then f unit else k unit
maybeH :: forall a p i. Maybe a -> (a -> HH.HTML p i) -> HH.HTML p i maybeH :: forall a p i. Maybe a -> (a -> HH.HTML p i) -> HH.HTML p i
maybeH m k = maybe (HH.text "") k m maybeH m k = maybe (HH.text "") k m

File diff suppressed because one or more lines are too long

Binary file not shown.

File diff suppressed because one or more lines are too long

Binary file not shown.