yammat/Handler/Modify.hs

126 lines
5.3 KiB
Haskell
Raw Normal View History

2015-08-09 21:16:33 +02: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 06:46:33 +02:00
module Handler.Modify where
import Import
import Handler.Common
getModifyR :: BeverageId -> Handler Html
2016-05-23 20:35:14 +02:00
getModifyR bId =
isBeverage bId SummaryR >>= (\bev -> do
p <- lookupGetParam "barcode"
_ <- handleGetParam p (Right bId)
rawbs <- runDB $ selectList [BarcodeBev ==. Just bId] []
let bs = map (barcodeCode . entityVal) rawbs
(modifyWidget, enctype) <- generateFormPost
$ renderBootstrap3 BootstrapBasicForm
$ modifyForm (Just bev) bs
2018-09-04 18:06:12 +02:00
defaultLayout $ do
setTitleI (MsgModifyBeverage (beverageIdent bev))
2016-05-23 20:35:14 +02:00
$(widgetFile "modify")
)
2015-04-04 06:46:33 +02:00
postModifyR :: BeverageId -> Handler Html
2016-05-23 20:35:14 +02:00
postModifyR bId =
isBeverage bId SummaryR >>= (\bev -> do
rawbs <- runDB $ selectList [BarcodeBev ==. Just bId] []
let bs = map (barcodeCode . entityVal) rawbs
((res, _), _) <- runFormPost
$ renderBootstrap3 BootstrapBasicForm
$ modifyForm (Just bev) bs
2016-05-23 20:35:14 +02:00
case res of
FormSuccess nBev -> do
runDB $ update bId
[ BeverageIdent =. modBevIdent nBev
, BeveragePrice =. modBevPrice nBev
, BeverageAmount =. modBevAmount nBev
, BeverageAlertAmount =. modBevAlertAmount nBev
, BeverageCorrectedAmount +=. (modBevAmount nBev - beverageAmount bev)
, BeverageMl =. modBevMl nBev
, BeverageAvatar =. modBevAvatar nBev
, BeverageSupplier =. modBevSupp nBev
, BeverageMaxAmount =. modBevMaxAmount nBev
, BeveragePerCrate =. modBevPC nBev
, BeverageArtNr =. modBevArtNr nBev
, BeveragePricePerCrate =. modBevPricePC nBev
]
handleBarcodes (Right bId) (fromMaybe [] $ modBevBarcodes nBev)
setMessageI MsgEditSuccess
redirect SummaryR
_ -> do
setMessageI MsgEditFail
redirect SummaryR
)
2015-04-04 06:46:33 +02:00
2015-07-21 09:14:38 +02:00
data ModBev = ModBev
{ modBevIdent :: Text
, modBevPrice :: Int
, modBevAmount :: Int
, modBevAlertAmount :: Int
2015-10-11 20:07:12 +02:00
, modBevMaxAmount :: Int
2015-07-21 09:14:38 +02:00
, modBevMl :: Int
2015-10-11 20:07:12 +02:00
, modBevPC :: Maybe Int
, modBevPricePC :: Maybe Int
2015-07-21 09:14:38 +02:00
, modBevAvatar :: Maybe AvatarId
, modBevBarcodes :: Maybe [Text]
2015-10-11 20:07:12 +02:00
, modBevSupp :: Maybe SupplierId
, modBevArtNr :: Maybe Text
2015-07-21 09:14:38 +02:00
}
modifyForm :: Maybe Beverage -> [Text] -> AForm Handler ModBev
modifyForm (Just bev) bs = ModBev
<$> areq textField (bfs MsgName) (Just $ beverageIdent bev)
<*> areq currencyField (bfs MsgPrice) (Just $ beveragePrice bev)
<*> areq amountField (bfs MsgCurrentStock) (Just $ beverageAmount bev)
<*> areq amountField (bfs MsgAnnouncedStock) (Just $ beverageAlertAmount bev)
<*> areq amountField (bfs MsgMaxAmount) (Just $ beverageMaxAmount bev)
<*> areq volumeField (bfs MsgVolume) (Just $ beverageMl bev)
<*> aopt amountField (bfs MsgAmountPerCrate) (Just $ beveragePerCrate bev)
<*> aopt currencyField (bfs MsgPricePerCrate) (Just $ beveragePricePerCrate bev)
2015-10-22 23:57:27 +02:00
<*> aopt (selectField avatars) (bfs MsgSelectAvatar) (Just $ beverageAvatar bev)
<*> aopt barcodeField (bfs MsgBarcodeField) (Just $ Just bs)
<*> aopt (selectField sups) (bfs MsgSelectSupplier) (Just $ beverageSupplier bev)
<*> aopt textField (bfs MsgArtNr) (Just $ beverageArtNr bev)
<* bootstrapSubmit (msgToBSSubmit MsgSubmit)
where
avatars = optionsPersistKey [] [Asc AvatarIdent] avatarIdent
sups = optionsPersistKey [] [Asc SupplierIdent] supplierIdent
modifyForm Nothing _ = ModBev
<$> areq textField (bfs MsgName) Nothing
<*> areq currencyField (bfs MsgPrice) Nothing
<*> areq amountField (bfs MsgCurrentStock) Nothing
<*> areq amountField (bfs MsgAnnouncedStock) Nothing
<*> areq amountField (bfs MsgMaxAmount) Nothing
<*> areq volumeField (bfs MsgVolume) Nothing
<*> aopt amountField (bfs MsgAmountPerCrate) Nothing
<*> aopt currencyField (bfs MsgPricePerCrate) Nothing
<*> aopt (selectField avatars) (bfs MsgSelectAvatar) Nothing
<*> aopt barcodeField (bfs MsgBarcodeField) Nothing
<*> aopt (selectField sups) (bfs MsgSelectSupplier) Nothing
<*> aopt textField (bfs MsgArtNr) Nothing
2015-10-22 23:57:27 +02:00
<* bootstrapSubmit (msgToBSSubmit MsgSubmit)
2015-04-16 02:12:03 +02:00
where
2015-10-11 20:07:12 +02:00
avatars = optionsPersistKey [] [Asc AvatarIdent] avatarIdent
sups = optionsPersistKey [] [Asc SupplierIdent] supplierIdent
2015-04-04 06:46:33 +02:00
getDeleteBeverageR :: BeverageId -> Handler Html
2016-05-23 20:35:14 +02:00
getDeleteBeverageR bId =
isBeverage bId HomeR >>= (\_ -> do
runDB $ delete bId
setMessageI MsgItemDeleted
redirect HomeR
)