diff options
-rw-r--r-- | Handler/Common.hs | 16 | ||||
-rw-r--r-- | Handler/InventoryListing.hs | 2 | ||||
-rw-r--r-- | Handler/ReferenceListing.hs | 2 | ||||
-rw-r--r-- | Model.hs | 22 |
4 files changed, 30 insertions, 12 deletions
diff --git a/Handler/Common.hs b/Handler/Common.hs index 1cf63de..65988da 100644 --- a/Handler/Common.hs +++ b/Handler/Common.hs | |||
@@ -10,13 +10,14 @@ module Handler.Common | |||
10 | , ReferenceState(..) | 10 | , ReferenceState(..) |
11 | , FormState(..) | 11 | , FormState(..) |
12 | , HasFormState(..) | 12 | , HasFormState(..) |
13 | , stockSort, referenceSort | ||
13 | ) where | 14 | ) where |
14 | 15 | ||
15 | import Import | 16 | import Import |
16 | 17 | ||
17 | import Data.Unique | 18 | import Data.Unique |
18 | 19 | ||
19 | import qualified Data.Text as Text (pack) | 20 | import qualified Data.Text as Text |
20 | 21 | ||
21 | import Data.Set (Set) | 22 | import Data.Set (Set) |
22 | import qualified Data.Set as Set | 23 | import qualified Data.Set as Set |
@@ -165,3 +166,16 @@ kinds = do | |||
165 | [ [ itemKind | Entity _ Item{..} <- stock ] | 166 | [ [ itemKind | Entity _ Item{..} <- stock ] |
166 | , [ referenceKind | Entity _ Reference{..} <- reference ] | 167 | , [ referenceKind | Entity _ Reference{..} <- reference ] |
167 | ] | 168 | ] |
169 | |||
170 | type Sort a = a -> a | ||
171 | |||
172 | stockSort :: Sort [WithType (Entity Item)] | ||
173 | stockSort = concat . map (sortOn $ entityVal . typedVal) . sortGroups . group | ||
174 | where | ||
175 | group = groupBy ((==) `on` valType) . sortOn valType | ||
176 | sortGroups = sortOn (fmap minimum . fromNullable . map (entityVal . typedVal)) | ||
177 | |||
178 | referenceSort :: Sort [WithType (Entity Reference)] | ||
179 | referenceSort = sortBy referenceOrdering | ||
180 | where | ||
181 | referenceOrdering (Entity _ refA `WithType` refAType) (Entity _ refB `WithType` refBType) = compare refAType refBType <> compare refA refB | ||
diff --git a/Handler/InventoryListing.hs b/Handler/InventoryListing.hs index 6d4d8fa..cbf4eab 100644 --- a/Handler/InventoryListing.hs +++ b/Handler/InventoryListing.hs | |||
@@ -16,7 +16,7 @@ postInventoryListingR = do | |||
16 | FormFailure errors -> mapM_ (addMessage "formError" . toHtml) errors | 16 | FormFailure errors -> mapM_ (addMessage "formError" . toHtml) errors |
17 | _ -> return () | 17 | _ -> return () |
18 | 18 | ||
19 | (sortOn (entityVal . typedVal) -> stock) <- runDB $ mapM withType =<< selectList [] [] | 19 | (stockSort -> stock) <- runDB $ mapM withType =<< selectList [] [] |
20 | 20 | ||
21 | selectRep $ do | 21 | selectRep $ do |
22 | provideJson (stock :: [WithType (Entity Item)]) | 22 | provideJson (stock :: [WithType (Entity Item)]) |
diff --git a/Handler/ReferenceListing.hs b/Handler/ReferenceListing.hs index 0b89a20..e433429 100644 --- a/Handler/ReferenceListing.hs +++ b/Handler/ReferenceListing.hs | |||
@@ -17,7 +17,7 @@ postReferenceListingR = do | |||
17 | FormFailure errors -> mapM_ (addMessage "formError" . toHtml) errors | 17 | FormFailure errors -> mapM_ (addMessage "formError" . toHtml) errors |
18 | _ -> return () | 18 | _ -> return () |
19 | 19 | ||
20 | reference <- runDB $ mapM withType =<< selectList [] [Asc ReferenceKind] | 20 | (referenceSort -> reference) <- runDB $ mapM withType =<< selectList [] [Asc ReferenceKind] |
21 | 21 | ||
22 | selectRep $ do | 22 | selectRep $ do |
23 | provideJson (reference :: [WithType (Entity Reference)]) | 23 | provideJson (reference :: [WithType (Entity Reference)]) |
@@ -45,14 +45,18 @@ withType :: ( BaseBackend backend ~ SqlBackend | |||
45 | withType val = (val `WithType`) . kindType <$> getType val | 45 | withType val = (val `WithType`) . kindType <$> getType val |
46 | 46 | ||
47 | instance Ord Item where | 47 | instance Ord Item where |
48 | x `compare` y = mconcat | 48 | x `compare` y = mconcat cmprs |
49 | [ (isNothing $ itemOpened x) `compare` (isNothing $ itemOpened y) | 49 | where |
50 | , itemOpened x `compare` itemOpened y | 50 | cmprs = [ itemOpened x `compareM` itemOpened y |
51 | , (isNothing $ itemExpires x) `compare` (isNothing $ itemExpires y) | 51 | , itemExpires x `compareM` itemExpires y |
52 | , itemExpires x `compare` itemExpires x | 52 | , itemKind x `compare` itemKind y |
53 | , itemKind x `compare` itemKind x | 53 | , itemBought x `compare` itemBought y |
54 | , itemBought x `compare` itemBought x | 54 | ] |
55 | ] | 55 | |
56 | compareM (Just _) Nothing = LT | ||
57 | compareM Nothing (Just _) = GT | ||
58 | compareM (Just a) (Just b) = compare a b | ||
59 | compareM _ _ = EQ | ||
56 | 60 | ||
57 | instance ToJSON Item where | 61 | instance ToJSON Item where |
58 | toJSON Item{..} = object $ | 62 | toJSON Item{..} = object $ |
@@ -124,7 +128,7 @@ toUpdate (ItemDiffs ds) = mconcat $ do | |||
124 | DiffOpened d -> (, []) [ ItemOpened =. d ] | 128 | DiffOpened d -> (, []) [ ItemOpened =. d ] |
125 | 129 | ||
126 | data WithType a = WithType { typedVal :: a, valType :: Text } | 130 | data WithType a = WithType { typedVal :: a, valType :: Text } |
127 | deriving (Eq, Ord) | 131 | deriving (Eq, Ord, Show) |
128 | 132 | ||
129 | typeToJSON :: ToJSON a | 133 | typeToJSON :: ToJSON a |
130 | => Text -- ^ Key for value, if needed | 134 | => Text -- ^ Key for value, if needed |