{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NoFieldSelectors #-}

module WikiMusic.Servant.ApiSpec
  ( WikiMusicPrivateAPI,
    WikiMusicPublicAPI,
    WikiMusicAPIServer,
    WikiMusicAPIDocsServer,
    WikiMusicPrivateArtistsAPI,
    WikiMusicPrivateSongsAPI,
    WikiMusicPrivateAuthAPI,
    WikiMusicPrivateGenresAPI,
  )
where

import Data.OpenApi qualified
import Data.UUID hiding (fromString)
import Relude
import Servant as S
import WikiMusic.Interaction.Model.Artist
import WikiMusic.Interaction.Model.Auth
import WikiMusic.Interaction.Model.Genre
import WikiMusic.Interaction.Model.Song
import WikiMusic.Interaction.Model.User
import WikiMusic.Model.Auth
import WikiMusic.Model.Other

type WikiMusicAPIServer =
  WikiMusicPrivateAPI
    :<|> SwaggerAPI
    :<|> WikiMusicPublicAPI

type WikiMusicAPIDocsServer = WikiMusicPublicAPI :<|> WikiMusicPrivateAPI

type WithAuth = Header "x-wikimusic-auth" Text

type WikiMusicPrivateArtistsAPI =
  "artists"
    :> WithAuth
    :> QueryParam "limit" Int
    :> QueryParam "offset" Int
    :> QueryParam "sort-order" Text
    :> QueryParam "include" Text
    :> Get '[JSON] GetArtistsQueryResponse
    :<|> "artists"
      :> WithAuth
      :> "search"
      :> Capture "searchInput" Text
      :> QueryParam "limit" Int
      :> QueryParam "offset" Int
      :> QueryParam "sort-order" Text
      :> QueryParam "include" Text
      :> Get '[JSON] GetArtistsQueryResponse
    :<|> "artists" :> "identifier" :> WithAuth :> Capture "identifier" UUID :> QueryParam "sort-order" Text :> QueryParam "include" Text :> Get '[JSON] GetArtistsQueryResponse
    :<|> "artists" :> WithAuth :> ReqBody '[JSON] InsertArtistsRequest :> Post '[JSON] InsertArtistsCommandResponse
    :<|> "artists" :> "comments" :> WithAuth :> ReqBody '[JSON] InsertArtistCommentsRequest :> Post '[JSON] InsertArtistCommentsCommandResponse
    :<|> "artists" :> "opinions" :> WithAuth :> ReqBody '[JSON] UpsertArtistOpinionsRequest :> Post '[JSON] UpsertArtistOpinionsCommandResponse
    :<|> "artists" :> "artworks" :> WithAuth :> ReqBody '[JSON] InsertArtistArtworksRequest :> Post '[JSON] InsertArtistArtworksCommandResponse
    :<|> "artists" :> WithAuth :> Capture "identifier" UUID :> Delete '[JSON] ()
    :<|> "artists" :> "comments" :> WithAuth :> Capture "identifier" UUID :> Delete '[JSON] ()
    :<|> "artists" :> "opinions" :> WithAuth :> Capture "identifier" UUID :> Delete '[JSON] ()
    :<|> "artists" :> "artworks" :> WithAuth :> Capture "identifier" UUID :> Delete '[JSON] ()
    :<|> "artists" :> "artworks" :> "order" :> WithAuth :> ReqBody '[JSON] ArtistArtworkOrderUpdateRequest :> Patch '[JSON] ()
    :<|> "artists" :> "edit" :> WithAuth :> ReqBody '[JSON] ArtistDeltaRequest :> Patch '[JSON] ()

type WikiMusicPrivateSongsAPI =
  "songs"
    :> WithAuth
    :> QueryParam "limit" Int
    :> QueryParam "offset" Int
    :> QueryParam "sort-order" Text
    :> QueryParam "include" Text
    :> Get '[JSON] GetSongsQueryResponse
    :<|> "songs"
      :> "search"
      :> WithAuth
      :> Capture "searchInput" Text
      :> QueryParam "limit" Int
      :> QueryParam "offset" Int
      :> QueryParam "sort-order" Text
      :> QueryParam "include" Text
      :> Get '[JSON] GetSongsQueryResponse
    :<|> "songs" :> "identifier" :> WithAuth :> Capture "identifier" UUID :> QueryParam "sort-order" Text :> QueryParam "include" Text :> Get '[JSON] GetSongsQueryResponse
    :<|> "songs" :> WithAuth :> ReqBody '[JSON] InsertSongsRequest :> Post '[JSON] InsertSongsCommandResponse
    :<|> "songs" :> "comments" :> WithAuth :> ReqBody '[JSON] InsertSongCommentsRequest :> Post '[JSON] InsertSongCommentsCommandResponse
    :<|> "songs" :> "opinions" :> WithAuth :> ReqBody '[JSON] UpsertSongOpinionsRequest :> Post '[JSON] UpsertSongOpinionsCommandResponse
    :<|> "songs" :> "artworks" :> WithAuth :> ReqBody '[JSON] InsertSongArtworksRequest :> Post '[JSON] InsertSongArtworksCommandResponse
    :<|> "songs" :> "artists" :> WithAuth :> ReqBody '[JSON] InsertArtistsOfSongsRequest :> Post '[JSON] InsertArtistsOfSongCommandResponse
    :<|> "songs" :> "artists" :> WithAuth :> ReqBody '[JSON] InsertArtistsOfSongsRequest :> Delete '[JSON] ()
    :<|> "songs" :> WithAuth :> Capture "identifier" UUID :> Delete '[JSON] ()
    :<|> "songs" :> "comments" :> WithAuth :> Capture "identifier" UUID :> Delete '[JSON] ()
    :<|> "songs" :> "opinions" :> WithAuth :> Capture "identifier" UUID :> Delete '[JSON] ()
    :<|> "songs" :> "artworks" :> WithAuth :> Capture "identifier" UUID :> Delete '[JSON] ()
    :<|> "songs" :> "artworks" :> "order" :> WithAuth :> ReqBody '[JSON] SongArtworkOrderUpdateRequest :> Patch '[JSON] ()
    :<|> "songs" :> "edit" :> WithAuth :> ReqBody '[JSON] SongDeltaRequest :> Patch '[JSON] ()
    :<|> "songs" :> "contents" :> WithAuth :> ReqBody '[JSON] InsertSongContentsRequest :> Post '[JSON] InsertSongContentsCommandResponse
    :<|> "songs" :> "contents" :> WithAuth :> Capture "identifier" UUID :> Delete '[JSON] ()
    :<|> "songs" :> "contents" :> WithAuth :> ReqBody '[JSON] SongContentDeltaRequest :> Patch '[JSON] ()

type WikiMusicPrivateGenresAPI =
  "genres"
    :> WithAuth
    :> QueryParam "limit" Int
    :> QueryParam "offset" Int
    :> QueryParam "sort-order" Text
    :> QueryParam "include" Text
    :> Get '[JSON] GetGenresQueryResponse
    :<|> "genres"
      :> "search"
      :> WithAuth
      :> Capture "searchInput" Text
      :> QueryParam "limit" Int
      :> QueryParam "offset" Int
      :> QueryParam "sort-order" Text
      :> QueryParam "include" Text
      :> Get '[JSON] GetGenresQueryResponse
    :<|> "genres" :> "identifier" :> WithAuth :> Capture "identifier" UUID :> QueryParam "sort-order" Text :> QueryParam "include" Text :> Get '[JSON] GetGenresQueryResponse
    :<|> "genres" :> WithAuth :> ReqBody '[JSON] InsertGenresRequest :> Post '[JSON] InsertGenresCommandResponse
    :<|> "genres" :> "comments" :> WithAuth :> ReqBody '[JSON] InsertGenreCommentsRequest :> Post '[JSON] InsertGenreCommentsCommandResponse
    :<|> "genres" :> "opinions" :> WithAuth :> ReqBody '[JSON] UpsertGenreOpinionsRequest :> Post '[JSON] UpsertGenreOpinionsCommandResponse
    :<|> "genres" :> "artworks" :> WithAuth :> ReqBody '[JSON] InsertGenreArtworksRequest :> Post '[JSON] InsertGenreArtworksCommandResponse
    :<|> "genres" :> WithAuth :> Capture "identifier" UUID :> Delete '[JSON] ()
    :<|> "genres" :> "comments" :> WithAuth :> Capture "identifier" UUID :> Delete '[JSON] ()
    :<|> "genres" :> "opinions" :> WithAuth :> Capture "identifier" UUID :> Delete '[JSON] ()
    :<|> "genres" :> "artworks" :> WithAuth :> Capture "identifier" UUID :> Delete '[JSON] ()
    :<|> "genres" :> "artworks" :> "order" :> WithAuth :> ReqBody '[JSON] GenreArtworkOrderUpdateRequest :> Patch '[JSON] ()
    :<|> "genres" :> "edit" :> WithAuth :> ReqBody '[JSON] GenreDeltaRequest :> Patch '[JSON] ()

type WikiMusicPrivateAuthAPI =
  "me" :> WithAuth :> Get '[JSON] GetMeQueryResponse
    :<|> "users" :> "invite" :> WithAuth :> ReqBody '[JSON] InviteUsersRequest :> Post '[JSON] MakeResetPasswordLinkResponse
    :<|> "users" :> "delete" :> WithAuth :> ReqBody '[JSON] DeleteUsersRequest :> Post '[JSON] ()

type WikiMusicPrivateAPI =
  WikiMusicPrivateArtistsAPI
    :<|> WikiMusicPrivateGenresAPI
    :<|> WikiMusicPrivateSongsAPI
    :<|> WikiMusicPrivateAuthAPI

type WikiMusicPublicAPI =
  "login"
    :> ReqBody '[JSON] LoginRequest
    :> Verb
         'POST
         204
         '[JSON]
         ( Headers
             '[WithAuth]
             NoContent
         )
    :<|> "reset-password"
      :> "email"
      :> Capture "email" Text
      :> Post '[JSON] MakeResetPasswordLinkResponse
    :<|> "reset-password"
      :> "do"
      :> ReqBody '[JSON] DoPasswordResetRequest
      :> Verb 'POST 204 '[JSON] ()
    :<|> "system-information"
      :> Get '[JSON] SystemInformationResponse

type SwaggerAPI = "swagger.json" :> Get '[JSON] Data.OpenApi.OpenApi