hunting wabbits

This commit is contained in:
nek0 2022-09-16 16:37:00 +02:00
parent 889c9e3ad1
commit 0d1d219291
5 changed files with 17 additions and 12 deletions

2
.gitignore vendored
View File

@ -8,3 +8,5 @@ dist/
.ghc* .ghc*
cabal.project.* cabal.project.*
*.bak* *.bak*
.direnv/
.envrc

View File

@ -9,5 +9,4 @@ import Types.Views as T
import Types.User as T import Types.User as T
import Types.Journal as T import Types.Journal as T
import Types.Product as T import Types.Product as T
import Types.Orphans as T
import Types.Configuration as T import Types.Configuration as T

View File

@ -8,17 +8,15 @@ module Util where
import Servant hiding (addHeader) import Servant hiding (addHeader)
import Servant.Client import Servant.Client
import Servant.Client.Core.Request
import qualified Text.Blaze.Html5.Attributes as HA import qualified Text.Blaze.Html5.Attributes as HA
import Text.Blaze.Internal
import qualified Data.Text as T import qualified Data.Text as T
import Data.Text.Encoding import Data.Text.Encoding
import Data.Text.I18n import Data.Text.I18n
import Data.ByteString.Builder
import Data.List (intercalate) import Data.List (intercalate)
import Data.List.Split (chunksOf) import Data.List.Split (chunksOf)
@ -26,13 +24,11 @@ import Data.String (fromString)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Web.Cookie
import Text.Printf (printf) import Text.Printf (printf)
import Network.HTTP.Types.Status import Network.HTTP.Types.Status
import Control.Monad.Reader (ask, asks) import Control.Monad.Reader (ask)
-- imports from "mateamt" -- imports from "mateamt"
@ -177,6 +173,9 @@ redirectOverAuth muid mLink mRefine = do
} }
) )
productBgStyle
:: AttributeValue
-> Attribute
productBgStyle aid = HA.style $ mconcat productBgStyle aid = HA.style $ mconcat
[ "background-image: url(#" <> aid <> ");" -- FILLME [ "background-image: url(#" <> aid <> ");" -- FILLME
, "backgronud-color: blue;" , "backgronud-color: blue;"
@ -196,6 +195,11 @@ controlInit mcookie = do
(ReadState l10n backend _ symbol version) <- ask (ReadState l10n backend _ symbol version) <- ask
return (token, muser, loc, l10n, backend, symbol, version) return (token, muser, loc, l10n, backend, symbol, version)
handleClientErr
:: ClientError
-> Maybe Int
-> Maybe Link
-> UserHandler UserOverviewPage
handleClientErr err muid authTargetLink = handleClientErr err muid authTargetLink =
case err of case err of
FailureResponse _ resp -> FailureResponse _ resp ->

View File

@ -13,7 +13,7 @@ import Data.String (fromString)
import Data.Text.I18n import Data.Text.I18n
import Data.Maybe (isJust, fromJust, fromMaybe) import Data.Maybe (isJust, fromJust)
import Control.Monad (when) import Control.Monad (when)
@ -59,8 +59,8 @@ buyConfirmPage l10n locale uid ziptups total forceBuy version mcookie symbol =
H.! HA.enctype "application/x-www-form-urlencoded" H.! HA.enctype "application/x-www-form-urlencoded"
$ do $ do
mapM_ mapM_
(\( MT.PurchaseDetail pdid amount (\( MT.PurchaseDetail _ _
, MT.ProductShortOverview pid ident price _ _ mava) -> , MT.ProductShortOverview pid ident price amount _ mava) ->
H.div H.! HA.class_ "form-group required" $ do H.div H.! HA.class_ "form-group required" $ do
H.input H.input
H.! HA.id ("product-select-" <> fromString (show pid)) H.! HA.id ("product-select-" <> fromString (show pid))
@ -141,7 +141,7 @@ buyProductsForm
-> H.Html -> H.Html
buyProductsForm l10n locale prods = do buyProductsForm l10n locale prods = do
H.div H.! HA.class_ "tile-list" $ H.div H.! HA.class_ "tile-list" $
mapM_ (\(MT.ProductShortOverview pid ident price amount ml maid) -> mapM_ (\(MT.ProductShortOverview pid ident _ _ _ maid) ->
H.div H.div
H.! HA.class_ "tile" H.! HA.class_ "tile"
H.!? H.!?

View File

@ -81,7 +81,7 @@ productRefillPage l10n loc version mcookie prodList =
H.! HA.enctype "application/x-www-form-urlencoded" H.! HA.enctype "application/x-www-form-urlencoded"
$ do $ do
mapM_ mapM_
(\(MT.ProductShortOverview pid ident price amount ml maid) -> do (\(MT.ProductShortOverview pid ident _ _ _ maid) -> do
H.div H.div
H.! HA.class_ "form-group optional" H.! HA.class_ "form-group optional"
H.!? H.!?