{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE QuasiQuotes #-} module Handler.Utils ( module Handler.Utils ) where import Import.NoFoundation import Handler.Utils.DateTime as Handler.Utils import Handler.Utils.Term as Handler.Utils import Handler.Utils.Bootstrap3 as Handler.Utils import Handler.Utils.Form as Handler.Utils import Handler.Utils.Table as Handler.Utils import Handler.Utils.Zip as Handler.Utils import Handler.Utils.Rating as Handler.Utils import Handler.Utils.Submission as Handler.Utils import Text.Blaze (Markup, ToMarkup) import Data.Map (Map) import qualified Data.Map as Map tickmark :: IsString a => a tickmark = fromString "✔" text2Html :: Text -> Html text2Html = toHtml -- prevents ambiguous types toWgt :: (ToMarkup a, MonadBaseControl IO m, MonadThrow m, MonadIO m) => a -> WidgetT site m () toWgt = toWidget . toHtml text2widget :: (MonadBaseControl IO m, MonadThrow m, MonadIO m) => Text -> WidgetT site m () text2widget t = [whamlet|#{t}|] str2widget :: (MonadBaseControl IO m, MonadThrow m, MonadIO m) => String -> WidgetT site m () str2widget s = [whamlet|#{s}|] withFragment :: ( Monad m ) => MForm m (a, WidgetT site IO ()) -> Markup -> MForm m (a, WidgetT site IO ()) withFragment form html = (flip fmap) form $ \(x, widget) -> (x, toWidget html >> widget) ----------- -- Maybe -- ----------- whenIsJust :: Monad m => Maybe a -> (a -> m ()) -> m () whenIsJust (Just x) f = f x whenIsJust Nothing _ = return () ---------- -- Maps -- ---------- entities2map :: PersistEntity record => [Entity record] -> Map (Key record) record entities2map = foldl' (\m entity -> Map.insert (entityKey entity) (entityVal entity) m) Map.empty