{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NoFieldSelectors #-}
{-# OPTIONS_GHC -fno-warn-ambiguous-fields #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module WikiMusic.Beam.Genre where
import Data.Map qualified as Map
import Data.UUID qualified as UUID
import Database.Beam
import Optics
import WikiMusic.Beam.Util
import WikiMusic.Model.Genre
import WikiMusic.Protolude
data GenreT f = Genre'
{ forall (f :: * -> *). GenreT f -> C f Text
identifier :: C f Text,
forall (f :: * -> *). GenreT f -> C f (Maybe Text)
parentIdentifier :: C f (Maybe Text),
forall (f :: * -> *). GenreT f -> C f Text
displayName :: C f Text,
forall (f :: * -> *). GenreT f -> C f Text
createdBy :: C f Text,
forall (f :: * -> *). GenreT f -> C f Int64
visibilityStatus :: C f Int64,
forall (f :: * -> *). GenreT f -> C f (Maybe Text)
approvedBy :: C f (Maybe Text),
forall (f :: * -> *). GenreT f -> C f UTCTime
createdAt :: C f UTCTime,
forall (f :: * -> *). GenreT f -> C f (Maybe UTCTime)
lastEditedAt :: C f (Maybe UTCTime),
forall (f :: * -> *). GenreT f -> C f Int64
viewCount :: C f Int64,
forall (f :: * -> *). GenreT f -> C f (Maybe Text)
description :: C f (Maybe Text)
}
deriving ((forall x. GenreT f -> Rep (GenreT f) x)
-> (forall x. Rep (GenreT f) x -> GenreT f) -> Generic (GenreT f)
forall x. Rep (GenreT f) x -> GenreT f
forall x. GenreT f -> Rep (GenreT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (GenreT f) x -> GenreT f
forall (f :: * -> *) x. GenreT f -> Rep (GenreT f) x
$cfrom :: forall (f :: * -> *) x. GenreT f -> Rep (GenreT f) x
from :: forall x. GenreT f -> Rep (GenreT f) x
$cto :: forall (f :: * -> *) x. Rep (GenreT f) x -> GenreT f
to :: forall x. Rep (GenreT f) x -> GenreT f
Generic, TableSkeleton GenreT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreT f -> GenreT g -> m (GenreT h))
-> TableSkeleton GenreT -> Beamable GenreT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreT f -> GenreT g -> m (GenreT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreT f -> GenreT g -> m (GenreT h)
zipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreT f -> GenreT g -> m (GenreT h)
$ctblSkeleton :: TableSkeleton GenreT
tblSkeleton :: TableSkeleton GenreT
Beamable)
makeFieldLabelsNoPrefix ''GenreT
type Genre' = GenreT Identity
instance Table GenreT where
data PrimaryKey GenreT f = GenreId (Columnar f Text) deriving ((forall x. PrimaryKey GenreT f -> Rep (PrimaryKey GenreT f) x)
-> (forall x. Rep (PrimaryKey GenreT f) x -> PrimaryKey GenreT f)
-> Generic (PrimaryKey GenreT f)
forall x. Rep (PrimaryKey GenreT f) x -> PrimaryKey GenreT f
forall x. PrimaryKey GenreT f -> Rep (PrimaryKey GenreT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey GenreT f) x -> PrimaryKey GenreT f
forall (f :: * -> *) x.
PrimaryKey GenreT f -> Rep (PrimaryKey GenreT f) x
$cfrom :: forall (f :: * -> *) x.
PrimaryKey GenreT f -> Rep (PrimaryKey GenreT f) x
from :: forall x. PrimaryKey GenreT f -> Rep (PrimaryKey GenreT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey GenreT f) x -> PrimaryKey GenreT f
to :: forall x. Rep (PrimaryKey GenreT f) x -> PrimaryKey GenreT f
Generic, TableSkeleton (PrimaryKey GenreT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreT f
-> PrimaryKey GenreT g
-> m (PrimaryKey GenreT h))
-> TableSkeleton (PrimaryKey GenreT)
-> Beamable (PrimaryKey GenreT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreT f
-> PrimaryKey GenreT g
-> m (PrimaryKey GenreT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreT f
-> PrimaryKey GenreT g
-> m (PrimaryKey GenreT h)
zipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreT f
-> PrimaryKey GenreT g
-> m (PrimaryKey GenreT h)
$ctblSkeleton :: TableSkeleton (PrimaryKey GenreT)
tblSkeleton :: TableSkeleton (PrimaryKey GenreT)
Beamable)
primaryKey :: forall (column :: * -> *).
GenreT column -> PrimaryKey GenreT column
primaryKey = Columnar column Text -> PrimaryKey GenreT column
forall (f :: * -> *). Columnar f Text -> PrimaryKey GenreT f
GenreId (Columnar column Text -> PrimaryKey GenreT column)
-> (GenreT column -> Columnar column Text)
-> GenreT column
-> PrimaryKey GenreT column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenreT column
-> Optic' A_Lens NoIx (GenreT column) (Columnar column Text)
-> Columnar column Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx (GenreT column) (Columnar column Text)
#identifier)
fromGenrePk :: PrimaryKey GenreT f -> Columnar f Text
fromGenrePk :: forall (f :: * -> *). PrimaryKey GenreT f -> Columnar f Text
fromGenrePk (GenreId Columnar f Text
i) = Columnar f Text
i
toGenre :: Genre' -> ExternalSources -> (UUID, Genre)
toGenre :: Genre' -> ExternalSources -> (UUID, Genre)
toGenre Genre'
x ExternalSources
ex =
( Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ Genre'
x Genre' -> Optic' A_Lens NoIx Genre' Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre' Text
#identifier,
Genre
{ $sel:identifier:Genre :: UUID
identifier = Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ Genre'
x Genre' -> Optic' A_Lens NoIx Genre' Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre' Text
#identifier,
$sel:parentIdentifier:Genre :: 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
$ Genre'
x Genre' -> Optic' A_Lens NoIx Genre' (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre' (Maybe Text)
#parentIdentifier,
$sel:displayName:Genre :: Text
displayName = Genre'
x Genre' -> Optic' A_Lens NoIx Genre' Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre' Text
#displayName,
$sel:createdBy:Genre :: UUID
createdBy = Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ Genre'
x Genre' -> Optic' A_Lens NoIx Genre' Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre' Text
#createdBy,
$sel:visibilityStatus:Genre :: Int
visibilityStatus = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int) -> Int64 -> Int
forall a b. (a -> b) -> a -> b
$ Genre'
x Genre' -> Optic' A_Lens NoIx Genre' Int64 -> Int64
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre' Int64
#visibilityStatus,
$sel:approvedBy:Genre :: 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
$ Genre'
x Genre' -> Optic' A_Lens NoIx Genre' (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre' (Maybe Text)
#approvedBy,
$sel:createdAt:Genre :: UTCTime
createdAt = Genre'
x Genre' -> Optic' A_Lens NoIx Genre' UTCTime -> UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre' UTCTime
#createdAt,
$sel:lastEditedAt:Genre :: Maybe UTCTime
lastEditedAt = Genre'
x Genre'
-> Optic' A_Lens NoIx Genre' (Maybe UTCTime) -> Maybe UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre' (Maybe UTCTime)
#lastEditedAt,
$sel:viewCount:Genre :: Int
viewCount = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int) -> Int64 -> Int
forall a b. (a -> b) -> a -> b
$ Genre'
x Genre' -> Optic' A_Lens NoIx Genre' Int64 -> Int64
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre' Int64
#viewCount,
$sel:description:Genre :: Maybe Text
description = Genre'
x Genre' -> Optic' A_Lens NoIx Genre' (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre' (Maybe Text)
#description,
$sel:artworks:Genre :: Map UUID GenreArtwork
artworks = Map UUID GenreArtwork
forall k a. Map k a
Map.empty,
$sel:comments:Genre :: [ThreadRender GenreComment]
comments = [],
$sel:opinions:Genre :: Map UUID GenreOpinion
opinions = Map UUID GenreOpinion
forall k a. Map k a
Map.empty,
$sel:spotifyUrl:Genre :: Maybe Text
spotifyUrl = ExternalSources
ex ExternalSources
-> Optic' A_Lens NoIx ExternalSources (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ExternalSources (Maybe Text)
#spotifyUrl,
$sel:youtubeUrl:Genre :: Maybe Text
youtubeUrl = ExternalSources
ex ExternalSources
-> Optic' A_Lens NoIx ExternalSources (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ExternalSources (Maybe Text)
#youtubeUrl,
$sel:soundcloudUrl:Genre :: Maybe Text
soundcloudUrl = ExternalSources
ex ExternalSources
-> Optic' A_Lens NoIx ExternalSources (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ExternalSources (Maybe Text)
#soundcloudUrl,
$sel:wikipediaUrl:Genre :: Maybe Text
wikipediaUrl = ExternalSources
ex ExternalSources
-> Optic' A_Lens NoIx ExternalSources (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ExternalSources (Maybe Text)
#wikipediaUrl
}
)
toPersistenceGenre :: Genre -> Genre'
toPersistenceGenre :: Genre -> Genre'
toPersistenceGenre Genre
x =
Genre'
{ $sel:identifier:Genre' :: C Identity Text
identifier = UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ Genre
x Genre -> Optic' A_Lens NoIx Genre UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre UUID
#identifier,
$sel:parentIdentifier:Genre' :: C Identity (Maybe Text)
parentIdentifier = (UUID -> Text) -> Maybe UUID -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap UUID -> Text
UUID.toText (Maybe UUID -> Maybe Text) -> Maybe UUID -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Genre
x Genre -> Optic' A_Lens NoIx Genre (Maybe UUID) -> Maybe UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre (Maybe UUID)
#parentIdentifier,
$sel:displayName:Genre' :: C Identity Text
displayName = Genre
x Genre -> Optic' A_Lens NoIx Genre Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre Text
#displayName,
$sel:createdBy:Genre' :: C Identity Text
createdBy = UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ Genre
x Genre -> Optic' A_Lens NoIx Genre UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre UUID
#createdBy,
$sel:visibilityStatus:Genre' :: C Identity Int64
visibilityStatus = Int -> C Identity Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> C Identity Int64) -> Int -> C Identity Int64
forall a b. (a -> b) -> a -> b
$ Genre
x Genre -> Optic' A_Lens NoIx Genre Int -> Int
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre Int
#visibilityStatus,
$sel:approvedBy:Genre' :: C Identity (Maybe Text)
approvedBy = (UUID -> Text) -> Maybe UUID -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap UUID -> Text
UUID.toText (Maybe UUID -> Maybe Text) -> Maybe UUID -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Genre
x Genre -> Optic' A_Lens NoIx Genre (Maybe UUID) -> Maybe UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre (Maybe UUID)
#approvedBy,
$sel:createdAt:Genre' :: C Identity UTCTime
createdAt = Genre
x Genre -> Optic' A_Lens NoIx Genre UTCTime -> UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre UTCTime
#createdAt,
$sel:lastEditedAt:Genre' :: C Identity (Maybe UTCTime)
lastEditedAt = Genre
x Genre -> Optic' A_Lens NoIx Genre (Maybe UTCTime) -> Maybe UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre (Maybe UTCTime)
#lastEditedAt,
$sel:viewCount:Genre' :: C Identity Int64
viewCount = Int -> C Identity Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> C Identity Int64) -> Int -> C Identity Int64
forall a b. (a -> b) -> a -> b
$ Genre
x Genre -> Optic' A_Lens NoIx Genre Int -> Int
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre Int
#viewCount,
$sel:description:Genre' :: C Identity (Maybe Text)
description = Genre
x Genre -> Optic' A_Lens NoIx Genre (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre (Maybe Text)
#description
}
data f =
{ :: C f Text,
:: C f (Maybe Text),
:: PrimaryKey GenreT f,
:: C f Text,
:: C f Int64,
:: C f Text,
:: C f (Maybe Text),
:: C f UTCTime,
:: C f (Maybe UTCTime)
}
deriving ((forall x. GenreCommentT f -> Rep (GenreCommentT f) x)
-> (forall x. Rep (GenreCommentT f) x -> GenreCommentT f)
-> Generic (GenreCommentT f)
forall x. Rep (GenreCommentT f) x -> GenreCommentT f
forall x. GenreCommentT f -> Rep (GenreCommentT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (GenreCommentT f) x -> GenreCommentT f
forall (f :: * -> *) x. GenreCommentT f -> Rep (GenreCommentT f) x
$cfrom :: forall (f :: * -> *) x. GenreCommentT f -> Rep (GenreCommentT f) x
from :: forall x. GenreCommentT f -> Rep (GenreCommentT f) x
$cto :: forall (f :: * -> *) x. Rep (GenreCommentT f) x -> GenreCommentT f
to :: forall x. Rep (GenreCommentT f) x -> GenreCommentT f
Generic, TableSkeleton GenreCommentT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreCommentT f -> GenreCommentT g -> m (GenreCommentT h))
-> TableSkeleton GenreCommentT -> Beamable GenreCommentT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreCommentT f -> GenreCommentT g -> m (GenreCommentT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreCommentT f -> GenreCommentT g -> m (GenreCommentT h)
zipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreCommentT f -> GenreCommentT g -> m (GenreCommentT h)
$ctblSkeleton :: TableSkeleton GenreCommentT
tblSkeleton :: TableSkeleton GenreCommentT
Beamable)
type = GenreCommentT Identity
instance Table GenreCommentT where
data PrimaryKey GenreCommentT f = (Columnar f Text) deriving ((forall x.
PrimaryKey GenreCommentT f -> Rep (PrimaryKey GenreCommentT f) x)
-> (forall x.
Rep (PrimaryKey GenreCommentT f) x -> PrimaryKey GenreCommentT f)
-> Generic (PrimaryKey GenreCommentT f)
forall x.
Rep (PrimaryKey GenreCommentT f) x -> PrimaryKey GenreCommentT f
forall x.
PrimaryKey GenreCommentT f -> Rep (PrimaryKey GenreCommentT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey GenreCommentT f) x -> PrimaryKey GenreCommentT f
forall (f :: * -> *) x.
PrimaryKey GenreCommentT f -> Rep (PrimaryKey GenreCommentT f) x
$cfrom :: forall (f :: * -> *) x.
PrimaryKey GenreCommentT f -> Rep (PrimaryKey GenreCommentT f) x
from :: forall x.
PrimaryKey GenreCommentT f -> Rep (PrimaryKey GenreCommentT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey GenreCommentT f) x -> PrimaryKey GenreCommentT f
to :: forall x.
Rep (PrimaryKey GenreCommentT f) x -> PrimaryKey GenreCommentT f
Generic, TableSkeleton (PrimaryKey GenreCommentT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreCommentT f
-> PrimaryKey GenreCommentT g
-> m (PrimaryKey GenreCommentT h))
-> TableSkeleton (PrimaryKey GenreCommentT)
-> Beamable (PrimaryKey GenreCommentT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreCommentT f
-> PrimaryKey GenreCommentT g
-> m (PrimaryKey GenreCommentT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreCommentT f
-> PrimaryKey GenreCommentT g
-> m (PrimaryKey GenreCommentT h)
zipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreCommentT f
-> PrimaryKey GenreCommentT g
-> m (PrimaryKey GenreCommentT h)
$ctblSkeleton :: TableSkeleton (PrimaryKey GenreCommentT)
tblSkeleton :: TableSkeleton (PrimaryKey GenreCommentT)
Beamable)
primaryKey :: forall (column :: * -> *).
GenreCommentT column -> PrimaryKey GenreCommentT column
primaryKey = Columnar column Text -> PrimaryKey GenreCommentT column
forall (f :: * -> *). Columnar f Text -> PrimaryKey GenreCommentT f
GenreCommentId (Columnar column Text -> PrimaryKey GenreCommentT column)
-> (GenreCommentT column -> Columnar column Text)
-> GenreCommentT column
-> PrimaryKey GenreCommentT column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenreCommentT column
-> Optic' A_Lens NoIx (GenreCommentT column) (Columnar column Text)
-> Columnar column Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx (GenreCommentT column) (Columnar column Text)
#identifier)
makeFieldLabelsNoPrefix ''GenreCommentT
toGenreComment :: GenreComment' -> (UUID, GenreComment)
GenreComment'
x =
( Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ GenreComment'
x GenreComment' -> Optic' A_Lens NoIx GenreComment' Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreComment' Text
#identifier,
GenreComment
{ $sel:genreIdentifier:GenreComment :: UUID
genreIdentifier = Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ PrimaryKey GenreT Identity -> C Identity Text
forall (f :: * -> *). PrimaryKey GenreT f -> Columnar f Text
fromGenrePk (PrimaryKey GenreT Identity -> C Identity Text)
-> PrimaryKey GenreT Identity -> C Identity Text
forall a b. (a -> b) -> a -> b
$ GenreComment'
x GenreComment'
-> Optic' A_Lens NoIx GenreComment' (PrimaryKey GenreT Identity)
-> PrimaryKey GenreT Identity
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreComment' (PrimaryKey GenreT Identity)
#genreIdentifier,
$sel:comment:GenreComment :: Comment
comment = GenreComment' -> Comment
forall {k1} {k2} {k3} {k4} {k5} {k6} {k7} {k8} {a} {s}.
(Is k1 A_Getter, Is k2 A_Getter, Is k3 A_Getter, Is k4 A_Getter,
Is k5 A_Getter, Is k6 A_Getter, Is k7 A_Getter, Is k8 A_Getter,
Integral a, LabelOptic "contents" k7 s s Text Text,
LabelOptic "identifier" k5 s s Text Text,
LabelOptic "createdBy" k6 s s Text Text,
LabelOptic "visibilityStatus" k3 s s a a,
LabelOptic "approvedBy" k2 s s (Maybe Text) (Maybe Text),
LabelOptic "createdAt" k8 s s UTCTime UTCTime,
LabelOptic "lastEditedAt" k1 s s (Maybe UTCTime) (Maybe UTCTime),
LabelOptic "parentIdentifier" k4 s s (Maybe Text) (Maybe Text)) =>
s -> Comment
fromPersistenceComment GenreComment'
x
}
)
mkGenreCommentP :: GenreComment -> GenreComment'
GenreComment
x =
GenreComment'
{ $sel:identifier:GenreComment' :: C Identity Text
identifier = UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ GenreComment
x GenreComment -> Optic' A_Lens NoIx GenreComment UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreComment GenreComment Comment Comment
#comment Optic A_Lens NoIx GenreComment GenreComment Comment Comment
-> Optic A_Lens NoIx Comment Comment UUID UUID
-> Optic' A_Lens NoIx GenreComment UUID
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 Comment Comment UUID UUID
#identifier,
$sel:parentIdentifier:GenreComment' :: C Identity (Maybe Text)
parentIdentifier = (UUID -> Text) -> Maybe UUID -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap UUID -> Text
UUID.toText (Maybe UUID -> Maybe Text) -> Maybe UUID -> Maybe Text
forall a b. (a -> b) -> a -> b
$ GenreComment
x GenreComment
-> Optic' A_Lens NoIx GenreComment (Maybe UUID) -> Maybe UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreComment GenreComment Comment Comment
#comment Optic A_Lens NoIx GenreComment GenreComment Comment Comment
-> Optic A_Lens NoIx Comment Comment (Maybe UUID) (Maybe UUID)
-> Optic' A_Lens NoIx GenreComment (Maybe UUID)
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 Comment Comment (Maybe UUID) (Maybe UUID)
#parentIdentifier,
$sel:genreIdentifier:GenreComment' :: PrimaryKey GenreT Identity
genreIdentifier = C Identity Text -> PrimaryKey GenreT Identity
forall (f :: * -> *). Columnar f Text -> PrimaryKey GenreT f
GenreId (C Identity Text -> PrimaryKey GenreT Identity)
-> C Identity Text -> PrimaryKey GenreT Identity
forall a b. (a -> b) -> a -> b
$ UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ GenreComment
x GenreComment -> Optic' A_Lens NoIx GenreComment UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreComment UUID
#genreIdentifier,
$sel:createdBy:GenreComment' :: C Identity Text
createdBy = UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ GenreComment
x GenreComment -> Optic' A_Lens NoIx GenreComment UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreComment GenreComment Comment Comment
#comment Optic A_Lens NoIx GenreComment GenreComment Comment Comment
-> Optic A_Lens NoIx Comment Comment UUID UUID
-> Optic' A_Lens NoIx GenreComment UUID
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 Comment Comment UUID UUID
#createdBy,
$sel:visibilityStatus:GenreComment' :: C Identity Int64
visibilityStatus = Int -> C Identity Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> C Identity Int64) -> Int -> C Identity Int64
forall a b. (a -> b) -> a -> b
$ GenreComment
x GenreComment -> Optic' A_Lens NoIx GenreComment Int -> Int
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreComment GenreComment Comment Comment
#comment Optic A_Lens NoIx GenreComment GenreComment Comment Comment
-> Optic A_Lens NoIx Comment Comment Int Int
-> Optic' A_Lens NoIx GenreComment Int
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 Comment Comment Int Int
#visibilityStatus,
$sel:contents:GenreComment' :: C Identity Text
contents = GenreComment
x GenreComment -> Optic' A_Lens NoIx GenreComment Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreComment GenreComment Comment Comment
#comment Optic A_Lens NoIx GenreComment GenreComment Comment Comment
-> Optic A_Lens NoIx Comment Comment Text Text
-> Optic' A_Lens NoIx GenreComment Text
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 Comment Comment Text Text
#contents,
$sel:approvedBy:GenreComment' :: C Identity (Maybe Text)
approvedBy = (UUID -> Text) -> Maybe UUID -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap UUID -> Text
UUID.toText (Maybe UUID -> Maybe Text) -> Maybe UUID -> Maybe Text
forall a b. (a -> b) -> a -> b
$ GenreComment
x GenreComment
-> Optic' A_Lens NoIx GenreComment (Maybe UUID) -> Maybe UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreComment GenreComment Comment Comment
#comment Optic A_Lens NoIx GenreComment GenreComment Comment Comment
-> Optic A_Lens NoIx Comment Comment (Maybe UUID) (Maybe UUID)
-> Optic' A_Lens NoIx GenreComment (Maybe UUID)
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 Comment Comment (Maybe UUID) (Maybe UUID)
#approvedBy,
$sel:createdAt:GenreComment' :: C Identity UTCTime
createdAt = GenreComment
x GenreComment -> Optic' A_Lens NoIx GenreComment UTCTime -> UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreComment GenreComment Comment Comment
#comment Optic A_Lens NoIx GenreComment GenreComment Comment Comment
-> Optic A_Lens NoIx Comment Comment UTCTime UTCTime
-> Optic' A_Lens NoIx GenreComment UTCTime
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 Comment Comment UTCTime UTCTime
#createdAt,
$sel:lastEditedAt:GenreComment' :: C Identity (Maybe UTCTime)
lastEditedAt = GenreComment
x GenreComment
-> Optic' A_Lens NoIx GenreComment (Maybe UTCTime) -> Maybe UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreComment GenreComment Comment Comment
#comment Optic A_Lens NoIx GenreComment GenreComment Comment Comment
-> Optic
A_Lens NoIx Comment Comment (Maybe UTCTime) (Maybe UTCTime)
-> Optic' A_Lens NoIx GenreComment (Maybe UTCTime)
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 Comment Comment (Maybe UTCTime) (Maybe UTCTime)
#lastEditedAt
}
data GenreArtworkT f = GenreArtwork'
{ forall (f :: * -> *). GenreArtworkT f -> C f Text
identifier :: C f Text,
forall (f :: * -> *). GenreArtworkT f -> PrimaryKey GenreT f
genreIdentifier :: PrimaryKey GenreT f,
forall (f :: * -> *). GenreArtworkT f -> C f Text
createdBy :: C f Text,
forall (f :: * -> *). GenreArtworkT f -> C f Int64
visibilityStatus :: C f Int64,
forall (f :: * -> *). GenreArtworkT f -> C f (Maybe Text)
approvedBy :: C f (Maybe Text),
forall (f :: * -> *). GenreArtworkT f -> C f Text
contentUrl :: C f Text,
forall (f :: * -> *). GenreArtworkT f -> C f (Maybe Text)
contentCaption :: C f (Maybe Text),
forall (f :: * -> *). GenreArtworkT f -> C f Int64
orderValue :: C f Int64,
forall (f :: * -> *). GenreArtworkT f -> C f UTCTime
createdAt :: C f UTCTime,
forall (f :: * -> *). GenreArtworkT f -> C f (Maybe UTCTime)
lastEditedAt :: C f (Maybe UTCTime)
}
deriving ((forall x. GenreArtworkT f -> Rep (GenreArtworkT f) x)
-> (forall x. Rep (GenreArtworkT f) x -> GenreArtworkT f)
-> Generic (GenreArtworkT f)
forall x. Rep (GenreArtworkT f) x -> GenreArtworkT f
forall x. GenreArtworkT f -> Rep (GenreArtworkT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (GenreArtworkT f) x -> GenreArtworkT f
forall (f :: * -> *) x. GenreArtworkT f -> Rep (GenreArtworkT f) x
$cfrom :: forall (f :: * -> *) x. GenreArtworkT f -> Rep (GenreArtworkT f) x
from :: forall x. GenreArtworkT f -> Rep (GenreArtworkT f) x
$cto :: forall (f :: * -> *) x. Rep (GenreArtworkT f) x -> GenreArtworkT f
to :: forall x. Rep (GenreArtworkT f) x -> GenreArtworkT f
Generic, TableSkeleton GenreArtworkT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreArtworkT f -> GenreArtworkT g -> m (GenreArtworkT h))
-> TableSkeleton GenreArtworkT -> Beamable GenreArtworkT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreArtworkT f -> GenreArtworkT g -> m (GenreArtworkT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreArtworkT f -> GenreArtworkT g -> m (GenreArtworkT h)
zipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreArtworkT f -> GenreArtworkT g -> m (GenreArtworkT h)
$ctblSkeleton :: TableSkeleton GenreArtworkT
tblSkeleton :: TableSkeleton GenreArtworkT
Beamable)
type GenreArtwork' = GenreArtworkT Identity
instance Table GenreArtworkT where
data PrimaryKey GenreArtworkT f = GenreArtworkId (Columnar f Text) deriving ((forall x.
PrimaryKey GenreArtworkT f -> Rep (PrimaryKey GenreArtworkT f) x)
-> (forall x.
Rep (PrimaryKey GenreArtworkT f) x -> PrimaryKey GenreArtworkT f)
-> Generic (PrimaryKey GenreArtworkT f)
forall x.
Rep (PrimaryKey GenreArtworkT f) x -> PrimaryKey GenreArtworkT f
forall x.
PrimaryKey GenreArtworkT f -> Rep (PrimaryKey GenreArtworkT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey GenreArtworkT f) x -> PrimaryKey GenreArtworkT f
forall (f :: * -> *) x.
PrimaryKey GenreArtworkT f -> Rep (PrimaryKey GenreArtworkT f) x
$cfrom :: forall (f :: * -> *) x.
PrimaryKey GenreArtworkT f -> Rep (PrimaryKey GenreArtworkT f) x
from :: forall x.
PrimaryKey GenreArtworkT f -> Rep (PrimaryKey GenreArtworkT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey GenreArtworkT f) x -> PrimaryKey GenreArtworkT f
to :: forall x.
Rep (PrimaryKey GenreArtworkT f) x -> PrimaryKey GenreArtworkT f
Generic, TableSkeleton (PrimaryKey GenreArtworkT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreArtworkT f
-> PrimaryKey GenreArtworkT g
-> m (PrimaryKey GenreArtworkT h))
-> TableSkeleton (PrimaryKey GenreArtworkT)
-> Beamable (PrimaryKey GenreArtworkT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreArtworkT f
-> PrimaryKey GenreArtworkT g
-> m (PrimaryKey GenreArtworkT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreArtworkT f
-> PrimaryKey GenreArtworkT g
-> m (PrimaryKey GenreArtworkT h)
zipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreArtworkT f
-> PrimaryKey GenreArtworkT g
-> m (PrimaryKey GenreArtworkT h)
$ctblSkeleton :: TableSkeleton (PrimaryKey GenreArtworkT)
tblSkeleton :: TableSkeleton (PrimaryKey GenreArtworkT)
Beamable)
primaryKey :: forall (column :: * -> *).
GenreArtworkT column -> PrimaryKey GenreArtworkT column
primaryKey = Columnar column Text -> PrimaryKey GenreArtworkT column
forall (f :: * -> *). Columnar f Text -> PrimaryKey GenreArtworkT f
GenreArtworkId (Columnar column Text -> PrimaryKey GenreArtworkT column)
-> (GenreArtworkT column -> Columnar column Text)
-> GenreArtworkT column
-> PrimaryKey GenreArtworkT column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenreArtworkT column
-> Optic' A_Lens NoIx (GenreArtworkT column) (Columnar column Text)
-> Columnar column Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx (GenreArtworkT column) (Columnar column Text)
#identifier)
makeFieldLabelsNoPrefix ''GenreArtworkT
toGenreArtwork :: GenreArtwork' -> (UUID, GenreArtwork)
toGenreArtwork :: GenreArtwork' -> (UUID, GenreArtwork)
toGenreArtwork GenreArtwork'
x =
( Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ GenreArtwork'
x GenreArtwork' -> Optic' A_Lens NoIx GenreArtwork' Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreArtwork' Text
#identifier,
GenreArtwork
{ $sel:genreIdentifier:GenreArtwork :: UUID
genreIdentifier = Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ PrimaryKey GenreT Identity -> C Identity Text
forall (f :: * -> *). PrimaryKey GenreT f -> Columnar f Text
fromGenrePk (PrimaryKey GenreT Identity -> C Identity Text)
-> PrimaryKey GenreT Identity -> C Identity Text
forall a b. (a -> b) -> a -> b
$ GenreArtwork'
x GenreArtwork'
-> Optic' A_Lens NoIx GenreArtwork' (PrimaryKey GenreT Identity)
-> PrimaryKey GenreT Identity
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreArtwork' (PrimaryKey GenreT Identity)
#genreIdentifier,
$sel:artwork:GenreArtwork :: Artwork
artwork = GenreArtwork' -> Artwork
forall {k1} {k2} {k3} {k4} {k5} {k6} {k7} {k8} {k9} {a1} {a2} {s}.
(Is k1 A_Getter, Is k2 A_Getter, Is k3 A_Getter, Is k4 A_Getter,
Is k5 A_Getter, Is k6 A_Getter, Is k7 A_Getter, Is k8 A_Getter,
Is k9 A_Getter, Integral a1, Integral a2,
LabelOptic "identifier" k5 s s Text Text,
LabelOptic "createdBy" k6 s s Text Text,
LabelOptic "visibilityStatus" k4 s s a2 a2,
LabelOptic "approvedBy" k7 s s (Maybe Text) (Maybe Text),
LabelOptic "contentUrl" k3 s s Text Text,
LabelOptic "contentCaption" k8 s s (Maybe Text) (Maybe Text),
LabelOptic "orderValue" k2 s s a1 a1,
LabelOptic "createdAt" k9 s s UTCTime UTCTime,
LabelOptic
"lastEditedAt" k1 s s (Maybe UTCTime) (Maybe UTCTime)) =>
s -> Artwork
fromPersistenceArtwork GenreArtwork'
x
}
)
mkGenreArtworkP :: GenreArtwork -> GenreArtwork'
mkGenreArtworkP :: GenreArtwork -> GenreArtwork'
mkGenreArtworkP GenreArtwork
x =
GenreArtwork'
{ $sel:identifier:GenreArtwork' :: C Identity Text
identifier = UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ GenreArtwork
x GenreArtwork -> Optic' A_Lens NoIx GenreArtwork UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
#artwork Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
-> Optic A_Lens NoIx Artwork Artwork UUID UUID
-> Optic' A_Lens NoIx GenreArtwork UUID
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 Artwork Artwork UUID UUID
#identifier,
$sel:genreIdentifier:GenreArtwork' :: PrimaryKey GenreT Identity
genreIdentifier = C Identity Text -> PrimaryKey GenreT Identity
forall (f :: * -> *). Columnar f Text -> PrimaryKey GenreT f
GenreId (C Identity Text -> PrimaryKey GenreT Identity)
-> C Identity Text -> PrimaryKey GenreT Identity
forall a b. (a -> b) -> a -> b
$ UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ GenreArtwork
x GenreArtwork -> Optic' A_Lens NoIx GenreArtwork UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreArtwork UUID
#genreIdentifier,
$sel:createdBy:GenreArtwork' :: C Identity Text
createdBy = UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ GenreArtwork
x GenreArtwork -> Optic' A_Lens NoIx GenreArtwork UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
#artwork Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
-> Optic A_Lens NoIx Artwork Artwork UUID UUID
-> Optic' A_Lens NoIx GenreArtwork UUID
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 Artwork Artwork UUID UUID
#createdBy,
$sel:visibilityStatus:GenreArtwork' :: C Identity Int64
visibilityStatus = Int -> C Identity Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> C Identity Int64) -> Int -> C Identity Int64
forall a b. (a -> b) -> a -> b
$ GenreArtwork
x GenreArtwork -> Optic' A_Lens NoIx GenreArtwork Int -> Int
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
#artwork Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
-> Optic A_Lens NoIx Artwork Artwork Int Int
-> Optic' A_Lens NoIx GenreArtwork Int
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 Artwork Artwork Int Int
#visibilityStatus,
$sel:contentUrl:GenreArtwork' :: C Identity Text
contentUrl = GenreArtwork
x GenreArtwork -> Optic' A_Lens NoIx GenreArtwork Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
#artwork Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
-> Optic A_Lens NoIx Artwork Artwork Text Text
-> Optic' A_Lens NoIx GenreArtwork Text
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 Artwork Artwork Text Text
#contentUrl,
$sel:contentCaption:GenreArtwork' :: C Identity (Maybe Text)
contentCaption = GenreArtwork
x GenreArtwork
-> Optic' A_Lens NoIx GenreArtwork (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
#artwork Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
-> Optic A_Lens NoIx Artwork Artwork (Maybe Text) (Maybe Text)
-> Optic' A_Lens NoIx GenreArtwork (Maybe Text)
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 Artwork Artwork (Maybe Text) (Maybe Text)
#contentCaption,
$sel:orderValue:GenreArtwork' :: C Identity Int64
orderValue = Int -> C Identity Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> C Identity Int64) -> Int -> C Identity Int64
forall a b. (a -> b) -> a -> b
$ GenreArtwork
x GenreArtwork -> Optic' A_Lens NoIx GenreArtwork Int -> Int
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
#artwork Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
-> Optic A_Lens NoIx Artwork Artwork Int Int
-> Optic' A_Lens NoIx GenreArtwork Int
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 Artwork Artwork Int Int
#orderValue,
$sel:approvedBy:GenreArtwork' :: C Identity (Maybe Text)
approvedBy = (UUID -> Text) -> Maybe UUID -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap UUID -> Text
UUID.toText (Maybe UUID -> Maybe Text) -> Maybe UUID -> Maybe Text
forall a b. (a -> b) -> a -> b
$ GenreArtwork
x GenreArtwork
-> Optic' A_Lens NoIx GenreArtwork (Maybe UUID) -> Maybe UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
#artwork Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
-> Optic A_Lens NoIx Artwork Artwork (Maybe UUID) (Maybe UUID)
-> Optic' A_Lens NoIx GenreArtwork (Maybe UUID)
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 Artwork Artwork (Maybe UUID) (Maybe UUID)
#approvedBy,
$sel:createdAt:GenreArtwork' :: C Identity UTCTime
createdAt = GenreArtwork
x GenreArtwork -> Optic' A_Lens NoIx GenreArtwork UTCTime -> UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
#artwork Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
-> Optic A_Lens NoIx Artwork Artwork UTCTime UTCTime
-> Optic' A_Lens NoIx GenreArtwork UTCTime
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 Artwork Artwork UTCTime UTCTime
#createdAt,
$sel:lastEditedAt:GenreArtwork' :: C Identity (Maybe UTCTime)
lastEditedAt = GenreArtwork
x GenreArtwork
-> Optic' A_Lens NoIx GenreArtwork (Maybe UTCTime) -> Maybe UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
#artwork Optic A_Lens NoIx GenreArtwork GenreArtwork Artwork Artwork
-> Optic
A_Lens NoIx Artwork Artwork (Maybe UTCTime) (Maybe UTCTime)
-> Optic' A_Lens NoIx GenreArtwork (Maybe UTCTime)
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 Artwork Artwork (Maybe UTCTime) (Maybe UTCTime)
#lastEditedAt
}
data GenreOpinionT f = GenreOpinion'
{ forall (f :: * -> *). GenreOpinionT f -> C f Text
identifier :: C f Text,
forall (f :: * -> *). GenreOpinionT f -> PrimaryKey GenreT f
genreIdentifier :: PrimaryKey GenreT f,
forall (f :: * -> *). GenreOpinionT f -> C f Text
createdBy :: C f Text,
forall (f :: * -> *). GenreOpinionT f -> C f Bool
isLike :: C f Bool,
forall (f :: * -> *). GenreOpinionT f -> C f Bool
isDislike :: C f Bool,
forall (f :: * -> *). GenreOpinionT f -> C f UTCTime
createdAt :: C f UTCTime,
forall (f :: * -> *). GenreOpinionT f -> C f (Maybe UTCTime)
lastEditedAt :: C f (Maybe UTCTime)
}
deriving ((forall x. GenreOpinionT f -> Rep (GenreOpinionT f) x)
-> (forall x. Rep (GenreOpinionT f) x -> GenreOpinionT f)
-> Generic (GenreOpinionT f)
forall x. Rep (GenreOpinionT f) x -> GenreOpinionT f
forall x. GenreOpinionT f -> Rep (GenreOpinionT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (GenreOpinionT f) x -> GenreOpinionT f
forall (f :: * -> *) x. GenreOpinionT f -> Rep (GenreOpinionT f) x
$cfrom :: forall (f :: * -> *) x. GenreOpinionT f -> Rep (GenreOpinionT f) x
from :: forall x. GenreOpinionT f -> Rep (GenreOpinionT f) x
$cto :: forall (f :: * -> *) x. Rep (GenreOpinionT f) x -> GenreOpinionT f
to :: forall x. Rep (GenreOpinionT f) x -> GenreOpinionT f
Generic, TableSkeleton GenreOpinionT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreOpinionT f -> GenreOpinionT g -> m (GenreOpinionT h))
-> TableSkeleton GenreOpinionT -> Beamable GenreOpinionT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreOpinionT f -> GenreOpinionT g -> m (GenreOpinionT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreOpinionT f -> GenreOpinionT g -> m (GenreOpinionT h)
zipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreOpinionT f -> GenreOpinionT g -> m (GenreOpinionT h)
$ctblSkeleton :: TableSkeleton GenreOpinionT
tblSkeleton :: TableSkeleton GenreOpinionT
Beamable)
type GenreOpinion' = GenreOpinionT Identity
instance Table GenreOpinionT where
data PrimaryKey GenreOpinionT f = GenreOpinionId (Columnar f Text) deriving ((forall x.
PrimaryKey GenreOpinionT f -> Rep (PrimaryKey GenreOpinionT f) x)
-> (forall x.
Rep (PrimaryKey GenreOpinionT f) x -> PrimaryKey GenreOpinionT f)
-> Generic (PrimaryKey GenreOpinionT f)
forall x.
Rep (PrimaryKey GenreOpinionT f) x -> PrimaryKey GenreOpinionT f
forall x.
PrimaryKey GenreOpinionT f -> Rep (PrimaryKey GenreOpinionT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey GenreOpinionT f) x -> PrimaryKey GenreOpinionT f
forall (f :: * -> *) x.
PrimaryKey GenreOpinionT f -> Rep (PrimaryKey GenreOpinionT f) x
$cfrom :: forall (f :: * -> *) x.
PrimaryKey GenreOpinionT f -> Rep (PrimaryKey GenreOpinionT f) x
from :: forall x.
PrimaryKey GenreOpinionT f -> Rep (PrimaryKey GenreOpinionT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey GenreOpinionT f) x -> PrimaryKey GenreOpinionT f
to :: forall x.
Rep (PrimaryKey GenreOpinionT f) x -> PrimaryKey GenreOpinionT f
Generic, TableSkeleton (PrimaryKey GenreOpinionT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreOpinionT f
-> PrimaryKey GenreOpinionT g
-> m (PrimaryKey GenreOpinionT h))
-> TableSkeleton (PrimaryKey GenreOpinionT)
-> Beamable (PrimaryKey GenreOpinionT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreOpinionT f
-> PrimaryKey GenreOpinionT g
-> m (PrimaryKey GenreOpinionT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreOpinionT f
-> PrimaryKey GenreOpinionT g
-> m (PrimaryKey GenreOpinionT h)
zipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreOpinionT f
-> PrimaryKey GenreOpinionT g
-> m (PrimaryKey GenreOpinionT h)
$ctblSkeleton :: TableSkeleton (PrimaryKey GenreOpinionT)
tblSkeleton :: TableSkeleton (PrimaryKey GenreOpinionT)
Beamable)
primaryKey :: forall (column :: * -> *).
GenreOpinionT column -> PrimaryKey GenreOpinionT column
primaryKey = Columnar column Text -> PrimaryKey GenreOpinionT column
forall (f :: * -> *). Columnar f Text -> PrimaryKey GenreOpinionT f
GenreOpinionId (Columnar column Text -> PrimaryKey GenreOpinionT column)
-> (GenreOpinionT column -> Columnar column Text)
-> GenreOpinionT column
-> PrimaryKey GenreOpinionT column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenreOpinionT column
-> Optic' A_Lens NoIx (GenreOpinionT column) (Columnar column Text)
-> Columnar column Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx (GenreOpinionT column) (Columnar column Text)
#identifier)
makeFieldLabelsNoPrefix ''GenreOpinionT
toGenreOpinion :: GenreOpinion' -> (UUID, GenreOpinion)
toGenreOpinion :: GenreOpinion' -> (UUID, GenreOpinion)
toGenreOpinion GenreOpinion'
x =
( Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ GenreOpinion'
x GenreOpinion' -> Optic' A_Lens NoIx GenreOpinion' Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreOpinion' Text
#identifier,
GenreOpinion
{ $sel:genreIdentifier:GenreOpinion :: UUID
genreIdentifier = Text -> UUID
textToUUID (Text -> UUID) -> Text -> UUID
forall a b. (a -> b) -> a -> b
$ PrimaryKey GenreT Identity -> C Identity Text
forall (f :: * -> *). PrimaryKey GenreT f -> Columnar f Text
fromGenrePk (PrimaryKey GenreT Identity -> C Identity Text)
-> PrimaryKey GenreT Identity -> C Identity Text
forall a b. (a -> b) -> a -> b
$ GenreOpinion'
x GenreOpinion'
-> Optic' A_Lens NoIx GenreOpinion' (PrimaryKey GenreT Identity)
-> PrimaryKey GenreT Identity
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreOpinion' (PrimaryKey GenreT Identity)
#genreIdentifier,
$sel:opinion:GenreOpinion :: Opinion
opinion = GenreOpinion' -> Opinion
forall {k1} {k2} {k3} {k4} {k5} {k6} {s}.
(Is k1 A_Getter, Is k2 A_Getter, Is k3 A_Getter, Is k4 A_Getter,
Is k5 A_Getter, Is k6 A_Getter,
LabelOptic "identifier" k4 s s Text Text,
LabelOptic "createdBy" k3 s s Text Text,
LabelOptic "createdAt" k6 s s UTCTime UTCTime,
LabelOptic "lastEditedAt" k1 s s (Maybe UTCTime) (Maybe UTCTime),
LabelOptic "isLike" k5 s s Bool Bool,
LabelOptic "isDislike" k2 s s Bool Bool) =>
s -> Opinion
fromPersistenceOpinion GenreOpinion'
x
}
)
mkGenreOpinionP :: GenreOpinion -> GenreOpinion'
mkGenreOpinionP :: GenreOpinion -> GenreOpinion'
mkGenreOpinionP GenreOpinion
x =
GenreOpinion'
{ $sel:identifier:GenreOpinion' :: C Identity Text
identifier = UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ GenreOpinion
x GenreOpinion -> Optic' A_Lens NoIx GenreOpinion UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
#opinion Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
-> Optic A_Lens NoIx Opinion Opinion UUID UUID
-> Optic' A_Lens NoIx GenreOpinion UUID
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 Opinion Opinion UUID UUID
#identifier,
$sel:genreIdentifier:GenreOpinion' :: PrimaryKey GenreT Identity
genreIdentifier = C Identity Text -> PrimaryKey GenreT Identity
forall (f :: * -> *). Columnar f Text -> PrimaryKey GenreT f
GenreId (C Identity Text -> PrimaryKey GenreT Identity)
-> C Identity Text -> PrimaryKey GenreT Identity
forall a b. (a -> b) -> a -> b
$ UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ GenreOpinion
x GenreOpinion -> Optic' A_Lens NoIx GenreOpinion UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreOpinion UUID
#genreIdentifier,
$sel:createdBy:GenreOpinion' :: C Identity Text
createdBy = UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ GenreOpinion
x GenreOpinion -> Optic' A_Lens NoIx GenreOpinion UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
#opinion Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
-> Optic A_Lens NoIx Opinion Opinion UUID UUID
-> Optic' A_Lens NoIx GenreOpinion UUID
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 Opinion Opinion UUID UUID
#createdBy,
$sel:isLike:GenreOpinion' :: C Identity Bool
isLike = GenreOpinion
x GenreOpinion -> Optic' A_Lens NoIx GenreOpinion Bool -> Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
#opinion Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
-> Optic A_Lens NoIx Opinion Opinion Bool Bool
-> Optic' A_Lens NoIx GenreOpinion Bool
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 Opinion Opinion Bool Bool
#isLike,
$sel:isDislike:GenreOpinion' :: C Identity Bool
isDislike = GenreOpinion
x GenreOpinion -> Optic' A_Lens NoIx GenreOpinion Bool -> Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
#opinion Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
-> Optic A_Lens NoIx Opinion Opinion Bool Bool
-> Optic' A_Lens NoIx GenreOpinion Bool
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 Opinion Opinion Bool Bool
#isDislike,
$sel:createdAt:GenreOpinion' :: C Identity UTCTime
createdAt = GenreOpinion
x GenreOpinion -> Optic' A_Lens NoIx GenreOpinion UTCTime -> UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
#opinion Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
-> Optic A_Lens NoIx Opinion Opinion UTCTime UTCTime
-> Optic' A_Lens NoIx GenreOpinion UTCTime
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 Opinion Opinion UTCTime UTCTime
#createdAt,
$sel:lastEditedAt:GenreOpinion' :: C Identity (Maybe UTCTime)
lastEditedAt = GenreOpinion
x GenreOpinion
-> Optic' A_Lens NoIx GenreOpinion (Maybe UTCTime) -> Maybe UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
#opinion Optic A_Lens NoIx GenreOpinion GenreOpinion Opinion Opinion
-> Optic
A_Lens NoIx Opinion Opinion (Maybe UTCTime) (Maybe UTCTime)
-> Optic' A_Lens NoIx GenreOpinion (Maybe UTCTime)
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 Opinion Opinion (Maybe UTCTime) (Maybe UTCTime)
#lastEditedAt
}
data GenreExternalSourcesT f = GenreExternalSources'
{ forall (f :: * -> *). GenreExternalSourcesT f -> C f Text
identifier :: C f Text,
forall (f :: * -> *).
GenreExternalSourcesT f -> PrimaryKey GenreT f
genreIdentifier :: PrimaryKey GenreT f,
forall (f :: * -> *). GenreExternalSourcesT f -> C f Text
createdBy :: C f Text,
forall (f :: * -> *). GenreExternalSourcesT f -> C f (Maybe Text)
spotifyUrl :: C f (Maybe Text),
forall (f :: * -> *). GenreExternalSourcesT f -> C f (Maybe Text)
youtubeUrl :: C f (Maybe Text),
forall (f :: * -> *). GenreExternalSourcesT f -> C f (Maybe Text)
soundcloudUrl :: C f (Maybe Text),
forall (f :: * -> *). GenreExternalSourcesT f -> C f (Maybe Text)
wikipediaUrl :: C f (Maybe Text),
forall (f :: * -> *). GenreExternalSourcesT f -> C f UTCTime
createdAt :: C f UTCTime,
forall (f :: * -> *).
GenreExternalSourcesT f -> C f (Maybe UTCTime)
lastEditedAt :: C f (Maybe UTCTime)
}
deriving ((forall x.
GenreExternalSourcesT f -> Rep (GenreExternalSourcesT f) x)
-> (forall x.
Rep (GenreExternalSourcesT f) x -> GenreExternalSourcesT f)
-> Generic (GenreExternalSourcesT f)
forall x.
Rep (GenreExternalSourcesT f) x -> GenreExternalSourcesT f
forall x.
GenreExternalSourcesT f -> Rep (GenreExternalSourcesT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (GenreExternalSourcesT f) x -> GenreExternalSourcesT f
forall (f :: * -> *) x.
GenreExternalSourcesT f -> Rep (GenreExternalSourcesT f) x
$cfrom :: forall (f :: * -> *) x.
GenreExternalSourcesT f -> Rep (GenreExternalSourcesT f) x
from :: forall x.
GenreExternalSourcesT f -> Rep (GenreExternalSourcesT f) x
$cto :: forall (f :: * -> *) x.
Rep (GenreExternalSourcesT f) x -> GenreExternalSourcesT f
to :: forall x.
Rep (GenreExternalSourcesT f) x -> GenreExternalSourcesT f
Generic, TableSkeleton GenreExternalSourcesT
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreExternalSourcesT f
-> GenreExternalSourcesT g
-> m (GenreExternalSourcesT h))
-> TableSkeleton GenreExternalSourcesT
-> Beamable GenreExternalSourcesT
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreExternalSourcesT f
-> GenreExternalSourcesT g
-> m (GenreExternalSourcesT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreExternalSourcesT f
-> GenreExternalSourcesT g
-> m (GenreExternalSourcesT h)
zipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> GenreExternalSourcesT f
-> GenreExternalSourcesT g
-> m (GenreExternalSourcesT h)
$ctblSkeleton :: TableSkeleton GenreExternalSourcesT
tblSkeleton :: TableSkeleton GenreExternalSourcesT
Beamable)
type GenreExternalSources' = GenreExternalSourcesT Identity
instance Table GenreExternalSourcesT where
data PrimaryKey GenreExternalSourcesT f = GenreExternalSourcesId (Columnar f Text) deriving ((forall x.
PrimaryKey GenreExternalSourcesT f
-> Rep (PrimaryKey GenreExternalSourcesT f) x)
-> (forall x.
Rep (PrimaryKey GenreExternalSourcesT f) x
-> PrimaryKey GenreExternalSourcesT f)
-> Generic (PrimaryKey GenreExternalSourcesT f)
forall x.
Rep (PrimaryKey GenreExternalSourcesT f) x
-> PrimaryKey GenreExternalSourcesT f
forall x.
PrimaryKey GenreExternalSourcesT f
-> Rep (PrimaryKey GenreExternalSourcesT f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x.
Rep (PrimaryKey GenreExternalSourcesT f) x
-> PrimaryKey GenreExternalSourcesT f
forall (f :: * -> *) x.
PrimaryKey GenreExternalSourcesT f
-> Rep (PrimaryKey GenreExternalSourcesT f) x
$cfrom :: forall (f :: * -> *) x.
PrimaryKey GenreExternalSourcesT f
-> Rep (PrimaryKey GenreExternalSourcesT f) x
from :: forall x.
PrimaryKey GenreExternalSourcesT f
-> Rep (PrimaryKey GenreExternalSourcesT f) x
$cto :: forall (f :: * -> *) x.
Rep (PrimaryKey GenreExternalSourcesT f) x
-> PrimaryKey GenreExternalSourcesT f
to :: forall x.
Rep (PrimaryKey GenreExternalSourcesT f) x
-> PrimaryKey GenreExternalSourcesT f
Generic, TableSkeleton (PrimaryKey GenreExternalSourcesT)
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreExternalSourcesT f
-> PrimaryKey GenreExternalSourcesT g
-> m (PrimaryKey GenreExternalSourcesT h))
-> TableSkeleton (PrimaryKey GenreExternalSourcesT)
-> Beamable (PrimaryKey GenreExternalSourcesT)
forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreExternalSourcesT f
-> PrimaryKey GenreExternalSourcesT g
-> m (PrimaryKey GenreExternalSourcesT h)
forall (table :: (* -> *) -> *).
(forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> table f -> table g -> m (table h))
-> TableSkeleton table -> Beamable table
$czipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreExternalSourcesT f
-> PrimaryKey GenreExternalSourcesT g
-> m (PrimaryKey GenreExternalSourcesT h)
zipBeamFieldsM :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *) (h :: * -> *).
Applicative m =>
(forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a))
-> PrimaryKey GenreExternalSourcesT f
-> PrimaryKey GenreExternalSourcesT g
-> m (PrimaryKey GenreExternalSourcesT h)
$ctblSkeleton :: TableSkeleton (PrimaryKey GenreExternalSourcesT)
tblSkeleton :: TableSkeleton (PrimaryKey GenreExternalSourcesT)
Beamable)
primaryKey :: forall (column :: * -> *).
GenreExternalSourcesT column
-> PrimaryKey GenreExternalSourcesT column
primaryKey = Columnar column Text -> PrimaryKey GenreExternalSourcesT column
forall (f :: * -> *).
Columnar f Text -> PrimaryKey GenreExternalSourcesT f
GenreExternalSourcesId (Columnar column Text -> PrimaryKey GenreExternalSourcesT column)
-> (GenreExternalSourcesT column -> Columnar column Text)
-> GenreExternalSourcesT column
-> PrimaryKey GenreExternalSourcesT column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenreExternalSourcesT column
-> Optic'
A_Lens NoIx (GenreExternalSourcesT column) (Columnar column Text)
-> Columnar column Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens NoIx (GenreExternalSourcesT column) (Columnar column Text)
#identifier)
makeFieldLabelsNoPrefix ''GenreExternalSourcesT
toPersistenceGenreExternalContents :: Genre -> UUID -> GenreExternalSources'
toPersistenceGenreExternalContents :: Genre -> UUID -> GenreExternalSources'
toPersistenceGenreExternalContents Genre
x UUID
newIdentifier =
GenreExternalSources'
{ $sel:identifier:GenreExternalSources' :: C Identity Text
identifier = UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ UUID
newIdentifier,
$sel:genreIdentifier:GenreExternalSources' :: PrimaryKey GenreT Identity
genreIdentifier = C Identity Text -> PrimaryKey GenreT Identity
forall (f :: * -> *). Columnar f Text -> PrimaryKey GenreT f
GenreId (C Identity Text -> PrimaryKey GenreT Identity)
-> C Identity Text -> PrimaryKey GenreT Identity
forall a b. (a -> b) -> a -> b
$ UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ Genre
x Genre -> Optic' A_Lens NoIx Genre UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre UUID
#identifier,
$sel:createdBy:GenreExternalSources' :: C Identity Text
createdBy = UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ Genre
x Genre -> Optic' A_Lens NoIx Genre UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre UUID
#createdBy,
$sel:spotifyUrl:GenreExternalSources' :: C Identity (Maybe Text)
spotifyUrl = Genre
x Genre -> Optic' A_Lens NoIx Genre (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre (Maybe Text)
#spotifyUrl,
$sel:youtubeUrl:GenreExternalSources' :: C Identity (Maybe Text)
youtubeUrl = Genre
x Genre -> Optic' A_Lens NoIx Genre (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre (Maybe Text)
#youtubeUrl,
$sel:soundcloudUrl:GenreExternalSources' :: C Identity (Maybe Text)
soundcloudUrl = Genre
x Genre -> Optic' A_Lens NoIx Genre (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre (Maybe Text)
#soundcloudUrl,
$sel:wikipediaUrl:GenreExternalSources' :: C Identity (Maybe Text)
wikipediaUrl = Genre
x Genre -> Optic' A_Lens NoIx Genre (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre (Maybe Text)
#wikipediaUrl,
$sel:createdAt:GenreExternalSources' :: C Identity UTCTime
createdAt = Genre
x Genre -> Optic' A_Lens NoIx Genre UTCTime -> UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre UTCTime
#createdAt,
$sel:lastEditedAt:GenreExternalSources' :: C Identity (Maybe UTCTime)
lastEditedAt = Genre
x Genre -> Optic' A_Lens NoIx Genre (Maybe UTCTime) -> Maybe UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Genre (Maybe UTCTime)
#lastEditedAt
}
toPersistenceGenreExternalSources :: GenreExternalSources -> GenreExternalSources'
toPersistenceGenreExternalSources :: GenreExternalSources -> GenreExternalSources'
toPersistenceGenreExternalSources GenreExternalSources
x =
GenreExternalSources'
{ $sel:identifier:GenreExternalSources' :: C Identity Text
identifier = UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ GenreExternalSources
x GenreExternalSources
-> Optic' A_Lens NoIx GenreExternalSources UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreExternalSources UUID
#identifier,
$sel:genreIdentifier:GenreExternalSources' :: PrimaryKey GenreT Identity
genreIdentifier = C Identity Text -> PrimaryKey GenreT Identity
forall (f :: * -> *). Columnar f Text -> PrimaryKey GenreT f
GenreId (C Identity Text -> PrimaryKey GenreT Identity)
-> C Identity Text -> PrimaryKey GenreT Identity
forall a b. (a -> b) -> a -> b
$ UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ GenreExternalSources
x GenreExternalSources
-> Optic' A_Lens NoIx GenreExternalSources UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreExternalSources UUID
#genreIdentifier,
$sel:createdBy:GenreExternalSources' :: C Identity Text
createdBy = UUID -> Text
UUID.toText (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ GenreExternalSources
x GenreExternalSources
-> Optic' A_Lens NoIx GenreExternalSources UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreExternalSources UUID
#createdBy,
$sel:spotifyUrl:GenreExternalSources' :: C Identity (Maybe Text)
spotifyUrl = GenreExternalSources
x GenreExternalSources
-> Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
-> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
#spotifyUrl,
$sel:youtubeUrl:GenreExternalSources' :: C Identity (Maybe Text)
youtubeUrl = GenreExternalSources
x GenreExternalSources
-> Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
-> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
#youtubeUrl,
$sel:soundcloudUrl:GenreExternalSources' :: C Identity (Maybe Text)
soundcloudUrl = GenreExternalSources
x GenreExternalSources
-> Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
-> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
#soundcloudUrl,
$sel:wikipediaUrl:GenreExternalSources' :: C Identity (Maybe Text)
wikipediaUrl = GenreExternalSources
x GenreExternalSources
-> Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
-> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreExternalSources (Maybe Text)
#wikipediaUrl,
$sel:createdAt:GenreExternalSources' :: C Identity UTCTime
createdAt = GenreExternalSources
x GenreExternalSources
-> Optic' A_Lens NoIx GenreExternalSources UTCTime -> UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreExternalSources UTCTime
#createdAt,
$sel:lastEditedAt:GenreExternalSources' :: C Identity (Maybe UTCTime)
lastEditedAt = GenreExternalSources
x GenreExternalSources
-> Optic' A_Lens NoIx GenreExternalSources (Maybe UTCTime)
-> Maybe UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GenreExternalSources (Maybe UTCTime)
#lastEditedAt
}
genreTModification :: GenreT (FieldModification (TableField GenreT))
genreTModification :: GenreT (FieldModification (TableField GenreT))
genreTModification =
GenreT (FieldModification Any)
forall (f :: * -> *) (tbl :: (* -> *) -> *).
Beamable tbl =>
tbl (FieldModification f)
tableModification
{ identifier = "identifier",
parentIdentifier = "parent_identifier",
displayName = "display_name",
createdBy = "created_by",
visibilityStatus = "visibility_status",
approvedBy = "approved_by",
createdAt = "created_at",
lastEditedAt = "last_edited_at",
viewCount = "views",
description = "description"
}
genreCommentTModification :: GenreCommentT (FieldModification (TableField GenreCommentT))
=
GenreCommentT (FieldModification Any)
forall (f :: * -> *) (tbl :: (* -> *) -> *).
Beamable tbl =>
tbl (FieldModification f)
tableModification
{ identifier = "identifier",
genreIdentifier = GenreId "genre_identifier",
parentIdentifier = "parent_identifier",
createdBy = "created_by",
visibilityStatus = "visibility_status",
contents = "contents",
approvedBy = "approved_by",
createdAt = "created_at",
lastEditedAt = "last_edited_at"
}
genreArtworkTModification :: GenreArtworkT (FieldModification (TableField GenreArtworkT))
genreArtworkTModification :: GenreArtworkT (FieldModification (TableField GenreArtworkT))
genreArtworkTModification =
GenreArtworkT (FieldModification Any)
forall (f :: * -> *) (tbl :: (* -> *) -> *).
Beamable tbl =>
tbl (FieldModification f)
tableModification
{ identifier = "identifier",
genreIdentifier = GenreId "genre_identifier",
createdBy = "created_by",
visibilityStatus = "visibility_status",
approvedBy = "approved_by",
contentUrl = "content_url",
contentCaption = "content_caption",
orderValue = "order_value",
createdAt = "created_at",
lastEditedAt = "last_edited_at"
}
genreOpinionTModification :: GenreOpinionT (FieldModification (TableField GenreOpinionT))
genreOpinionTModification :: GenreOpinionT (FieldModification (TableField GenreOpinionT))
genreOpinionTModification =
GenreOpinionT (FieldModification Any)
forall (f :: * -> *) (tbl :: (* -> *) -> *).
Beamable tbl =>
tbl (FieldModification f)
tableModification
{ identifier = "identifier",
genreIdentifier = GenreId "genre_identifier",
createdBy = "created_by",
isLike = "is_like",
isDislike = "is_dislike",
createdAt = "created_at",
lastEditedAt = "last_edited_at"
}
genreExternalSourcesTModification :: GenreExternalSourcesT (FieldModification (TableField GenreExternalSourcesT))
genreExternalSourcesTModification :: GenreExternalSourcesT
(FieldModification (TableField GenreExternalSourcesT))
genreExternalSourcesTModification =
GenreExternalSourcesT (FieldModification Any)
forall (f :: * -> *) (tbl :: (* -> *) -> *).
Beamable tbl =>
tbl (FieldModification f)
tableModification
{ identifier = "identifier",
genreIdentifier = GenreId "genre_identifier",
createdBy = "created_by",
spotifyUrl = "spotify_url",
youtubeUrl = "youtube_url",
soundcloudUrl = "soundcloud_url",
wikipediaUrl = "wikipedia_url",
createdAt = "created_at",
lastEditedAt = "last_edited_at"
}