{-# LANGUAGE ApplicativeDo #-} module Handler.Common ( inventoryListing , itemForm , referenceListing , referenceForm , kinds , InventoryState(..) , ReferenceState(..) , FormState(..) , HasFormState(..) , stockSort, referenceSort , humanId ) where import Import hiding ((\\)) import Data.Unique import qualified Data.Text as Text import qualified Data.ByteString.Char8 as CBS import Data.Set (Set) import qualified Data.Set as Set import Control.Lens import Handler.Common.Types import Text.Julius (RawJS(..)) import Database.Persist.Sql (fromSqlKey) import qualified Web.Hashids as HID import Data.List ((\\)) humanId :: ItemId -> Text humanId = Text.pack . CBS.unpack . HID.encode ctx . fromIntegral . fromSqlKey where ctx = HID.createHashidsContext "ItemId" 3 $ (['0'..'9'] ++ ['a'..'z']) \\ ['0', 'l', 'v', '2'] dayFormat :: Day -> String dayFormat = formatTime defaultTimeLocale "%e. %b %y" 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 (maybe (Just $ Just today) Just $ fmap itemBought proto) "Unknown" (expiresRes, expiresWidget) <- dayForm (fmap itemExpires proto) "Never" (openedRes, openedWidget) <- dayForm (fmap itemOpened proto) "Never" 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 (Maybe Day) -> String -> MForm Handler (FormResult (Maybe Day), Widget) dayForm proto label = do today <- utctDay <$> liftIO getCurrentTime checkboxId <- ("check" <>) . show . hashUnique <$> liftIO newUnique (fmap (fromMaybe False) -> isNothingRes, isNothingView) <- mopt checkBoxField ("" { fsId = Just $ Text.pack checkboxId }) . Just . Just . fromMaybe True $ fmap isNothing proto (dayRes, dayView) <- mreq dayField "" . Just . fromMaybe today $ join proto let res = (bool Just (const Nothing) <$> isNothingRes) <*> dayRes return . (res, ) $ do [whamlet| $newline never