yammat/Handler/Modify.hs

101 lines
3.7 KiB
Haskell
Raw Normal View History

2015-08-09 19:16:33 +00:00
-- yammat - Yet Another MateMAT
-- Copyright (C) 2015 Amedeo Molnár
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU Affero General Public License as published
-- by the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU Affero General Public License for more details.
--
-- You should have received a copy of the GNU Affero General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
2015-04-04 04:46:33 +00:00
module Handler.Modify where
import Import
import Handler.Common
getModifyR :: BeverageId -> Handler Html
getModifyR bId = do
mBev <- runDB $ get bId
case mBev of
Just bev -> do
2015-07-21 07:14:38 +00:00
p <- lookupGetParam "barcode"
_ <- handleGetParam p (Right bId)
rawbs <- runDB $ selectList [BarcodeBev ==. Just bId] []
bs <- return $ map (barcodeCode . entityVal) rawbs
(modifyWidget, enctype) <- generateFormPost $ modifyForm bev bs
2015-04-04 04:46:33 +00:00
defaultLayout $ do
$(widgetFile "modify")
Nothing -> do
2015-04-09 22:40:58 +00:00
setMessageI MsgItemUnknown
2015-04-04 04:46:33 +00:00
redirect $ SummaryR
postModifyR :: BeverageId -> Handler Html
postModifyR bId = do
mBev <- runDB $ get bId
case mBev of
Just bev -> do
2015-07-21 07:14:38 +00:00
rawbs <- runDB $ selectList [BarcodeBev ==. Just bId] []
bs <- return $ map (barcodeCode . entityVal) rawbs
((res, _), _) <- runFormPost $ modifyForm bev bs
2015-04-04 04:46:33 +00:00
case res of
FormSuccess nBev -> do
runDB $ update bId
2015-07-21 07:14:38 +00:00
[ BeverageIdent =. modBevIdent nBev
, BeveragePrice =. modBevPrice nBev
, BeverageAmount =. modBevAmount nBev
, BeverageAlertAmount =. modBevAlertAmount nBev
, BeverageCorrectedAmount +=. ((modBevAmount nBev) - (beverageAmount bev))
, BeverageMl =. modBevMl nBev
, BeverageAvatar =. modBevAvatar nBev
2015-04-04 04:46:33 +00:00
]
2015-07-21 08:00:19 +00:00
handleBarcodes (Right bId) (fromMaybe [] $ modBevBarcodes nBev)
2015-04-09 22:40:58 +00:00
setMessageI MsgEditSuccess
2015-04-04 04:46:33 +00:00
redirect $ SummaryR
_ -> do
2015-04-09 22:40:58 +00:00
setMessageI MsgEditFail
2015-04-04 04:46:33 +00:00
redirect $ SummaryR
Nothing -> do
2015-04-09 22:40:58 +00:00
setMessageI MsgItemUnknown
2015-04-04 04:46:33 +00:00
redirect $ SummaryR
2015-07-21 07:14:38 +00:00
data ModBev = ModBev
{ modBevIdent :: Text
, modBevPrice :: Int
, modBevAmount :: Int
, modBevAlertAmount :: Int
, modBevMl :: Int
, modBevAvatar :: Maybe AvatarId
, modBevBarcodes :: Maybe [Text]
}
modifyForm :: Beverage -> [Text] -> Form ModBev
modifyForm bev bs = renderDivs $ ModBev
2015-04-09 22:40:58 +00:00
<$> areq textField (fieldSettingsLabel MsgName) (Just $ beverageIdent bev)
<*> areq currencyField (fieldSettingsLabel MsgPrice) (Just $ beveragePrice bev)
<*> areq amountField (fieldSettingsLabel MsgCurrentStock) (Just $ beverageAmount bev)
<*> areq amountField (fieldSettingsLabel MsgAnnouncedStock) (Just $ beverageAlertAmount bev)
2015-05-03 16:01:30 +00:00
<*> areq volumeField (fieldSettingsLabel MsgVolume) (Just $ beverageMl bev)
2015-04-16 00:12:03 +00:00
<*> aopt (selectField avatars) (fieldSettingsLabel MsgSelectAvatar) (Just $ beverageAvatar bev)
2015-07-21 07:14:38 +00:00
<*> aopt barcodeField (fieldSettingsLabel MsgBarcodeField) (Just $ Just bs)
2015-04-16 00:12:03 +00:00
where
avatars = do
ents <- runDB $ selectList [] [Asc AvatarIdent]
optionsPairs $ map (\ent -> ((avatarIdent $ entityVal ent), entityKey ent)) ents
2015-04-04 04:46:33 +00:00
getDeleteBeverageR :: BeverageId -> Handler Html
getDeleteBeverageR bId = do
mBev <- runDB $ get bId
case mBev of
Just bev -> do
runDB $ delete bId
2015-04-09 22:40:58 +00:00
setMessageI MsgItemDeleted
2015-04-04 04:46:33 +00:00
redirect $ HomeR
Nothing -> do
2015-04-09 22:40:58 +00:00
setMessageI MsgItemUnknown
2015-04-04 04:46:33 +00:00
redirect $ HomeR