diff options
| -rw-r--r-- | Handler/List.hs | 60 | ||||
| -rw-r--r-- | templates/default-layout.cassius | 2 | ||||
| -rw-r--r-- | templates/list.cassius | 4 | ||||
| -rw-r--r-- | templates/list.hamlet | 28 |
4 files changed, 70 insertions, 24 deletions
diff --git a/Handler/List.hs b/Handler/List.hs index 8f9e777..2fd745d 100644 --- a/Handler/List.hs +++ b/Handler/List.hs | |||
| @@ -1,4 +1,3 @@ | |||
| 1 | {-# LANGUAGE ApplicativeDo #-} | ||
| 2 | {-# LANGUAGE OverloadedLists #-} | 1 | {-# LANGUAGE OverloadedLists #-} |
| 3 | 2 | ||
| 4 | module Handler.List where | 3 | module Handler.List where |
| @@ -50,17 +49,31 @@ getListR, postListR :: Handler TypedContent | |||
| 50 | getListR = postListR | 49 | getListR = postListR |
| 51 | postListR = do | 50 | postListR = do |
| 52 | Client{..} <- mkClient' . appThermoprintBase . appSettings <$> getYesod | 51 | Client{..} <- mkClient' . appThermoprintBase . appSettings <$> getYesod |
| 52 | |||
| 53 | let | 53 | let |
| 54 | formatPrinter (pId@(PrinterId num), pStatus) = | 54 | formatPrinter (pId@(PrinterId num), pStatus) = |
| 55 | ("Printer #" <> tshow num <> " – " <> tshow pStatus, pId) | 55 | ("Printer #" <> tshow num <> " – " <> tshow pStatus, pId) |
| 56 | printers' <- map formatPrinter . Map.toAscList <$> printers | 56 | printers' <- map formatPrinter . Map.toAscList <$> printers |
| 57 | |||
| 58 | let | ||
| 59 | formatDraft (dId@(DraftId num), Nothing) = | ||
| 60 | ("Draft #" <> tshow num, dId) | ||
| 61 | formatDraft (dId@(DraftId num), Just t) = | ||
| 62 | (t <> " (" <> tshow num <> ")", dId) | ||
| 63 | drafts' <- map formatDraft . Map.toAscList <$> drafts | ||
| 64 | |||
| 57 | list <- list | 65 | list <- list |
| 58 | 66 | ||
| 59 | ((printResult, printView), printEnc) <- runFormPost . renderDivsNoLabels $ do | 67 | ((printResult, printView), printEnc) <- runFormPost . identifyForm "print" . renderDivsNoLabels |
| 60 | pId <- case printers' of | 68 | $ case printers' of |
| 61 | [(_, pId)] -> pure pId | 69 | [(_, pId)] -> pure pId |
| 62 | _ -> areq (selectFieldList printers') "Printer" . listToMaybe $ map snd printers' | 70 | _ -> areq (selectFieldList printers') "Printer" . listToMaybe $ map snd printers' |
| 63 | pure pId | 71 | |
| 72 | ((oDraftResult, oDraftView), oDraftEnc) <- runFormPost . identifyForm "oldDraft" . renderDivsNoLabels | ||
| 73 | $ areq (selectFieldList drafts') "Draft" Nothing | ||
| 74 | |||
| 75 | ((nDraftResult, nDraftView), nDraftEnc) <- runFormPost . identifyForm "newDraft" . renderDivsNoLabels | ||
| 76 | $ areq textField "Title" Nothing | ||
| 64 | 77 | ||
| 65 | case printResult of | 78 | case printResult of |
| 66 | FormSuccess pId -> do | 79 | FormSuccess pId -> do |
| @@ -68,23 +81,24 @@ postListR = do | |||
| 68 | addMessage "printSuccess" [shamlet|List is printing as job ##{jId}|] | 81 | addMessage "printSuccess" [shamlet|List is printing as job ##{jId}|] |
| 69 | FormFailure errors -> mapM_ (addMessage "formError" . toHtml) errors | 82 | FormFailure errors -> mapM_ (addMessage "formError" . toHtml) errors |
| 70 | _ -> return () | 83 | _ -> return () |
| 84 | |||
| 85 | case oDraftResult of | ||
| 86 | FormSuccess dId@(DraftId num) -> do | ||
| 87 | (t, printout) <- draft dId | ||
| 88 | let t' = fromMaybe "" t | ||
| 89 | draftReplace dId t $ printout `mappend` mkPrintout list | ||
| 90 | addMessage "appendSuccess" [shamlet|Appended shopping list to ‘#{t'}’ (#{num})|] | ||
| 91 | FormFailure errors -> mapM_ (addMessage "formError" . toHtml) errors | ||
| 92 | _ -> return () | ||
| 93 | |||
| 94 | case nDraftResult of | ||
| 95 | FormSuccess (Text.strip -> t) -> do | ||
| 96 | let t' = t <$ guard (not $ Text.null t) | ||
| 97 | (DraftId num) <- draftCreate t' $ mkPrintout list | ||
| 98 | addMessage "saveSuccess" [shamlet|Saved shopping list as ‘#{t}’ (#{num})|] | ||
| 99 | FormFailure errors -> mapM_ (addMessage "formError" . toHtml) errors | ||
| 100 | _ -> return () | ||
| 71 | 101 | ||
| 72 | selectRep $ do | 102 | selectRep $ do |
| 73 | provideJson $ typeToJSON "item" <$> Set.toAscList list | 103 | provideJson $ typeToJSON "item" <$> Set.toAscList list |
| 74 | provideRep . defaultLayout $ | 104 | provideRep . defaultLayout $ $(widgetFile "list") |
| 75 | [whamlet| | ||
| 76 | <table .main> | ||
| 77 | <tr .sepBelow> | ||
| 78 | <th>Item | ||
| 79 | <th>Type | ||
| 80 | $forall WithType item itemType <- Set.toAscList list | ||
| 81 | <tr .color> | ||
| 82 | <td .kind>#{item} | ||
| 83 | <td .type>#{itemType} | ||
| 84 | <tr .sepAbove> | ||
| 85 | <td colspan=2> | ||
| 86 | <form method=post action=@{ListR} enctype=#{printEnc}> | ||
| 87 | ^{printView} | ||
| 88 | <button type=submit :Set.null list:disabled> | ||
| 89 | |||
| 90 | |] | ||
diff --git a/templates/default-layout.cassius b/templates/default-layout.cassius index 31389d8..e3aaa52 100644 --- a/templates/default-layout.cassius +++ b/templates/default-layout.cassius | |||
| @@ -47,7 +47,7 @@ table table td, table table th, .table table td, .table table th | |||
| 47 | margin: 0 | 47 | margin: 0 |
| 48 | .formError | 48 | .formError |
| 49 | color: #800 | 49 | color: #800 |
| 50 | .printSuccess, .insertSuccess | 50 | .printSuccess, .insertSuccess, .appendSuccess, .saveSuccess |
| 51 | color: #080 | 51 | color: #080 |
| 52 | .insertAmbiguous | 52 | .insertAmbiguous |
| 53 | color: inherit | 53 | color: inherit |
diff --git a/templates/list.cassius b/templates/list.cassius new file mode 100644 index 0000000..5a4c58d --- /dev/null +++ b/templates/list.cassius | |||
| @@ -0,0 +1,4 @@ | |||
| 1 | #listActions form | ||
| 2 | display: block | ||
| 3 | div | ||
| 4 | display: inline-block \ No newline at end of file | ||
diff --git a/templates/list.hamlet b/templates/list.hamlet new file mode 100644 index 0000000..a69ef1d --- /dev/null +++ b/templates/list.hamlet | |||
| @@ -0,0 +1,28 @@ | |||
| 1 | <div .table .main> | ||
| 2 | <div .tr .sepBelow> | ||
| 3 | <div .td>Item | ||
| 4 | <div .td>Type | ||
| 5 | $forall WithType item itemType <- Set.toAscList list | ||
| 6 | <div .tr .color> | ||
| 7 | <div .td .kind>#{item} | ||
| 8 | <div .td .type>#{itemType} | ||
| 9 | <form method=post enctype=#{nDraftEnc} .sepAbove .tr> | ||
| 10 | <div .td> | ||
| 11 | ^{nDraftView} | ||
| 12 | <div .td> | ||
| 13 | <button type=submit :Set.null list:disabled> | ||
| 14 | Save | ||
| 15 | $if not (null drafts') | ||
| 16 | <form method=post enctype=#{oDraftEnc} .tr> | ||
| 17 | <div .td> | ||
| 18 | ^{oDraftView} | ||
| 19 | <div .td> | ||
| 20 | <button type=submit :Set.null list:disabled> | ||
| 21 | Append | ||
| 22 | $if not (null printers') | ||
| 23 | <form method=post enctype=#{printEnc} .tr> | ||
| 24 | <div .td> | ||
| 25 | ^{printView} | ||
| 26 | <div .td> | ||
| 27 | <button type=submit :Set.null list:disabled> | ||
| 28 | |||
