{-# LANGUAGE OverloadedLabels #-} module WikiMusic.SSR.Servant.PreferenceRoutes ( setLanguageRoute, setArtistSortingRoute, setGenreSortingRoute, setSongSortingRoute, setDarkModeRoute, setSongAsciiSizeRoute, setPaletteRoute, ) where import Control.Monad.Error.Class import Data.Map qualified as Map import Optics import Relude import Servant import Servant.Multipart import WikiMusic.SSR.Backend.Rest () import WikiMusic.SSR.Model.Api import WikiMusic.SSR.Model.Env import WikiMusic.SSR.Servant.Utilities import WikiMusic.SSR.View.Html () setLanguageRoute :: (MonadError ServerError m) => Env -> Maybe Text -> MultipartData tag -> m a setLanguageRoute :: forall (m :: * -> *) tag a. MonadError ServerError m => Env -> Maybe Text -> MultipartData tag -> m a setLanguageRoute Env env Maybe Text maybeReferer MultipartData tag multipartData = CookieConfig -> Text -> Map Text Text -> m a forall (m :: * -> *) a. MonadError ServerError m => CookieConfig -> Text -> Map Text Text -> m a setCookieRoute (Env env Env -> Optic' A_Lens NoIx Env CookieConfig -> CookieConfig forall k s (is :: IxList) a. Is k A_Getter => s -> Optic' k is s a -> a ^. Optic A_Lens NoIx Env Env AppConfig AppConfig #cfg Optic A_Lens NoIx Env Env AppConfig AppConfig -> Optic A_Lens NoIx AppConfig AppConfig CookieConfig CookieConfig -> Optic' A_Lens NoIx Env CookieConfig forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a b. (JoinKinds k l m, AppendIndices is js ks) => Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b % Optic A_Lens NoIx AppConfig AppConfig CookieConfig CookieConfig #cookie) (Text -> Maybe Text -> Text forall a. a -> Maybe a -> a fromMaybe Text "/songs" Maybe Text maybeReferer) ([(Text, Text)] -> Map Text Text forall k a. Ord k => [(k, a)] -> Map k a Map.fromList [(Text localeCookieName, Text wantedLanguage)]) where wantedLanguage :: Text wantedLanguage = MultipartData tag -> Text -> Text -> Text forall tag. MultipartData tag -> Text -> Text -> Text fromForm MultipartData tag multipartData Text "en" Text "locale" setArtistSortingRoute :: (MonadError ServerError m) => Env -> Maybe Text -> MultipartData tag -> m a setArtistSortingRoute :: forall (m :: * -> *) tag a. MonadError ServerError m => Env -> Maybe Text -> MultipartData tag -> m a setArtistSortingRoute Env env Maybe Text maybeReferer MultipartData tag multipartData = CookieConfig -> Text -> Map Text Text -> m a forall (m :: * -> *) a. MonadError ServerError m => CookieConfig -> Text -> Map Text Text -> m a setCookieRoute (Env env Env -> Optic' A_Lens NoIx Env CookieConfig -> CookieConfig forall k s (is :: IxList) a. Is k A_Getter => s -> Optic' k is s a -> a ^. Optic A_Lens NoIx Env Env AppConfig AppConfig #cfg Optic A_Lens NoIx Env Env AppConfig AppConfig -> Optic A_Lens NoIx AppConfig AppConfig CookieConfig CookieConfig -> Optic' A_Lens NoIx Env CookieConfig forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a b. (JoinKinds k l m, AppendIndices is js ks) => Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b % Optic A_Lens NoIx AppConfig AppConfig CookieConfig CookieConfig #cookie) (Text -> Maybe Text -> Text forall a. a -> Maybe a -> a fromMaybe Text "/artists" Maybe Text maybeReferer) ([(Text, Text)] -> Map Text Text forall k a. Ord k => [(k, a)] -> Map k a Map.fromList [(Text artistSortingCookieName, Text artistSorting)]) where artistSorting :: Text artistSorting = MultipartData tag -> Text -> Text -> Text forall tag. MultipartData tag -> Text -> Text -> Text fromForm MultipartData tag multipartData Text "created-at-desc" Text "artist-sorting" setGenreSortingRoute :: (MonadError ServerError m) => Env -> Maybe Text -> MultipartData tag -> m a setGenreSortingRoute :: forall (m :: * -> *) tag a. MonadError ServerError m => Env -> Maybe Text -> MultipartData tag -> m a setGenreSortingRoute Env env Maybe Text maybeReferer MultipartData tag multipartData = CookieConfig -> Text -> Map Text Text -> m a forall (m :: * -> *) a. MonadError ServerError m => CookieConfig -> Text -> Map Text Text -> m a setCookieRoute (Env env Env -> Optic' A_Lens NoIx Env CookieConfig -> CookieConfig forall k s (is :: IxList) a. Is k A_Getter => s -> Optic' k is s a -> a ^. Optic A_Lens NoIx Env Env AppConfig AppConfig #cfg Optic A_Lens NoIx Env Env AppConfig AppConfig -> Optic A_Lens NoIx AppConfig AppConfig CookieConfig CookieConfig -> Optic' A_Lens NoIx Env CookieConfig forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a b. (JoinKinds k l m, AppendIndices is js ks) => Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b % Optic A_Lens NoIx AppConfig AppConfig CookieConfig CookieConfig #cookie) (Text -> Maybe Text -> Text forall a. a -> Maybe a -> a fromMaybe Text "/genres" Maybe Text maybeReferer) ([(Text, Text)] -> Map Text Text forall k a. Ord k => [(k, a)] -> Map k a Map.fromList [(Text genreSortingCookieName, Text genreSorting)]) where genreSorting :: Text genreSorting = MultipartData tag -> Text -> Text -> Text forall tag. MultipartData tag -> Text -> Text -> Text fromForm MultipartData tag multipartData Text "created-at-desc" Text "genre-sorting" setSongSortingRoute :: (MonadError ServerError m) => Env -> Maybe Text -> MultipartData tag -> m a setSongSortingRoute :: forall (m :: * -> *) tag a. MonadError ServerError m => Env -> Maybe Text -> MultipartData tag -> m a setSongSortingRoute Env env Maybe Text maybeReferer MultipartData tag multipartData = CookieConfig -> Text -> Map Text Text -> m a forall (m :: * -> *) a. MonadError ServerError m => CookieConfig -> Text -> Map Text Text -> m a setCookieRoute (Env env Env -> Optic' A_Lens NoIx Env CookieConfig -> CookieConfig forall k s (is :: IxList) a. Is k A_Getter => s -> Optic' k is s a -> a ^. Optic A_Lens NoIx Env Env AppConfig AppConfig #cfg Optic A_Lens NoIx Env Env AppConfig AppConfig -> Optic A_Lens NoIx AppConfig AppConfig CookieConfig CookieConfig -> Optic' A_Lens NoIx Env CookieConfig forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a b. (JoinKinds k l m, AppendIndices is js ks) => Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b % Optic A_Lens NoIx AppConfig AppConfig CookieConfig CookieConfig #cookie) (Text -> Maybe Text -> Text forall a. a -> Maybe a -> a fromMaybe Text "/songs" Maybe Text maybeReferer) ([(Text, Text)] -> Map Text Text forall k a. Ord k => [(k, a)] -> Map k a Map.fromList [(Text songSortingCookieName, Text songSorting)]) where songSorting :: Text songSorting = MultipartData tag -> Text -> Text -> Text forall tag. MultipartData tag -> Text -> Text -> Text fromForm MultipartData tag multipartData Text "created-at-desc" Text "song-sorting" setDarkModeRoute :: (MonadError ServerError m) => Env -> Maybe Text -> MultipartData tag -> m a setDarkModeRoute :: forall (m :: * -> *) tag a. MonadError ServerError m => Env -> Maybe Text -> MultipartData tag -> m a setDarkModeRoute Env env Maybe Text maybeReferer MultipartData tag multipartData = CookieConfig -> Text -> Map Text Text -> m a forall (m :: * -> *) a. MonadError ServerError m => CookieConfig -> Text -> Map Text Text -> m a setCookieRoute (Env env Env -> Optic' A_Lens NoIx Env CookieConfig -> CookieConfig forall k s (is :: IxList) a. Is k A_Getter => s -> Optic' k is s a -> a ^. Optic A_Lens NoIx Env Env AppConfig AppConfig #cfg Optic A_Lens NoIx Env Env AppConfig AppConfig -> Optic A_Lens NoIx AppConfig AppConfig CookieConfig CookieConfig -> Optic' A_Lens NoIx Env CookieConfig forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a b. (JoinKinds k l m, AppendIndices is js ks) => Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b % Optic A_Lens NoIx AppConfig AppConfig CookieConfig CookieConfig #cookie) (Text -> Maybe Text -> Text forall a. a -> Maybe a -> a fromMaybe Text "/songs" Maybe Text maybeReferer) ([(Text, Text)] -> Map Text Text forall k a. Ord k => [(k, a)] -> Map k a Map.fromList [(Text uiModeCookieName, Text mode)]) where mode :: Text mode = MultipartData tag -> Text -> Text -> Text forall tag. MultipartData tag -> Text -> Text -> Text fromForm MultipartData tag multipartData Text "dark" Text "dark-mode" setSongAsciiSizeRoute :: (MonadError ServerError m) => Env -> Maybe Text -> MultipartData tag -> m a setSongAsciiSizeRoute :: forall (m :: * -> *) tag a. MonadError ServerError m => Env -> Maybe Text -> MultipartData tag -> m a setSongAsciiSizeRoute Env env Maybe Text maybeReferer MultipartData tag multipartData = CookieConfig -> Text -> Map Text Text -> m a forall (m :: * -> *) a. MonadError ServerError m => CookieConfig -> Text -> Map Text Text -> m a setCookieRoute (Env env Env -> Optic' A_Lens NoIx Env CookieConfig -> CookieConfig forall k s (is :: IxList) a. Is k A_Getter => s -> Optic' k is s a -> a ^. Optic A_Lens NoIx Env Env AppConfig AppConfig #cfg Optic A_Lens NoIx Env Env AppConfig AppConfig -> Optic A_Lens NoIx AppConfig AppConfig CookieConfig CookieConfig -> Optic' A_Lens NoIx Env CookieConfig forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a b. (JoinKinds k l m, AppendIndices is js ks) => Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b % Optic A_Lens NoIx AppConfig AppConfig CookieConfig CookieConfig #cookie) (Text -> Maybe Text -> Text forall a. a -> Maybe a -> a fromMaybe Text "/songs" Maybe Text maybeReferer) ([(Text, Text)] -> Map Text Text forall k a. Ord k => [(k, a)] -> Map k a Map.fromList [(Text songAsciiSizeCookieName, Text songAsciiSize)]) where songAsciiSize :: Text songAsciiSize = MultipartData tag -> Text -> Text -> Text forall tag. MultipartData tag -> Text -> Text -> Text fromForm MultipartData tag multipartData Text "medium" Text "song-ascii-size" setPaletteRoute :: (MonadError ServerError m) => Env -> Maybe Text -> MultipartData tag -> m a setPaletteRoute :: forall (m :: * -> *) tag a. MonadError ServerError m => Env -> Maybe Text -> MultipartData tag -> m a setPaletteRoute Env env Maybe Text maybeReferer MultipartData tag multipartData = CookieConfig -> Text -> Map Text Text -> m a forall (m :: * -> *) a. MonadError ServerError m => CookieConfig -> Text -> Map Text Text -> m a setCookieRoute (Env env Env -> Optic' A_Lens NoIx Env CookieConfig -> CookieConfig forall k s (is :: IxList) a. Is k A_Getter => s -> Optic' k is s a -> a ^. Optic A_Lens NoIx Env Env AppConfig AppConfig #cfg Optic A_Lens NoIx Env Env AppConfig AppConfig -> Optic A_Lens NoIx AppConfig AppConfig CookieConfig CookieConfig -> Optic' A_Lens NoIx Env CookieConfig forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a b. (JoinKinds k l m, AppendIndices is js ks) => Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b % Optic A_Lens NoIx AppConfig AppConfig CookieConfig CookieConfig #cookie) (Text -> Maybe Text -> Text forall a. a -> Maybe a -> a fromMaybe Text "/songs" Maybe Text maybeReferer) ([(Text, Text)] -> Map Text Text forall k a. Ord k => [(k, a)] -> Map k a Map.fromList [(Text paletteCookieName, Text palette')]) where palette' :: Text palette' = MultipartData tag -> Text -> Text -> Text forall tag. MultipartData tag -> Text -> Text -> Text fromForm MultipartData tag multipartData Text "mauve" Text "palette"