{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module WikiMusic.SSR.View.SongHtml
( songListPage',
songDetailPage',
songCreatePage',
songEditPage',
)
where
import Principium
import Text.Blaze.Html5 as H hiding (map)
import Text.Blaze.Html5.Attributes as A
import WikiMusic.Interaction.Model.Song
import WikiMusic.Model.Song hiding (show)
import WikiMusic.SSR.View.Components.DetailList
import WikiMusic.SSR.View.Components.Forms
import WikiMusic.SSR.View.Components.Other
import WikiMusic.SSR.View.HtmlUtil
songListPage' :: (MonadIO m) => Limit -> Offset -> Env -> ViewVars -> GetSongsQueryResponse -> m Html
songListPage' :: forall (m :: * -> *).
MonadIO m =>
Limit
-> Offset -> Env -> ViewVars -> GetSongsQueryResponse -> m Html
songListPage' Limit
limit Offset
offset Env
env ViewVars
vv GetSongsQueryResponse
xs =
Env -> ViewVars -> SimplePageTitle -> Html -> m Html
forall (m :: * -> *).
MonadIO m =>
Env -> ViewVars -> SimplePageTitle -> Html -> m Html
simplePage Env
env ViewVars
vv (Text -> SimplePageTitle
SimplePageTitle (Text -> SimplePageTitle) -> Text -> SimplePageTitle
forall a b. (a -> b) -> a -> b
$ (ApplicationDictionary
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm -> DictTerm
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic
A_Lens
NoIx
ApplicationDictionary
ApplicationDictionary
Titles
Titles
#titles Optic
A_Lens
NoIx
ApplicationDictionary
ApplicationDictionary
Titles
Titles
-> Optic A_Lens NoIx Titles Titles DictTerm DictTerm
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm
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 Titles Titles DictTerm DictTerm
#songsPage) (ApplicationDictionary -> DictTerm) -> Language -> Text
|##| (ViewVars
vv ViewVars -> Optic' A_Lens NoIx ViewVars Language -> Language
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ViewVars Language
#language)) (Html -> m Html) -> Html -> m Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
section (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! [Text] -> Attribute
css' [Text
"flex", Text
"flex-row", Text
"flex-wrap", Text
"gap-4", Text
"justify-center", Text
"align-center", Text
"items-center"] (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Text -> Html -> Html
searchForm Text
"/songs/search" (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Text -> Html
searchInput Text
"searchInput"
Html
submitButtonNoText
Html -> Html
section (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.a (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
href AttributeValue
"/songs/create" (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Html -> Html
button (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Html -> Html
H.small Html
"+ new song"
ViewVars -> SortOrder -> Text -> Text -> Html
mkSortingForm ViewVars
vv (ViewVars
vv ViewVars -> Optic' A_Lens NoIx ViewVars SortOrder -> SortOrder
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ViewVars SortOrder
#songSorting) Text
"/user-preferences/song-sorting" Text
"song-sorting"
Html -> Html
section (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! Set Text -> Attribute
css Set Text
cssCenteredCardGrid (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ (Song -> Html) -> [Song] -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (ViewVars -> Text -> Song -> Html
forall {k1} {k2} {k3} {k4} {k5} {k6} {k7} {k8} {a1} {k9} {l1} {l2}
{s1} {u} {v} {k10} {s2} {k11} {a2}.
(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,
Show a1, JoinKinds k9 l1 k3, JoinKinds k9 l2 k2,
LabelOptic "identifier" k4 s1 s1 UUID UUID,
LabelOptic "displayName" k7 s1 s1 Text Text,
LabelOptic "isLike" l1 u v Bool Bool,
LabelOptic "artworks" k6 s1 s1 (Map k10 s2) (Map k10 s2),
LabelOptic "opinions" k8 s1 s1 (Map k11 a2) (Map k11 a2),
LabelOptic "viewCount" k1 s1 s1 a1 a1,
LabelOptic "artwork" k5 s2 s2 Artwork Artwork,
LabelOptic "opinion" k9 a2 a2 u v,
LabelOptic "isDislike" l2 u v Bool Bool) =>
ViewVars -> Text -> s1 -> Html
simpleEntityCard ViewVars
vv Text
"songs") [Song]
sortedXs
Html -> Html
section (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! [Text] -> Attribute
css' [Text
"flex", Text
"flex-row", Text
"flex-wrap", Text
"gap-4", Text
"justify-center", Text
"align-center", Text
"items-center", Text
"my-6"] (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
ViewVars -> Limit -> Offset -> Int -> Html
maybePrevPaginationButton ViewVars
vv Limit
limit Offset
offset (Map UUID Song -> Int
forall a. Map UUID a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (GetSongsQueryResponse
xs GetSongsQueryResponse
-> Optic' A_Lens NoIx GetSongsQueryResponse (Map UUID Song)
-> Map UUID Song
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GetSongsQueryResponse (Map UUID Song)
#songs))
ViewVars -> Limit -> Offset -> Int -> Html
maybeNextPaginationButton ViewVars
vv Limit
limit Offset
offset (Map UUID Song -> Int
forall a. Map UUID a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (GetSongsQueryResponse
xs GetSongsQueryResponse
-> Optic' A_Lens NoIx GetSongsQueryResponse (Map UUID Song)
-> Map UUID Song
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GetSongsQueryResponse (Map UUID Song)
#songs))
where
sortedXs :: [Song]
sortedXs =
(UUID -> Maybe Song) -> [UUID] -> [Song]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe
(\UUID
identifier -> (GetSongsQueryResponse
xs GetSongsQueryResponse
-> Optic' A_Lens NoIx GetSongsQueryResponse (Map UUID Song)
-> Map UUID Song
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GetSongsQueryResponse (Map UUID Song)
#songs) Map UUID Song -> UUID -> Maybe Song
forall k a. Ord k => Map k a -> k -> Maybe a
Principium.!? UUID
identifier)
(GetSongsQueryResponse
xs GetSongsQueryResponse
-> Optic' A_Lens NoIx GetSongsQueryResponse [UUID] -> [UUID]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx GetSongsQueryResponse [UUID]
#sortOrder)
songDetailPage' :: (MonadIO m) => Env -> ViewVars -> Song -> m Html
songDetailPage' :: forall (m :: * -> *).
MonadIO m =>
Env -> ViewVars -> Song -> m Html
songDetailPage' Env
env ViewVars
vv Song
x = do
Env -> ViewVars -> SimplePageTitle -> Html -> m Html
forall (m :: * -> *).
MonadIO m =>
Env -> ViewVars -> SimplePageTitle -> Html -> m Html
simplePage Env
env ViewVars
vv (Text -> SimplePageTitle
SimplePageTitle (Text -> SimplePageTitle) -> Text -> SimplePageTitle
forall a b. (a -> b) -> a -> b
$ (ApplicationDictionary
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm -> DictTerm
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic
A_Lens
NoIx
ApplicationDictionary
ApplicationDictionary
Titles
Titles
#titles Optic
A_Lens
NoIx
ApplicationDictionary
ApplicationDictionary
Titles
Titles
-> Optic A_Lens NoIx Titles Titles DictTerm DictTerm
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm
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 Titles Titles DictTerm DictTerm
#songsPage) (ApplicationDictionary -> DictTerm) -> Language -> Text
|##| (ViewVars
vv ViewVars -> Optic' A_Lens NoIx ViewVars Language -> Language
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ViewVars Language
#language)) (Html -> m Html) -> Html -> m Html
forall a b. (a -> b) -> a -> b
$ do
ViewVars -> Text -> Song -> Html
forall {a1} {a2} {a3} {a4} {a5} {t1 :: * -> *} {k1} {l1} {k2} {l2}
{k3} {k4} {k5} {k6} {k7} {k8} {k9} {k10} {k11} {k12} {k13} {k14}
{k15} {k16} {k17} {t2 :: * -> *} {t3 :: * -> *} {t4 :: * -> *}
{t5 :: * -> *} {t6 :: * -> *} {s} {u} {v} {k18} {a6} {k19} {a7}.
(Show a1, Show a2, Show a3, Show a4, Show a5, Functor t1,
JoinKinds k1 l1 k2, JoinKinds k1 l2 k3, Is k4 A_Getter,
Is k5 A_Getter, Is k6 A_Getter, Is k7 A_Getter, Is k8 A_Getter,
Is k9 A_Getter, Is k10 A_Getter, Is k11 A_Getter, Is k3 A_Getter,
Is k2 A_Getter, Is k12 A_Getter, Is k13 A_Getter, Is k14 A_Getter,
Is k15 A_Getter, Is k16 A_Getter, Is k17 A_Getter, Foldable t2,
Foldable t1, Foldable t3, Foldable t4, Foldable t5, Foldable t6,
LabelOptic "description" k4 s s (t2 Text) (t2 Text),
LabelOptic "identifier" k8 s s a1 a1,
LabelOptic "createdBy" k9 s s a2 a2,
LabelOptic "createdAt" k10 s s a3 a3,
LabelOptic "lastEditedAt" k13 s s (t1 a5) (t1 a5),
LabelOptic "displayName" k7 s s Text Text,
LabelOptic "soundcloudUrl" k14 s s (t3 Text) (t3 Text),
LabelOptic "spotifyUrl" k16 s s (t5 Text) (t5 Text),
LabelOptic "wikipediaUrl" k15 s s (t4 Text) (t4 Text),
LabelOptic "youtubeUrl" k17 s s (t6 Text) (t6 Text),
LabelOptic "isLike" l2 u v Bool Bool,
LabelOptic "artworks" k5 s s (Map k18 a6) (Map k18 a6),
LabelOptic "opinions" k11 s s (Map k19 a7) (Map k19 a7),
LabelOptic "viewCount" k12 s s a4 a4,
LabelOptic "artwork" k6 a6 a6 Artwork Artwork,
LabelOptic "opinion" k1 a7 a7 u v,
LabelOptic "isDislike" l1 u v Bool Bool) =>
ViewVars -> Text -> s -> Html
entityDetails ViewVars
vv Text
"songs" Song
x
ViewVars -> Song -> Html
songDetails ViewVars
vv Song
x
Html -> Html
H.form (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! [Text] -> Attribute
css' [Text
"flex", Text
"flex-row", Text
"flex-wrap", Text
"justify-center", Text
"gap-4", Text
"items-center"] (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
action AttributeValue
"/user-preferences/song-ascii-size" (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
method AttributeValue
"POST" (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
enctype AttributeValue
"multipart/form-data" (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.label (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
for AttributeValue
"song-ascii-size" (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Html
"ascii size:"
Html -> Html
select (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! Set Text -> Attribute
css (ViewVars -> Set Text
cssSelect ViewVars
vv) (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
onchange AttributeValue
"this.form.submit()" (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
type_ AttributeValue
"checkbox" (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
name AttributeValue
"song-ascii-size" (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.id AttributeValue
"song-ascii-size" (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
((Text, Text) -> Html) -> [(Text, Text)] -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
( \(Text
size', Text
sizeName) ->
let mkOption :: Html -> Html
mkOption = Html -> Html
option (Html -> Html) -> (Bool, Attribute) -> Html -> Html
forall h. Attributable h => h -> (Bool, Attribute) -> h
H.!? ((ViewVars
vv ViewVars -> Optic' A_Lens NoIx ViewVars Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx ViewVars ViewVars SongAsciiSize SongAsciiSize
#songAsciiSize Optic A_Lens NoIx ViewVars ViewVars SongAsciiSize SongAsciiSize
-> Optic An_Iso NoIx SongAsciiSize SongAsciiSize Text Text
-> Optic' A_Lens NoIx ViewVars 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 An_Iso NoIx SongAsciiSize SongAsciiSize Text Text
#value) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
size', AttributeValue -> Attribute
selected AttributeValue
"true") (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
value (Text -> AttributeValue
textToAttrValue Text
size')
in Html -> Html
mkOption (Html -> Html) -> (Text -> Html) -> Text -> Html
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Html
text (Text -> Html) -> Text -> Html
forall a b. (a -> b) -> a -> b
$ Text
sizeName
)
[(Text, Text)]
fontSizes
Html -> Html
noscript (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Html -> Html
button (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
type_ AttributeValue
"submit" (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Html
"submit"
Html -> Html
section (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! [Text] -> Attribute
css' [Text
"container", Text
"mx-auto"] (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
(SongContent -> Html) -> Map UUID SongContent -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (ViewVars -> SongContent -> Html
mkVersion ViewVars
vv) (Song
x Song
-> Optic' A_Lens NoIx Song (Map UUID SongContent)
-> Map UUID SongContent
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Song (Map UUID SongContent)
#contents)
where
fontSizes :: [(Text, Text)]
fontSizes :: [(Text, Text)]
fontSizes = [(Text
"xs", Text
"extra small"), (Text
"sm", Text
"small"), (Text
"md", Text
"medium"), (Text
"lg", Text
"large"), (Text
"xl", Text
"extra large")]
songDetails :: ViewVars -> Song -> Html
songDetails :: ViewVars -> Song -> Html
songDetails ViewVars
vv Song
x = do
Html -> Html
section (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Html -> Html
detailList (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
(Text -> Html) -> Maybe Text -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
(ViewVars -> Text -> Html -> Html
monoDetailListEntry ViewVars
vv ((ApplicationDictionary
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm -> DictTerm
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
#more Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
-> Optic A_Lens NoIx More More DictTerm DictTerm
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm
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 More More DictTerm DictTerm
#musicTuning) (ApplicationDictionary -> DictTerm) -> Language -> Text
|##| (ViewVars
vv ViewVars -> Optic' A_Lens NoIx ViewVars Language -> Language
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ViewVars Language
#language)) (Html -> Html) -> (Text -> Html) -> Text -> Html
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Html
text)
(Song
x Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#musicTuning)
(Text -> Html) -> Maybe Text -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
(ViewVars -> Text -> Html -> Html
detailListEntry ViewVars
vv ((ApplicationDictionary
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm -> DictTerm
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
#more Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
-> Optic A_Lens NoIx More More DictTerm DictTerm
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm
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 More More DictTerm DictTerm
#musicKey) (ApplicationDictionary -> DictTerm) -> Language -> Text
|##| (ViewVars
vv ViewVars -> Optic' A_Lens NoIx ViewVars Language -> Language
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ViewVars Language
#language)) (Html -> Html) -> (Text -> Html) -> Text -> Html
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Html
text)
(Song
x Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#musicKey)
(Text -> Html) -> Maybe Text -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
(ViewVars -> Text -> Html -> Html
detailListEntry ViewVars
vv ((ApplicationDictionary
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm -> DictTerm
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
#more Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
-> Optic A_Lens NoIx More More DictTerm DictTerm
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm
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 More More DictTerm DictTerm
#musicCreationDate) (ApplicationDictionary -> DictTerm) -> Language -> Text
|##| (ViewVars
vv ViewVars -> Optic' A_Lens NoIx ViewVars Language -> Language
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ViewVars Language
#language)) (Html -> Html) -> (Text -> Html) -> Text -> Html
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Html
text)
(Song
x Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#musicCreationDate)
(Text -> Html) -> Maybe Text -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
(ViewVars -> Text -> Html -> Html
detailListEntry ViewVars
vv ((ApplicationDictionary
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm -> DictTerm
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
#more Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
-> Optic A_Lens NoIx More More DictTerm DictTerm
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm
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 More More DictTerm DictTerm
#albumName) (ApplicationDictionary -> DictTerm) -> Language -> Text
|##| (ViewVars
vv ViewVars -> Optic' A_Lens NoIx ViewVars Language -> Language
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ViewVars Language
#language)) (Html -> Html) -> (Text -> Html) -> Text -> Html
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Html
text)
(Song
x Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#albumName)
(Text -> Html) -> Maybe Text -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
(ViewVars -> Text -> Html -> Html
detailListEntry ViewVars
vv ((ApplicationDictionary
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm -> DictTerm
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
#more Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
-> Optic A_Lens NoIx More More DictTerm DictTerm
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm
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 More More DictTerm DictTerm
#albumInfoLink) (ApplicationDictionary -> DictTerm) -> Language -> Text
|##| (ViewVars
vv ViewVars -> Optic' A_Lens NoIx ViewVars Language -> Language
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ViewVars Language
#language)) (Html -> Html) -> (Text -> Html) -> Text -> Html
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Html
text)
(Song
x Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#albumInfoLink)
mkVersion :: ViewVars -> SongContent -> Html
mkVersion :: ViewVars -> SongContent -> Html
mkVersion ViewVars
vv SongContent
v = do
Html
hr
Html -> Html
H.article (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! [Text] -> Attribute
css' [Text
"my-6"] (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
(Html -> Html
h3 (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! [Text] -> Attribute
css' [Text
"text-xl", Text
"font-bold"]) (Html -> Html) -> (Text -> Html) -> Text -> Html
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Html
text (Text -> Html) -> Text -> Html
forall a b. (a -> b) -> a -> b
$ (SongContent
v SongContent -> Optic' A_Lens NoIx SongContent Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx SongContent Text
#versionName) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (SongContent
v SongContent -> Optic' A_Lens NoIx SongContent Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx SongContent Text
#instrumentType)
Html -> Html
detailList (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
(Html -> Html) -> Maybe Html -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
(ViewVars -> Text -> Html -> Html
detailListEntry ViewVars
vv ((ApplicationDictionary
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm -> DictTerm
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
#more Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
-> Optic A_Lens NoIx More More DictTerm DictTerm
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm
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 More More DictTerm DictTerm
#lastEditedAt) (ApplicationDictionary -> DictTerm) -> Language -> Text
|##| (ViewVars
vv ViewVars -> Optic' A_Lens NoIx ViewVars Language -> Language
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ViewVars Language
#language)))
(UTCTime -> Html
forall b a. (Show a, IsString b) => a -> b
show (UTCTime -> Html) -> Maybe UTCTime -> Maybe Html
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SongContent
v SongContent
-> Optic' A_Lens NoIx SongContent (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 SongContent (Maybe UTCTime)
#lastEditedAt)
ViewVars -> Text -> Html -> Html
detailListEntry ViewVars
vv ((ApplicationDictionary
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm -> DictTerm
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
#more Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
-> Optic A_Lens NoIx More More DictTerm DictTerm
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm
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 More More DictTerm DictTerm
#createdAt) (ApplicationDictionary -> DictTerm) -> Language -> Text
|##| (ViewVars
vv ViewVars -> Optic' A_Lens NoIx ViewVars Language -> Language
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ViewVars Language
#language)) (UTCTime -> Html
forall b a. (Show a, IsString b) => a -> b
show (UTCTime -> Html) -> UTCTime -> Html
forall a b. (a -> b) -> a -> b
$ SongContent
v SongContent -> Optic' A_Lens NoIx SongContent UTCTime -> UTCTime
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx SongContent UTCTime
#createdAt)
ViewVars -> Text -> Html -> Html
monoDetailListEntry ViewVars
vv ((ApplicationDictionary
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm -> DictTerm
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
#more Optic
A_Lens NoIx ApplicationDictionary ApplicationDictionary More More
-> Optic A_Lens NoIx More More DictTerm DictTerm
-> Optic' A_Lens NoIx ApplicationDictionary DictTerm
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 More More DictTerm DictTerm
#createdBy) (ApplicationDictionary -> DictTerm) -> Language -> Text
|##| (ViewVars
vv ViewVars -> Optic' A_Lens NoIx ViewVars Language -> Language
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ViewVars Language
#language)) (UUID -> Html
forall b a. (Show a, IsString b) => a -> b
show (UUID -> Html) -> UUID -> Html
forall a b. (a -> b) -> a -> b
$ SongContent
v SongContent -> Optic' A_Lens NoIx SongContent UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx SongContent UUID
#createdBy)
(Text -> Html) -> Maybe Text -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
( \Text
asciiLegend -> Html -> Html
details (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! Set Text -> Attribute
css (ViewVars -> Set Text
cssDetails ViewVars
vv) (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
open AttributeValue
"" (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.summary (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! Set Text -> Attribute
css Set Text
cssSummary (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Html
"ASCII Legend"
(Html -> Html
H.pre (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
class_ (Text -> AttributeValue
textToAttrValue (Text -> AttributeValue) -> Text -> AttributeValue
forall a b. (a -> b) -> a -> b
$ Text
"text-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (ViewVars
vv ViewVars -> Optic' A_Lens NoIx ViewVars Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx ViewVars ViewVars SongAsciiSize SongAsciiSize
#songAsciiSize Optic A_Lens NoIx ViewVars ViewVars SongAsciiSize SongAsciiSize
-> Optic An_Iso NoIx SongAsciiSize SongAsciiSize Text Text
-> Optic' A_Lens NoIx ViewVars 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 An_Iso NoIx SongAsciiSize SongAsciiSize Text Text
#value))) (Html -> Html) -> (Text -> Html) -> Text -> Html
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Html
text (Text -> Html) -> Text -> Html
forall a b. (a -> b) -> a -> b
$ Text
asciiLegend
)
(SongContent
v SongContent
-> Optic' A_Lens NoIx SongContent (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 SongContent (Maybe Text)
#asciiLegend)
(Text -> Html) -> Maybe Text -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
( \Text
asciiContents -> Html -> Html
details (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! Set Text -> Attribute
css (ViewVars -> Set Text
cssDetails ViewVars
vv) (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
open AttributeValue
"" (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.summary (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! Set Text -> Attribute
css Set Text
cssSummary (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Html
"ASCII Content"
(Html -> Html
H.pre (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
class_ (Text -> AttributeValue
textToAttrValue (Text -> AttributeValue) -> Text -> AttributeValue
forall a b. (a -> b) -> a -> b
$ Text
"text-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (ViewVars
vv ViewVars -> Optic' A_Lens NoIx ViewVars Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic A_Lens NoIx ViewVars ViewVars SongAsciiSize SongAsciiSize
#songAsciiSize Optic A_Lens NoIx ViewVars ViewVars SongAsciiSize SongAsciiSize
-> Optic An_Iso NoIx SongAsciiSize SongAsciiSize Text Text
-> Optic' A_Lens NoIx ViewVars 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 An_Iso NoIx SongAsciiSize SongAsciiSize Text Text
#value))) (Html -> Html) -> (Text -> Html) -> Text -> Html
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Html
text (Text -> Html) -> Text -> Html
forall a b. (a -> b) -> a -> b
$ Text
asciiContents
)
(SongContent
v SongContent
-> Optic' A_Lens NoIx SongContent (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 SongContent (Maybe Text)
#asciiContents)
(Text -> Html) -> Maybe Text -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
( \Text
pdfContents ->
Bool -> Html -> Html
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text
pdfContents Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"data:application/octet-stream;base64,") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
details (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! Set Text -> Attribute
css (ViewVars -> Set Text
cssDetails ViewVars
vv) (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
open AttributeValue
"" (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.summary (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! Set Text -> Attribute
css Set Text
cssSummary (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Html
"PDF Content"
Html -> Html
H.iframe
(Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! [Text] -> Attribute
css' [Text
"w-full", Text
"h-full", Text
"block"]
(Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! Tag -> AttributeValue -> Attribute
customAttribute Tag
"loading" AttributeValue
"lazy"
(Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! Tag -> AttributeValue -> Attribute
customAttribute Tag
"allowed" AttributeValue
""
(Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! Tag -> AttributeValue -> Attribute
customAttribute Tag
"allowfullscreen" AttributeValue
""
(Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! Tag -> AttributeValue -> Attribute
customAttribute Tag
"referrerpolicy" AttributeValue
"noreferrer"
(Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.src (Text -> AttributeValue
textToAttrValue Text
pdfContents)
(Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Html
""
)
(SongContent
v SongContent
-> Optic' A_Lens NoIx SongContent (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 SongContent (Maybe Text)
#pdfContents)
songCreatePage' :: (MonadIO m) => Env -> ViewVars -> m Html
songCreatePage' :: forall (m :: * -> *). MonadIO m => Env -> ViewVars -> m Html
songCreatePage' Env
env ViewVars
vv = do
Env -> ViewVars -> SimplePageTitle -> Html -> m Html
forall (m :: * -> *).
MonadIO m =>
Env -> ViewVars -> SimplePageTitle -> Html -> m Html
simplePage Env
env ViewVars
vv (Text -> SimplePageTitle
SimplePageTitle Text
"Create song") (Html -> m Html) -> Html -> m Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
section (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! [Text] -> Attribute
css' [Text
"container", Text
"mx-auto"] (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Text -> Html -> Html
postForm Text
"/songs/create" (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Text -> Text -> Html
requiredTextInput Text
"displayName" Text
"song name"
Text -> Text -> Html
optionalTextArea Text
"description" Text
"description"
Text -> Text -> Html
optionalTextInput Text
"spotifyUrl" Text
"spotify URL"
Text -> Text -> Html
optionalTextInput Text
"youtubeUrl" Text
"youtube URL"
Text -> Text -> Html
optionalTextInput Text
"wikipediaUrl" Text
"wikipedia URL"
Text -> Text -> Html
optionalTextInput Text
"soundcloudUrl" Text
"soundcloud URL"
Text -> Text -> Html
optionalTextInput Text
"musicKey" Text
"music key"
Text -> Text -> Html
optionalTextInput Text
"musicTuning" Text
"tuning"
Text -> Text -> Html
optionalTextInput Text
"musicCreationDate" Text
"date composed"
Text -> Text -> Html
optionalTextInput Text
"albumName" Text
"album name"
Text -> Text -> Html
optionalTextInput Text
"albumInfoLink" Text
"about the album"
ViewVars -> Html
submitButton ViewVars
vv
songEditPage' :: (MonadIO m) => Env -> ViewVars -> Song -> m Html
songEditPage' :: forall (m :: * -> *).
MonadIO m =>
Env -> ViewVars -> Song -> m Html
songEditPage' Env
env ViewVars
vv Song
song = do
Env -> ViewVars -> SimplePageTitle -> Html -> m Html
forall (m :: * -> *).
MonadIO m =>
Env -> ViewVars -> SimplePageTitle -> Html -> m Html
simplePage Env
env ViewVars
vv (Text -> SimplePageTitle
SimplePageTitle Text
"Edit song") (Html -> m Html) -> Html -> m Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
section (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! [Text] -> Attribute
css' [Text
"container", Text
"mx-auto"] (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Text -> Html -> Html
postForm (Text
"/songs/edit/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> UUID -> Text
uuidToText (Song
song Song -> Optic' A_Lens NoIx Song UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Song UUID
#identifier)) (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Text -> Text -> Maybe Text -> Html
requiredTextInput' Text
"displayName" Text
"song name" (Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Song
song Song -> Optic' A_Lens NoIx Song Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Song Text
#displayName)
Text -> Text -> Maybe Text -> Html
optionalTextArea' Text
"description" Text
"description" (Song
song Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#description)
Text -> Text -> Maybe Text -> Html
optionalTextInput' Text
"spotifyUrl" Text
"spotify URL" (Song
song Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#spotifyUrl)
Text -> Text -> Maybe Text -> Html
optionalTextInput' Text
"youtubeUrl" Text
"youtube URL" (Song
song Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#youtubeUrl)
Text -> Text -> Maybe Text -> Html
optionalTextInput' Text
"wikipediaUrl" Text
"wikipedia URL" (Song
song Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#wikipediaUrl)
Text -> Text -> Maybe Text -> Html
optionalTextInput' Text
"soundcloudUrl" Text
"soundcloud URL" (Song
song Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#soundcloudUrl)
Text -> Text -> Maybe Text -> Html
optionalTextInput' Text
"musicKey" Text
"music key" (Song
song Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#musicKey)
Text -> Text -> Maybe Text -> Html
optionalTextInput' Text
"musicTuning" Text
"tuning" (Song
song Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#musicTuning)
Text -> Text -> Maybe Text -> Html
optionalTextInput' Text
"musicCreationDate" Text
"date composed" (Song
song Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#musicCreationDate)
Text -> Text -> Maybe Text -> Html
optionalTextInput' Text
"albumName" Text
"album name" (Song
song Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#albumName)
Text -> Text -> Maybe Text -> Html
optionalTextInput' Text
"albumInfoLink" Text
"about the album" (Song
song Song -> Optic' A_Lens NoIx Song (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 Song (Maybe Text)
#albumInfoLink)
ViewVars -> Html
submitButton ViewVars
vv
ViewVars -> Text -> [Artwork] -> Html
entityArtworkForm ViewVars
vv Text
"songs" ((SongArtwork -> Artwork) -> [SongArtwork] -> [Artwork]
forall a b. (a -> b) -> [a] -> [b]
map (SongArtwork -> Optic' A_Lens NoIx SongArtwork Artwork -> Artwork
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx SongArtwork Artwork
#artwork) ([SongArtwork] -> [Artwork])
-> (Map UUID SongArtwork -> [SongArtwork])
-> Map UUID SongArtwork
-> [Artwork]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map UUID SongArtwork -> [SongArtwork]
forall k a. Map k a -> [a]
mapElems (Map UUID SongArtwork -> [Artwork])
-> Map UUID SongArtwork -> [Artwork]
forall a b. (a -> b) -> a -> b
$ Song
song Song
-> Optic' A_Lens NoIx Song (Map UUID SongArtwork)
-> Map UUID SongArtwork
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Song (Map UUID SongArtwork)
#artworks)
Html
hr
ViewVars -> Text -> UUID -> Html
entityNewArtworkForm ViewVars
vv Text
"songs" (Song
song Song -> Optic' A_Lens NoIx Song UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Song UUID
#identifier)
(SongContent -> Html) -> [SongContent] -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\SongContent
c -> Html
hr Html -> Html -> Html
forall a b. MarkupM a -> MarkupM b -> MarkupM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Env -> ViewVars -> UUID -> SongContent -> Html
songContentsEditForm Env
env ViewVars
vv (Song
song Song -> Optic' A_Lens NoIx Song UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Song UUID
#identifier) SongContent
c) (Map UUID SongContent -> [SongContent]
forall k a. Map k a -> [a]
mapElems (Map UUID SongContent -> [SongContent])
-> Map UUID SongContent -> [SongContent]
forall a b. (a -> b) -> a -> b
$ Song
song Song
-> Optic' A_Lens NoIx Song (Map UUID SongContent)
-> Map UUID SongContent
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Song (Map UUID SongContent)
#contents)
Html
hr
Html -> Html
H.h2 Html
"Create contents"
ViewVars -> UUID -> Html
songContentsCreateForm ViewVars
vv (Song
song Song -> Optic' A_Lens NoIx Song UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Song UUID
#identifier)
Html
hr
Html -> Html
H.h2 Html
"Artist <> Song"
(Text -> Html) -> [Text] -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
( \Text
art -> do
Html -> Html
H.h4 (Html -> Html) -> (Text -> Html) -> Text -> Html
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Html
text (Text -> Html) -> Text -> Html
forall a b. (a -> b) -> a -> b
$ Text
art
)
(Map UUID Text -> [Text]
forall k a. Map k a -> [a]
mapElems (Map UUID Text -> [Text]) -> Map UUID Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Song
song Song -> Optic' A_Lens NoIx Song (Map UUID Text) -> Map UUID Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Song (Map UUID Text)
#artists)
ViewVars -> UUID -> Html
songArtistForm ViewVars
vv (Song
song Song -> Optic' A_Lens NoIx Song UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx Song UUID
#identifier)
songArtistForm :: ViewVars -> UUID -> Html
songArtistForm :: ViewVars -> UUID -> Html
songArtistForm ViewVars
vv UUID
songIdentifier = do
Text -> Html -> Html
postForm (Text
"/songs/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> UUID -> Text
uuidToText UUID
songIdentifier Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/artists") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Text -> Text -> Html
requiredTextInput Text
"identifier" Text
"artist identifier (UUID)"
ViewVars -> Html
submitButton ViewVars
vv
songContentsCreateForm :: ViewVars -> UUID -> Html
songContentsCreateForm :: ViewVars -> UUID -> Html
songContentsCreateForm ViewVars
vv UUID
songIdentifier = do
Text -> Html -> Html
postForm (Text
"/songs/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (String -> Text
packText (String -> Text) -> (UUID -> String) -> UUID -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> String
forall b a. (Show a, IsString b) => a -> b
show (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ UUID
songIdentifier) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/contents") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Text -> Text -> Html
requiredTextInput Text
"versionName" Text
"version name"
Text -> Text -> Html
requiredTextInput Text
"instrumentType" Text
"instrument type"
Text -> Text -> Html
optionalMonoArea Text
"asciiLegend" Text
"ascii legend"
Text -> Text -> Html
optionalMonoArea Text
"asciiContents" Text
"ascii contents"
Text -> Text -> Html
optionalFileInput Text
"pdfContents" Text
"pdf file"
Text -> Text -> Html
optionalFileInput Text
"guitarProContents" Text
"guitar pro file"
ViewVars -> Html
submitButton ViewVars
vv
songContentsEditForm :: Env -> ViewVars -> UUID -> SongContent -> Html
songContentsEditForm :: Env -> ViewVars -> UUID -> SongContent -> Html
songContentsEditForm Env
_ ViewVars
vv UUID
songIdentifier SongContent
content' = do
Html -> Html
H.h3 Html
"Edit contents"
ViewVars -> Text -> Html -> Html
dangerPostForm
ViewVars
vv
( Text
"/songs/contents/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (String -> Text
packText (String -> Text) -> (UUID -> String) -> UUID -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> String
forall b a. (Show a, IsString b) => a -> b
show (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ SongContent
content' SongContent -> Optic' A_Lens NoIx SongContent UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx SongContent UUID
#identifier)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/delete"
)
(Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
ViewVars -> Html
deleteButton ViewVars
vv
Text -> Html -> Html
postForm
( Text
"/songs/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (String -> Text
packText (String -> Text) -> (UUID -> String) -> UUID -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> String
forall b a. (Show a, IsString b) => a -> b
show (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ UUID
songIdentifier)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/contents/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (String -> Text
packText (String -> Text) -> (UUID -> String) -> UUID -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> String
forall b a. (Show a, IsString b) => a -> b
show (UUID -> Text) -> UUID -> Text
forall a b. (a -> b) -> a -> b
$ SongContent
content' SongContent -> Optic' A_Lens NoIx SongContent UUID -> UUID
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx SongContent UUID
#identifier)
)
(Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Text -> Text -> Maybe Text -> Html
requiredTextInput' Text
"versionName" Text
"version name" (Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ SongContent
content' SongContent -> Optic' A_Lens NoIx SongContent Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx SongContent Text
#versionName)
Text -> Text -> Maybe Text -> Html
requiredTextInput' Text
"instrumentType" Text
"instrument type" (Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ SongContent
content' SongContent -> Optic' A_Lens NoIx SongContent Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx SongContent Text
#instrumentType)
Text -> Text -> Maybe Text -> Html
optionalMonoArea' Text
"asciiLegend" Text
"ascii legend" (SongContent
content' SongContent
-> Optic' A_Lens NoIx SongContent (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 SongContent (Maybe Text)
#asciiLegend)
Text -> Text -> Maybe Text -> Html
optionalMonoArea' Text
"asciiContents" Text
"ascii contents" (SongContent
content' SongContent
-> Optic' A_Lens NoIx SongContent (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 SongContent (Maybe Text)
#asciiContents)
ViewVars -> Html
submitButton ViewVars
vv