{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NoFieldSelectors #-}
{-# OPTIONS_GHC -fno-warn-ambiguous-fields #-}
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
module WikiMusic.Beam.Util where
import Data.UUID qualified as UUID
import Database.Beam
import Optics
import Relude
import Relude.Unsafe qualified as Unsafe
import WikiMusic.Model.Artwork
import WikiMusic.Model.Comment
import WikiMusic.Model.Opinion
textToUUID :: Text -> UUID.UUID
textToUUID :: Text -> UUID
textToUUID = Maybe UUID -> UUID
forall a. HasCallStack => Maybe a -> a
Unsafe.fromJust (Maybe UUID -> UUID) -> (Text -> Maybe UUID) -> Text -> UUID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe UUID
UUID.fromText
fromPersistenceArtwork :: s -> Artwork
fromPersistenceArtwork s
x =
Artwork
{ $sel:identifier:Artwork :: UUID
identifier = Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ s
x s -> Optic' k NoIx s Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s Text
#identifier,
$sel:createdBy:Artwork :: UUID
createdBy = Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ s
x s -> Optic' k NoIx s Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s Text
#createdBy,
$sel:visibilityStatus:Artwork :: Int
visibilityStatus = a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> Int) -> a -> Int
forall a b. (a -> b) -> a -> b
$ s
x s -> Optic' k NoIx s a -> a
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s a
#visibilityStatus,
$sel:approvedBy:Artwork :: Maybe UUID
approvedBy = (Text -> UUID) -> Maybe Text -> Maybe UUID
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> UUID
textToUUID (Maybe Text -> Maybe UUID) -> Maybe Text -> Maybe UUID
forall a b. (a -> b) -> a -> b
$ s
x s -> Optic' k NoIx s (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s (Maybe Text)
#approvedBy,
$sel:contentUrl:Artwork :: Text
contentUrl = s
x s -> Optic' k NoIx s Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s Text
#contentUrl,
$sel:contentCaption:Artwork :: Maybe Text
contentCaption = s
x s -> Optic' k NoIx s (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s (Maybe Text)
#contentCaption,
$sel:orderValue:Artwork :: Int
orderValue = a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> Int) -> a -> Int
forall a b. (a -> b) -> a -> b
$ s
x s -> Optic' k NoIx s a -> a
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s a
#orderValue,
$sel:createdAt:Artwork :: UTCTime
createdAt = s
x s -> Optic' k NoIx s UTCTime -> UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s UTCTime
#createdAt,
$sel:lastEditedAt:Artwork :: Maybe UTCTime
lastEditedAt = s
x s -> Optic' k NoIx s (Maybe UTCTime) -> Maybe UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s (Maybe UTCTime)
#lastEditedAt
}
s
x =
Comment
{ $sel:identifier:Comment :: UUID
identifier = Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ s
x s -> Optic' k NoIx s Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s Text
#identifier,
$sel:parentIdentifier:Comment :: Maybe UUID
parentIdentifier = (Text -> UUID) -> Maybe Text -> Maybe UUID
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> UUID
textToUUID (Maybe Text -> Maybe UUID) -> Maybe Text -> Maybe UUID
forall a b. (a -> b) -> a -> b
$ s
x s -> Optic' k NoIx s (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s (Maybe Text)
#parentIdentifier,
$sel:createdBy:Comment :: UUID
createdBy = Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ s
x s -> Optic' k NoIx s Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s Text
#createdBy,
$sel:visibilityStatus:Comment :: Int
visibilityStatus = a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> Int) -> a -> Int
forall a b. (a -> b) -> a -> b
$ s
x s -> Optic' k NoIx s a -> a
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s a
#visibilityStatus,
$sel:contents:Comment :: Text
contents = s
x s -> Optic' k NoIx s Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s Text
#contents,
$sel:approvedBy:Comment :: Maybe UUID
approvedBy = (Text -> UUID) -> Maybe Text -> Maybe UUID
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> UUID
textToUUID (Maybe Text -> Maybe UUID) -> Maybe Text -> Maybe UUID
forall a b. (a -> b) -> a -> b
$ s
x s -> Optic' k NoIx s (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s (Maybe Text)
#approvedBy,
$sel:createdAt:Comment :: UTCTime
createdAt = s
x s -> Optic' k NoIx s UTCTime -> UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s UTCTime
#createdAt,
$sel:lastEditedAt:Comment :: Maybe UTCTime
lastEditedAt = s
x s -> Optic' k NoIx s (Maybe UTCTime) -> Maybe UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s (Maybe UTCTime)
#lastEditedAt
}
fromPersistenceOpinion :: s -> Opinion
fromPersistenceOpinion s
x =
Opinion
{ $sel:identifier:Opinion :: UUID
identifier = Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ s
x s -> Optic' k NoIx s Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s Text
#identifier,
$sel:createdBy:Opinion :: UUID
createdBy = Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ s
x s -> Optic' k NoIx s Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s Text
#createdBy,
$sel:isLike:Opinion :: Bool
isLike = s
x s -> Optic' k NoIx s Bool -> Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s Bool
#isLike,
$sel:isDislike:Opinion :: Bool
isDislike = s
x s -> Optic' k NoIx s Bool -> Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s Bool
#isDislike,
$sel:createdAt:Opinion :: UTCTime
createdAt = s
x s -> Optic' k NoIx s UTCTime -> UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s UTCTime
#createdAt,
$sel:lastEditedAt:Opinion :: Maybe UTCTime
lastEditedAt = s
x s -> Optic' k NoIx s (Maybe UTCTime) -> Maybe UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s (Maybe UTCTime)
#lastEditedAt
}
fromPersistenceExternalSource :: s -> ExternalSources
fromPersistenceExternalSource s
x =
ExternalSources
{ $sel:spotifyUrl:ExternalSources :: Maybe Text
spotifyUrl = s
x s -> Optic' k NoIx s (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s (Maybe Text)
#spotifyUrl,
$sel:youtubeUrl:ExternalSources :: Maybe Text
youtubeUrl = s
x s -> Optic' k NoIx s (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s (Maybe Text)
#youtubeUrl,
$sel:soundcloudUrl:ExternalSources :: Maybe Text
soundcloudUrl = s
x s -> Optic' k NoIx s (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s (Maybe Text)
#soundcloudUrl,
$sel:wikipediaUrl:ExternalSources :: Maybe Text
wikipediaUrl = s
x s -> Optic' k NoIx s (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' k NoIx s (Maybe Text)
#wikipediaUrl
}
data ExternalSources = ExternalSources
{ ExternalSources -> Maybe Text
spotifyUrl :: Maybe Text,
ExternalSources -> Maybe Text
youtubeUrl :: Maybe Text,
ExternalSources -> Maybe Text
soundcloudUrl :: Maybe Text,
ExternalSources -> Maybe Text
wikipediaUrl :: Maybe Text
}
deriving ((forall x. ExternalSources -> Rep ExternalSources x)
-> (forall x. Rep ExternalSources x -> ExternalSources)
-> Generic ExternalSources
forall x. Rep ExternalSources x -> ExternalSources
forall x. ExternalSources -> Rep ExternalSources x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExternalSources -> Rep ExternalSources x
from :: forall x. ExternalSources -> Rep ExternalSources x
$cto :: forall x. Rep ExternalSources x -> ExternalSources
to :: forall x. Rep ExternalSources x -> ExternalSources
Generic, ExternalSources -> ExternalSources -> Bool
(ExternalSources -> ExternalSources -> Bool)
-> (ExternalSources -> ExternalSources -> Bool)
-> Eq ExternalSources
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExternalSources -> ExternalSources -> Bool
== :: ExternalSources -> ExternalSources -> Bool
$c/= :: ExternalSources -> ExternalSources -> Bool
/= :: ExternalSources -> ExternalSources -> Bool
Eq, Int -> ExternalSources -> ShowS
[ExternalSources] -> ShowS
ExternalSources -> String
(Int -> ExternalSources -> ShowS)
-> (ExternalSources -> String)
-> ([ExternalSources] -> ShowS)
-> Show ExternalSources
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExternalSources -> ShowS
showsPrec :: Int -> ExternalSources -> ShowS
$cshow :: ExternalSources -> String
show :: ExternalSources -> String
$cshowList :: [ExternalSources] -> ShowS
showList :: [ExternalSources] -> ShowS
Show)
makeFieldLabelsNoPrefix ''ExternalSources
emptyExternalSources :: ExternalSources
emptyExternalSources :: ExternalSources
emptyExternalSources =
ExternalSources
{ $sel:spotifyUrl:ExternalSources :: Maybe Text
spotifyUrl = Maybe Text
forall a. Maybe a
Nothing,
$sel:youtubeUrl:ExternalSources :: Maybe Text
youtubeUrl = Maybe Text
forall a. Maybe a
Nothing,
$sel:soundcloudUrl:ExternalSources :: Maybe Text
soundcloudUrl = Maybe Text
forall a. Maybe a
Nothing,
$sel:wikipediaUrl:ExternalSources :: Maybe Text
wikipediaUrl = Maybe Text
forall a. Maybe a
Nothing
}