diff options
Diffstat (limited to 'Handler/List.hs')
-rw-r--r-- | Handler/List.hs | 71 |
1 files changed, 71 insertions, 0 deletions
diff --git a/Handler/List.hs b/Handler/List.hs new file mode 100644 index 0000000..cfd3f7c --- /dev/null +++ b/Handler/List.hs | |||
@@ -0,0 +1,71 @@ | |||
1 | {-# LANGUAGE ApplicativeDo #-} | ||
2 | {-# LANGUAGE OverloadedLists #-} | ||
3 | |||
4 | module Handler.List where | ||
5 | |||
6 | import Import | ||
7 | |||
8 | import Data.Set (Set) | ||
9 | import qualified Data.Set as Set | ||
10 | |||
11 | import Data.Map (Map) | ||
12 | import qualified Data.Map as Map | ||
13 | |||
14 | import qualified Data.Text as Text | ||
15 | import qualified Data.Text.Lazy as Lazy.Text | ||
16 | |||
17 | import Database.Persist.Sql (Single(..), rawSql) | ||
18 | |||
19 | import Thermoprint.Client | ||
20 | |||
21 | list :: Handler (Set Text) | ||
22 | list = do | ||
23 | (map unSingle -> kinds) <- runDB $ rawSql "select reference.kind from reference where not exists (select * from item where COALESCE(item.expires >= CURRENT_DATE, TRUE) and (item.norm_kind = reference.norm_kind)) " [] | ||
24 | return $ Set.fromList kinds | ||
25 | |||
26 | mkPrintout :: Set Text -> Printout | ||
27 | mkPrintout list = Printout | ||
28 | [ Paragraph | ||
29 | [Cooked . either id Line . text . Lazy.Text.fromStrict . Text.unlines . map (" - " <>) $ Set.toAscList list | ||
30 | ] | ||
31 | ] | ||
32 | |||
33 | getListR, postListR :: Handler TypedContent | ||
34 | getListR = postListR | ||
35 | postListR = do | ||
36 | Client{..} <- mkClient' . appThermoprintBase . appSettings <$> getYesod | ||
37 | let | ||
38 | formatPrinter (pId@(PrinterId num), pStatus) = | ||
39 | ("Printer #" <> tshow num <> " – " <> tshow pStatus, pId) | ||
40 | printers' <- map formatPrinter . Map.toAscList <$> printers | ||
41 | list <- list | ||
42 | |||
43 | ((printResult, printView), printEnc) <- runFormPost . renderDivsNoLabels $ do | ||
44 | pId <- case printers' of | ||
45 | [(_, pId)] -> pure pId | ||
46 | _ -> areq (selectFieldList printers') "Printer" . listToMaybe $ map snd printers' | ||
47 | pure pId | ||
48 | |||
49 | case printResult of | ||
50 | FormSuccess pId -> do | ||
51 | (JobId jId) <- jobCreate (Just pId) $ mkPrintout list | ||
52 | addMessage "printSuccess" . toHtml $ "List is printing as job #" <> tshow jId | ||
53 | FormFailure errors -> mapM_ (addMessage "formError" . toHtml) errors | ||
54 | _ -> return () | ||
55 | |||
56 | selectRep $ do | ||
57 | provideJson list | ||
58 | provideRep . defaultLayout $ | ||
59 | [whamlet| | ||
60 | <div .table .main> | ||
61 | <div .tr .sepBelow> | ||
62 | <div .th>Item | ||
63 | $forall item <- Set.toAscList list | ||
64 | <div .tr .color> | ||
65 | <div .kind>#{item} | ||
66 | <form .tr .sepAbove method=post action=@{ListR} enctype=#{printEnc}> | ||
67 | <div .td> | ||
68 | ^{printView} | ||
69 | <button type=submit :Set.null list:disabled> | ||
70 | |||
71 | |] | ||