module Handler.InventoryListing where
import Import
import Handler.Common
getInventoryListingR, postInventoryListingR :: Handler TypedContent
getInventoryListingR = postInventoryListingR
postInventoryListingR = do
((insertResult, fsInsertForm), fsInsertEncoding) <- runFormPost $ itemForm Nothing
case insertResult of
FormSuccess (Item{..} `WithType` t) -> runDB $ do
void $ upsertBy (UniqueKind itemNormKind) (Kind itemNormKind t) [ KindType =. t ]
newItem <- insert Item{..}
otherItems <- selectKeysList [ ItemNormKind ==. itemNormKind, ItemId !=. newItem ] []
when (not $ null otherItems) . addMessage "insertAmbiguous" $
[shamlet|
$newline never
There are other items of the same kind.
$forall other <- otherItems
- #{humanId other}
|]
addMessage "insertSuccess" [shamlet|
$newline never
Inserted new item as #
#{humanId newItem}
|]
FormFailure errors -> mapM_ (addMessage "formError" . toHtml) errors
_ -> return ()
(stockSort -> stock) <- runDB $ withTypes =<< selectList [] []
selectRep $ do
provideJson (stock :: [WithType (Entity Item)])
provideRep . defaultLayout $ inventoryListing InventoryState
{ invFormState = Just InsertForm{..}
, ..
}
putInventoryListingR :: Handler Value
putInventoryListingR = do
(Item{..} `WithType` t) <- requireCheckJsonBody
returnJson <=< runDB $ do
void $ upsertBy (UniqueKind itemNormKind) (Kind itemNormKind t) [ KindType =. t ]
withType =<< insertEntity Item{..}