{-# LANGUAGE ApplicativeDo #-} module Handler.Common ( inventoryListing , itemForm , referenceListing , referenceForm , kinds , InventoryState(..) , ReferenceState(..) , FormState(..) , HasFormState(..) , stockSort, referenceSort ) where import Import import Data.Unique import qualified Data.Text as Text import Data.Set (Set) import qualified Data.Set as Set import Control.Lens import Handler.Common.Types import Text.Julius (RawJS(..)) import Data.List.NonEmpty (NonEmpty) import Data.Semigroup hiding (First(..)) import Data.Monoid (First(..)) dayFormat :: Day -> String dayFormat = formatTime defaultTimeLocale "%e. %b %y" data DayFormConfig = DayFormConfig { dfNever :: Bool , dfUnknown :: Bool , dfKnown :: Bool } itemForm :: Maybe Item -- ^ Update existing item or insert new? -> Html -> MForm Handler (FormResult (WithType Item), Widget) itemForm proto identView = do today <- utctDay <$> liftIO getCurrentTime t <- lift . runDB $ maybe (return Nothing) (fmap (Just . kindType) . getType) proto let kt kWidget tWidget = [whamlet|
^{kWidget}
^{tWidget} |] ((kindRes, typeRes), typedKindWidget) <- typedKindField kt ((itemKind <$> proto), t) (boughtRes, boughtWidget) <- dayForm (Just . fromMaybe (DateKnown today) $ itemBought <$> proto) $ DayFormConfig False True True (expiresRes, expiresWidget) <- dayForm (itemExpires <$> proto) $ DayFormConfig True False True (openedRes, openedWidget) <- dayForm (itemOpened <$> proto) $ DayFormConfig True True True let itemRes = do itemKind <- kindRes itemBought <- boughtRes itemExpires <- expiresRes itemOpened <- openedRes t <- typeRes return $ Item{ itemNormKind = normalizeKind itemKind, ..} `WithType` t return . (itemRes, ) $ [whamlet| $newline never #{identView} ^{typedKindWidget}
^{boughtWidget}
^{expiresWidget}
^{openedWidget} |] where dayForm :: Maybe ItemDate -> DayFormConfig -> MForm Handler (FormResult ItemDate, Widget) dayForm proto DayFormConfig{..} = do today <- utctDay <$> liftIO getCurrentTime let mWhen = bool (Nothing <$) (fmap Just) neverBoxId <- ("check" <>) . show . hashUnique <$> liftIO newUnique unknownBoxId <- ("check" <>) . show . hashUnique <$> liftIO newUnique groupId <- ("dateGroup" <>) . show . hashUnique <$> liftIO newUnique dNever <- mWhen dfNever $ mopt checkBoxField ("" { fsId = Just $ Text.pack neverBoxId }) . Just . Just . fromMaybe True $ fmap isNever proto dUnknown <- mWhen dfUnknown $ mopt checkBoxField ("" { fsId = Just $ Text.pack unknownBoxId }) . Just . Just . fromMaybe False $ fmap isUnknown proto dDay <- mWhen dfKnown $ mopt dayField "" . Just . Just $ case proto of Just (DateKnown d) -> d _ -> today let res = resFromMaybe . fromMaybe FormMissing . fmap (fmap getFirst) $ mconcat [ fmap (fmap (First . bool Nothing (Just DateNever) . fromMaybe False) . fst) dNever , fmap (fmap (First . bool Nothing (Just DateUnknown) . fromMaybe False) . fst) dUnknown , fmap (fmap (First . fmap DateKnown) . fst) dDay ] resFromMaybe (FormSuccess Nothing) = FormFailure ["Missing required information"] resFromMaybe (FormSuccess (Just x)) = FormSuccess x resFromMaybe FormMissing = FormMissing resFromMaybe (FormFailure es) = FormFailure es return . (res, ) $ do toWidget $ [julius| $(function () { var updateInput = function() { $('##{rawJS groupId} :input').filter(':not(:checkbox)').prop("disabled", $('##{rawJS groupId} :checkbox').filter(':checked').length > 0); }; $('##{rawJS groupId} :checkbox').change(function() { if (this.checked) { $('##{rawJS groupId} :checkbox').not(this).prop('checked', false); } updateInput(); }); updateInput(); }); |] let width = length $ (filter id [ isJust dNever, isJust dUnknown ] :: [Bool]) [whamlet| $newline never $maybe (_, isNeverView) <- dNever
0:colspan=#{width}> ^{fvInput dayView} |] inventoryListing :: InventoryState -> Widget inventoryListing InventoryState{ invFormState = formState, ..} = do today <- liftIO $ utctDay <$> getCurrentTime $(widgetFile "inventoryListing") referenceForm :: Maybe Reference -- ^ Update existing item or insert new? -> Html -> MForm Handler (FormResult (WithType Reference), Widget) referenceForm proto identView = do t <- lift . runDB $ maybe (return Nothing) (fmap (Just . kindType) . getType) proto let kt kWidget tWidget = [whamlet|
^{kWidget}
^{tWidget} |] ((kindRes, typeRes), typedKindWidget) <- typedKindField kt ((referenceKind <$> proto), t) let referenceRes = do referenceKind <- kindRes t <- typeRes return $ Reference{ referenceNormKind = normalizeKind referenceKind, .. } `WithType` t return . (referenceRes, ) $ [whamlet| $newline never #{identView} ^{typedKindWidget} |] referenceListing :: ReferenceState -> Widget referenceListing ReferenceState{ refFormState = formState, ..} = $(widgetFile "referenceListing") typedKindField :: (Widget -> Widget -> Widget) -- ^ `\kindWidget typeWidget -> _` -> (Maybe Text, Maybe Text) -- ^ `(kindProto, typeProto)` -> MForm Handler ((FormResult Text, FormResult Text), Widget) -- ^ `((kindRes, typeRes), typedKindWidget)` typedKindField collate (kindProto, typeProto) = do tOptionId <- ("options" <>) . tshow . hashUnique <$> liftIO newUnique let tAttrs = [ ("list", tOptionId) , ("autocomplete", "off") ] kOptionId <- ("options" <>) . tshow . hashUnique <$> liftIO newUnique let kAttrs = [ ("list", kOptionId) , ("autocomplete", "off") ] (kindRes, kindView) <- mreq textField ("" { fsAttrs = kAttrs }) kindProto (typeRes, typeView) <- mreq textField ("" { fsAttrs = tAttrs }) typeProto kOptions <- lift kinds (Set.fromList . map (kindType . entityVal) -> tOptions) <- lift . runDB $ selectList [] [] return . ((kindRes, typeRes), ) $ do toWidget $ [julius| $(function () { $("##{rawJS $ fvId kindView}").change(function () { $.ajax({ url: '@{TypeR}', type: 'GET', contentType: 'application/json', data: { kind: $(this).val() }, success: function (answer) { $("##{rawJS $ fvId typeView}").val(answer); typeChanged = false; } }); }) ; }); |] let kindWidget = [whamlet| $newline never ^{fvInput kindView} $forall opt <- kOptions