summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2017-03-16 13:18:34 +0100
committerGregor Kleen <gkleen@yggdrasil.li>2017-03-16 13:18:34 +0100
commit57d594818c14652681dce54d324b6b76941b2f4e (patch)
treef3e1e02e2fa41ff0d87eace034d6c883668841c5
parent3d828feba67f21ae62d1e6eb598a22ffaebf1174 (diff)
parent3bfe0bdcb79b398a387e202c5150b5e6fd230d3a (diff)
downloadbar-57d594818c14652681dce54d324b6b76941b2f4e.tar
bar-57d594818c14652681dce54d324b6b76941b2f4e.tar.gz
bar-57d594818c14652681dce54d324b6b76941b2f4e.tar.bz2
bar-57d594818c14652681dce54d324b6b76941b2f4e.tar.xz
bar-57d594818c14652681dce54d324b6b76941b2f4e.zip
Merge branch 'feat/openYes'
-rw-r--r--Handler/Common.hs102
-rw-r--r--Handler/List.hs20
-rw-r--r--Handler/OpenItem.hs2
-rw-r--r--Import/NoFoundation.hs1
-rw-r--r--Model.hs33
-rw-r--r--Model/Types.hs35
-rw-r--r--bar.cabal3
-rw-r--r--bar.nix2
-rw-r--r--config/models6
-rw-r--r--templates/default-layout.cassius2
-rw-r--r--templates/inventoryListing.cassius3
-rw-r--r--templates/inventoryListing.hamlet33
12 files changed, 178 insertions, 64 deletions
diff --git a/Handler/Common.hs b/Handler/Common.hs
index c2788e8..65e6ce1 100644
--- a/Handler/Common.hs
+++ b/Handler/Common.hs
@@ -34,6 +34,10 @@ import Database.Persist.Sql (fromSqlKey)
34import qualified Web.Hashids as HID 34import qualified Web.Hashids as HID
35import Data.List ((\\)) 35import Data.List ((\\))
36 36
37import Data.List.NonEmpty (NonEmpty)
38import Data.Semigroup hiding (First(..))
39import Data.Monoid (First(..))
40
37humanId :: ItemId -> Text 41humanId :: ItemId -> Text
38humanId = Text.pack . CBS.unpack . HID.encode ctx . fromIntegral . fromSqlKey 42humanId = Text.pack . CBS.unpack . HID.encode ctx . fromIntegral . fromSqlKey
39 where 43 where
@@ -42,6 +46,12 @@ humanId = Text.pack . CBS.unpack . HID.encode ctx . fromIntegral . fromSqlKey
42dayFormat :: Day -> String 46dayFormat :: Day -> String
43dayFormat = formatTime defaultTimeLocale "%e. %b %y" 47dayFormat = formatTime defaultTimeLocale "%e. %b %y"
44 48
49data DayFormConfig = DayFormConfig
50 { dfNever :: Bool
51 , dfUnknown :: Bool
52 , dfKnown :: Bool
53 }
54
45itemForm :: Maybe Item -- ^ Update existing item or insert new? 55itemForm :: Maybe Item -- ^ Update existing item or insert new?
46 -> Html -> MForm Handler (FormResult (WithType Item), Widget) 56 -> Html -> MForm Handler (FormResult (WithType Item), Widget)
47itemForm proto identView = do 57itemForm proto identView = do
@@ -52,12 +62,12 @@ itemForm proto identView = do
52 let kt kWidget tWidget = 62 let kt kWidget tWidget =
53 [whamlet| 63 [whamlet|
54 <div .td>^{kWidget} 64 <div .td>^{kWidget}
55 <div .td>^{tWidget} 65 <div .td>^{tWidget}
56 |] 66 |]
57 ((kindRes, typeRes), typedKindWidget) <- typedKindField kt ((itemKind <$> proto), t) 67 ((kindRes, typeRes), typedKindWidget) <- typedKindField kt ((itemKind <$> proto), t)
58 (boughtRes, boughtWidget) <- dayForm (maybe (Just $ Just today) Just $ fmap itemBought proto) "Unknown" 68 (boughtRes, boughtWidget) <- dayForm (Just . fromMaybe (DateKnown today) $ itemBought <$> proto) $ DayFormConfig False True True
59 (expiresRes, expiresWidget) <- dayForm (fmap itemExpires proto) "Never" 69 (expiresRes, expiresWidget) <- dayForm (itemExpires <$> proto) $ DayFormConfig True False True
60 (openedRes, openedWidget) <- dayForm (fmap itemOpened proto) "Never" 70 (openedRes, openedWidget) <- dayForm (itemOpened <$> proto) $ DayFormConfig True True True
61 71
62 let itemRes = do 72 let itemRes = do
63 itemKind <- kindRes 73 itemKind <- kindRes
@@ -77,33 +87,79 @@ itemForm proto identView = do
77 <div .td>^{openedWidget} 87 <div .td>^{openedWidget}
78 |] 88 |]
79 where 89 where
80 dayForm :: Maybe (Maybe Day) -> String -> MForm Handler (FormResult (Maybe Day), Widget) 90 dayForm :: Maybe ItemDate -> DayFormConfig -> MForm Handler (FormResult ItemDate, Widget)
81 dayForm proto label = do 91 dayForm proto DayFormConfig{..} = do
82 today <- utctDay <$> liftIO getCurrentTime 92 today <- utctDay <$> liftIO getCurrentTime
83 93
84 checkboxId <- ("check" <>) . show . hashUnique <$> liftIO newUnique 94 let mWhen = bool (Nothing <$) (fmap Just)
85
86 (fmap (fromMaybe False) -> isNothingRes, isNothingView) <-
87 mopt checkBoxField ("" { fsId = Just $ Text.pack checkboxId }) . Just . Just . fromMaybe True $ fmap isNothing proto
88 (dayRes, dayView) <-
89 mreq dayField "" . Just . fromMaybe today $ join proto
90 95
91 let res = (bool Just (const Nothing) <$> isNothingRes) <*> dayRes 96 neverBoxId <- ("check" <>) . show . hashUnique <$> liftIO newUnique
97 unknownBoxId <- ("check" <>) . show . hashUnique <$> liftIO newUnique
98 groupId <- ("dateGroup" <>) . show . hashUnique <$> liftIO newUnique
99
100 dNever <- mWhen dfNever $
101 mopt checkBoxField ("" { fsId = Just $ Text.pack neverBoxId }) . Just . Just . fromMaybe True $ fmap isNever proto
102 dUnknown <- mWhen dfUnknown $
103 mopt checkBoxField ("" { fsId = Just $ Text.pack unknownBoxId }) . Just . Just . fromMaybe False $ fmap isUnknown proto
104 dDay <- mWhen dfKnown $
105 mopt dayField "" . Just . Just $ case proto of
106 Just (DateKnown d) -> d
107 _ -> today
108
109 let res = resFromMaybe . fromMaybe FormMissing . fmap (fmap getFirst) $ mconcat
110 [ fmap (fmap (First . bool Nothing (Just DateNever) . fromMaybe False) . fst) dNever
111 , fmap (fmap (First . bool Nothing (Just DateUnknown) . fromMaybe False) . fst) dUnknown
112 , fmap (fmap (First . fmap DateKnown) . fst) dDay
113 ]
114 resFromMaybe (FormSuccess Nothing) = FormFailure ["Missing required information"]
115 resFromMaybe (FormSuccess (Just x)) = FormSuccess x
116 resFromMaybe FormMissing = FormMissing
117 resFromMaybe (FormFailure es) = FormFailure es
92 return . (res, ) $ do 118 return . (res, ) $ do
119 toWidget $
120 [julius|
121 $(function () {
122 var updateInput = function() {
123 $('##{rawJS groupId} :input').filter(':not(:checkbox)').prop("disabled", $('##{rawJS groupId} :checkbox').filter(':checked').length > 0);
124 };
125
126 $('##{rawJS groupId} :checkbox').change(function() {
127 if (this.checked) {
128 $('##{rawJS groupId} :checkbox').not(this).prop('checked', false);
129 }
130 updateInput();
131 });
132
133 updateInput();
134 });
135 |]
136 let width = length $ (filter id [ isJust dNever, isJust dUnknown ] :: [Bool])
93 [whamlet| 137 [whamlet|
94 $newline never 138 $newline never
95 <div .table> 139 <table ##{groupId} .dayField>
96 <div .tr> 140 <tr>
97 <label for=#{checkboxId} .checkbox .td> 141 $maybe (_, isNeverView) <- dNever
98 ^{fvInput isNothingView} 142 <td>
99 <span> 143 <label for=#{neverBoxId} .checkbox>
100 #{label} 144 ^{fvInput isNeverView}
101 <div .tr> 145 <span>
102 <div .td .dayInput>^{fvInput dayView} 146 Never
147 $maybe (_, isUnknownView) <- dUnknown
148 <td>
149 <label for=#{unknownBoxId} .checkbox>
150 ^{fvInput isUnknownView}
151 <span>
152 Unknown
153 $maybe (_, dayView) <- dDay
154 <tr>
155 <td .dayInput :width > 0:colspan=#{width}>
156 ^{fvInput dayView}
103 |] 157 |]
104 158
105inventoryListing :: InventoryState -> Widget 159inventoryListing :: InventoryState -> Widget
106inventoryListing InventoryState{ invFormState = formState, ..} = $(widgetFile "inventoryListing") 160inventoryListing InventoryState{ invFormState = formState, ..} = do
161 today <- liftIO $ utctDay <$> getCurrentTime
162 $(widgetFile "inventoryListing")
107 163
108referenceForm :: Maybe Reference -- ^ Update existing item or insert new? 164referenceForm :: Maybe Reference -- ^ Update existing item or insert new?
109 -> Html -> MForm Handler (FormResult (WithType Reference), Widget) 165 -> Html -> MForm Handler (FormResult (WithType Reference), Widget)
@@ -199,7 +255,7 @@ kinds = do
199 stock <- runDB $ selectList [] [] 255 stock <- runDB $ selectList [] []
200 reference <- runDB $ selectList [] [] 256 reference <- runDB $ selectList [] []
201 257
202 return . Set.fromList $ concat 258 return . Set.fromList $ (concat :: [[a]] -> [a])
203 [ [ itemKind | Entity _ Item{..} <- stock ] 259 [ [ itemKind | Entity _ Item{..} <- stock ]
204 , [ referenceKind | Entity _ Reference{..} <- reference ] 260 , [ referenceKind | Entity _ Reference{..} <- reference ]
205 ] 261 ]
diff --git a/Handler/List.hs b/Handler/List.hs
index 21b735b..7ab4ebe 100644
--- a/Handler/List.hs
+++ b/Handler/List.hs
@@ -19,9 +19,23 @@ import Database.Persist.Sql (Single(..), rawSql)
19import Thermoprint.Client 19import Thermoprint.Client
20 20
21list :: Handler (Set (WithType Text)) 21list :: Handler (Set (WithType Text))
22list = do 22list = runDB $ do
23 (map (uncurry WithType . bimap unSingle unSingle) -> kinds) <- runDB $ rawSql "select reference.kind, kind.type from reference,kind where (not exists (select * from item where COALESCE(item.expires >= CURRENT_DATE, TRUE) and (item.norm_kind = reference.norm_kind))) and (reference.norm_kind = kind.norm_kind)" [] 23 today <- liftIO $ utctDay <$> getCurrentTime
24 return $ Set.fromList kinds 24
25 items <- map entityVal <$> selectList [] []
26 references <- Set.fromList <$> (withTypes . fmap entityVal =<< selectList [] [])
27
28 let
29 references' = Set.filter (isNothing . flip find items . matches) references
30 matches (Reference{..} `WithType` _) Item{..}
31 | today `isBefore` itemExpires = itemNormKind == referenceNormKind
32 | otherwise = False
33
34 isBefore _ DateNever = True
35 isBefore _ DateUnknown = False
36 isBefore d1 (DateKnown d2) = d1 < d2
37
38 return $ Set.map (fmap referenceKind) references'
25 39
26mkPrintout :: Set (WithType Text) -> Printout 40mkPrintout :: Set (WithType Text) -> Printout
27mkPrintout list = Printout ps 41mkPrintout list = Printout ps
diff --git a/Handler/OpenItem.hs b/Handler/OpenItem.hs
index 468c6ec..3b1dfeb 100644
--- a/Handler/OpenItem.hs
+++ b/Handler/OpenItem.hs
@@ -5,7 +5,7 @@ import Import
5postOpenItemR :: ItemId -> Handler TypedContent 5postOpenItemR :: ItemId -> Handler TypedContent
6postOpenItemR itemId = do 6postOpenItemR itemId = do
7 today <- utctDay <$> liftIO getCurrentTime 7 today <- utctDay <$> liftIO getCurrentTime
8 result <- fmap (Entity itemId) . runDB $ updateGet itemId [ ItemOpened =. Just today 8 result <- fmap (Entity itemId) . runDB $ updateGet itemId [ ItemOpened =. DateKnown today
9 ] 9 ]
10 selectRep $ do 10 selectRep $ do
11 provideJson result 11 provideJson result
diff --git a/Import/NoFoundation.hs b/Import/NoFoundation.hs
index 6872d0a..1a5b107 100644
--- a/Import/NoFoundation.hs
+++ b/Import/NoFoundation.hs
@@ -5,6 +5,7 @@ module Import.NoFoundation
5 5
6import ClassyPrelude.Yesod as Import 6import ClassyPrelude.Yesod as Import
7import Model as Import 7import Model as Import
8import Model.Types as Import
8import Settings as Import 9import Settings as Import
9import Settings.StaticFiles as Import 10import Settings.StaticFiles as Import
10import Yesod.Auth as Import 11import Yesod.Auth as Import
diff --git a/Model.hs b/Model.hs
index 90f5904..8778111 100644
--- a/Model.hs
+++ b/Model.hs
@@ -1,4 +1,5 @@
1{-# LANGUAGE FlexibleInstances #-} 1{-# LANGUAGE FlexibleInstances #-}
2{-# LANGUAGE DeriveFunctor #-}
2 3
3module Model where 4module Model where
4 5
@@ -18,6 +19,8 @@ import qualified Data.HashMap.Lazy as HashMap
18import Data.Aeson 19import Data.Aeson
19import Data.Aeson.Types (Parser, Value(..)) 20import Data.Aeson.Types (Parser, Value(..))
20 21
22import Model.Types
23
21-- You can define all of your database entities in the entities file. 24-- You can define all of your database entities in the entities file.
22-- You can find more information on persistent and how to declare entities 25-- You can find more information on persistent and how to declare entities
23-- at: 26-- at:
@@ -68,32 +71,28 @@ withTypes vals = do
68instance Ord Item where 71instance Ord Item where
69 x `compare` y = mconcat cmprs 72 x `compare` y = mconcat cmprs
70 where 73 where
71 cmprs = [ itemOpened x `compareM` itemOpened y 74 cmprs = [ itemOpened x `compare` itemOpened y
72 , itemExpires x `compareM` itemExpires y 75 , itemExpires x `compare` itemExpires y
73 , itemKind x `compare` itemKind y 76 , itemKind x `compare` itemKind y
74 , itemBought x `compare` itemBought y 77 , itemBought x `compare` itemBought y
75 ] 78 ]
76 79
77 compareM (Just _) Nothing = LT
78 compareM Nothing (Just _) = GT
79 compareM (Just a) (Just b) = compare a b
80 compareM _ _ = EQ
81
82instance ToJSON Item where 80instance ToJSON Item where
83 toJSON Item{..} = object $ 81 toJSON Item{..} = object $
84 [ "kind" .= itemKind 82 [ "kind" .= itemKind
85 ] ++ maybe [] (\x -> ["bought" .= x]) itemBought 83 , "bought" .= itemBought
86 ++ maybe [] (\x -> ["expires" .= x]) itemExpires 84 , "expires" .= itemExpires
87 ++ maybe [] (\x -> ["opened" .= x]) itemOpened 85 , "opened" .= itemOpened
86 ]
88 87
89instance FromJSON Item where 88instance FromJSON Item where
90 parseJSON = withObject "Item" $ \obj -> do 89 parseJSON = withObject "Item" $ \obj -> do
91 itemKind <- obj .: "kind" 90 itemKind <- obj .: "kind"
92 let 91 let
93 itemNormKind = normalizeKind itemKind 92 itemNormKind = normalizeKind itemKind
94 itemBought <- obj .:? "bought" 93 itemBought <- maybe DateUnknown DateKnown <$> obj .:? "bought"
95 itemExpires <- obj .:? "expires" 94 itemExpires <- maybe DateNever DateKnown <$> obj .:? "expires"
96 itemOpened <- obj .:? "opened" 95 itemOpened <- obj .: "opened"
97 return Item{..} 96 return Item{..}
98 97
99instance ToJSON (Entity Item) where 98instance ToJSON (Entity Item) where
@@ -122,9 +121,9 @@ normalizeKind = Text.strip . Text.toCaseFold
122 121
123data ItemDiff = DiffKind Text 122data ItemDiff = DiffKind Text
124 | DiffType Text 123 | DiffType Text
125 | DiffBought (Maybe Day) 124 | DiffBought ItemDate
126 | DiffExpires (Maybe Day) 125 | DiffExpires ItemDate
127 | DiffOpened (Maybe Day) 126 | DiffOpened ItemDate
128 127
129newtype ItemDiffs = ItemDiffs [ItemDiff] 128newtype ItemDiffs = ItemDiffs [ItemDiff]
130 129
@@ -149,7 +148,7 @@ toUpdate (ItemDiffs ds) = mconcat $ do
149 DiffOpened d -> (, []) [ ItemOpened =. d ] 148 DiffOpened d -> (, []) [ ItemOpened =. d ]
150 149
151data WithType a = WithType { typedVal :: a, valType :: Text } 150data WithType a = WithType { typedVal :: a, valType :: Text }
152 deriving (Eq, Ord, Show) 151 deriving (Eq, Ord, Show, Functor)
153 152
154typeToJSON :: ToJSON a 153typeToJSON :: ToJSON a
155 => Text -- ^ Key for value, if needed 154 => Text -- ^ Key for value, if needed
diff --git a/Model/Types.hs b/Model/Types.hs
new file mode 100644
index 0000000..61bebfd
--- /dev/null
+++ b/Model/Types.hs
@@ -0,0 +1,35 @@
1{-# LANGUAGE DeriveGeneric #-}
2
3module Model.Types
4 ( ItemDate(..)
5 , isNever, isUnknown, isKnown
6 ) where
7
8import ClassyPrelude.Yesod
9
10data ItemDate = DateUnknown | DateKnown Day | DateNever
11 deriving (Eq, Ord, Show, Read, Generic)
12
13isNever, isUnknown, isKnown :: ItemDate -> Bool
14isNever DateNever = True
15isNever _ = False
16isUnknown DateUnknown = True
17isUnknown _ = False
18isKnown (DateKnown _) = True
19isKnown _ = False
20
21unknownVerb :: IsString a => a
22unknownVerb = "unknown"
23
24instance ToJSON ItemDate where
25 toJSON DateNever = Null
26 toJSON DateUnknown = String unknownVerb
27 toJSON (DateKnown d) = toJSON d
28instance FromJSON ItemDate where
29 parseJSON Null = pure DateNever
30 parseJSON v@(String inp)
31 | unknownVerb == inp = pure DateUnknown
32 | otherwise = DateKnown <$> parseJSON v
33 parseJSON v = DateKnown <$> parseJSON v
34
35derivePersistFieldJSON "ItemDate"
diff --git a/bar.cabal b/bar.cabal
index 53e4f1e..4022f7f 100644
--- a/bar.cabal
+++ b/bar.cabal
@@ -1,5 +1,5 @@
1name: bar 1name: bar
2version: 0.1.0 2version: 0.2.0
3cabal-version: >= 1.8 3cabal-version: >= 1.8
4build-type: Simple 4build-type: Simple
5 5
@@ -18,6 +18,7 @@ library
18 Import 18 Import
19 Import.NoFoundation 19 Import.NoFoundation
20 Model 20 Model
21 Model.Types
21 Settings 22 Settings
22 Settings.StaticFiles 23 Settings.StaticFiles
23 Handler.Common 24 Handler.Common
diff --git a/bar.nix b/bar.nix
index e80d685..f31cce4 100644
--- a/bar.nix
+++ b/bar.nix
@@ -10,7 +10,7 @@
10}: 10}:
11mkDerivation { 11mkDerivation {
12 pname = "bar"; 12 pname = "bar";
13 version = "0.1.0"; 13 version = "0.2.0";
14 src = ./.; 14 src = ./.;
15 isLibrary = true; 15 isLibrary = true;
16 isExecutable = true; 16 isExecutable = true;
diff --git a/config/models b/config/models
index 16b4ce0..8aebc5b 100644
--- a/config/models
+++ b/config/models
@@ -1,9 +1,9 @@
1Item 1Item
2 kind Text 2 kind Text
3 normKind Text 3 normKind Text
4 bought Day Maybe 4 bought ItemDate
5 expires Day Maybe 5 expires ItemDate
6 opened Day Maybe 6 opened ItemDate
7 Foreign Kind fkType normKind 7 Foreign Kind fkType normKind
8 deriving Show Eq 8 deriving Show Eq
9Reference 9Reference
diff --git a/templates/default-layout.cassius b/templates/default-layout.cassius
index da76e28..bc64e8e 100644
--- a/templates/default-layout.cassius
+++ b/templates/default-layout.cassius
@@ -40,7 +40,7 @@ div.itemId
40 color: #aaa 40 color: #aaa
41.table .table .td, .table .table .tc, .table .table .th, .table .table .kind 41.table .table .td, .table .table .tc, .table .table .th, .table .table .kind
42 padding: 0 42 padding: 0
43table table td, table table th 43table table td, table table th, .table table td, .table table th
44 padding: 0 44 padding: 0
45#messages 45#messages
46 list-style-type: none 46 list-style-type: none
diff --git a/templates/inventoryListing.cassius b/templates/inventoryListing.cassius
new file mode 100644
index 0000000..9a7459e
--- /dev/null
+++ b/templates/inventoryListing.cassius
@@ -0,0 +1,3 @@
1.expired
2 color: #800
3 font-weight: bold \ No newline at end of file
diff --git a/templates/inventoryListing.hamlet b/templates/inventoryListing.hamlet
index f0ff1e4..802905d 100644
--- a/templates/inventoryListing.hamlet
+++ b/templates/inventoryListing.hamlet
@@ -30,22 +30,27 @@
30 <div .kind>#{itemKind} 30 <div .kind>#{itemKind}
31 <div .type>#{itemType} 31 <div .type>#{itemType}
32 <div .td .day> 32 <div .td .day>
33 $maybe bought <- itemBought 33 $case itemBought
34 #{dayFormat bought} 34 $of DateUnknown
35 $nothing 35 <hr>
36 <hr> 36 $of DateKnown d
37 #{dayFormat d}
37 <div .td .day> 38 <div .td .day>
38 $maybe expires <- itemExpires 39 $case itemExpires
39 #{dayFormat expires} 40 $of DateNever
40 $nothing 41 <hr>
41 <hr> 42 $of DateKnown d
43 <span :d < today:.expired>#{dayFormat d}
42 <div .td .day> 44 <div .td .day>
43 $maybe opened <- itemOpened 45 $case itemOpened
44 #{dayFormat opened} 46 $of DateKnown d
45 $nothing 47 #{dayFormat d}
46 <form method=post action=@{OpenItemR itemId}> 48 $of DateUnknown
47 <button type=submit> 49 Yes
48 Open 50 $of DateNever
51 <form method=post action=@{OpenItemR itemId}>
52 <button type=submit>
53 Open
49 <div .td> 54 <div .td>
50 <form method=get action=@{UpdateItemR itemId}##{toPathPiece itemId}> 55 <form method=get action=@{UpdateItemR itemId}##{toPathPiece itemId}>
51 <button type=submit> 56 <button type=submit>