2022-04-10 07:47:15 +03:00
|
|
|
{-# LANGUAGE DeriveAnyClass #-}
|
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
|
|
|
|
module Test.Data
|
|
|
|
( Artist (..),
|
|
|
|
Album (..),
|
|
|
|
schemaTables,
|
|
|
|
artists,
|
|
|
|
artistsAsJson,
|
|
|
|
artistsAsJsonById,
|
|
|
|
albums,
|
|
|
|
albumsAsJson,
|
|
|
|
sortBy,
|
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
import Control.Lens (ix, (^?))
|
|
|
|
import Data.Aeson (FromJSON (..), Object, eitherDecodeStrict, withObject, (.:))
|
2022-06-08 18:31:28 +03:00
|
|
|
import Data.Aeson.Key qualified as K
|
2022-04-10 07:47:15 +03:00
|
|
|
import Data.Aeson.Lens (_Number)
|
|
|
|
import Data.ByteString (ByteString)
|
|
|
|
import Data.FileEmbed (embedFile, makeRelativeToProject)
|
|
|
|
import Data.HashMap.Strict (HashMap)
|
|
|
|
import Data.HashMap.Strict qualified as HashMap
|
|
|
|
import Data.Hashable (Hashable)
|
|
|
|
import Data.List (sortOn)
|
|
|
|
import Data.Maybe (mapMaybe)
|
|
|
|
import Data.Scientific (Scientific)
|
|
|
|
import Data.Text (Text)
|
|
|
|
import GHC.Generics (Generic)
|
2022-05-02 08:03:12 +03:00
|
|
|
import Hasura.Backends.DataConnector.API (TableInfo (..))
|
2022-04-10 07:47:15 +03:00
|
|
|
import Prelude
|
|
|
|
|
|
|
|
data Artist = Artist
|
|
|
|
{ _artistId :: Int,
|
|
|
|
_artistName :: Text
|
|
|
|
}
|
|
|
|
deriving stock (Eq, Show, Ord, Generic)
|
|
|
|
deriving anyclass (Hashable)
|
|
|
|
|
|
|
|
instance FromJSON Artist where
|
|
|
|
parseJSON = withObject "Artist" $ \obj ->
|
|
|
|
Artist
|
|
|
|
<$> obj .: "id"
|
|
|
|
<*> obj .: "name"
|
|
|
|
|
|
|
|
data Album = Album
|
|
|
|
{ _albumId :: Int,
|
|
|
|
_albumTitle :: Text,
|
|
|
|
_albumArtistId :: Int
|
|
|
|
}
|
|
|
|
deriving stock (Eq, Show, Ord, Generic)
|
|
|
|
deriving anyclass (Hashable)
|
|
|
|
|
|
|
|
instance FromJSON Album where
|
|
|
|
parseJSON = withObject "Album" $ \obj ->
|
|
|
|
Album
|
|
|
|
<$> obj .: "id"
|
|
|
|
<*> obj .: "title"
|
|
|
|
<*> obj .: "artist_id"
|
|
|
|
|
|
|
|
schemaBS :: ByteString
|
2022-05-02 08:03:12 +03:00
|
|
|
schemaBS = $(makeRelativeToProject "tests-dc-api/Test/Data/schema-tables.json" >>= embedFile)
|
2022-04-10 07:47:15 +03:00
|
|
|
|
|
|
|
artistsBS :: ByteString
|
2022-05-02 08:03:12 +03:00
|
|
|
artistsBS = $(makeRelativeToProject "tests-dc-api/Test/Data/artists.json" >>= embedFile)
|
2022-04-10 07:47:15 +03:00
|
|
|
|
|
|
|
albumsBS :: ByteString
|
2022-05-02 08:03:12 +03:00
|
|
|
albumsBS = $(makeRelativeToProject "tests-dc-api/Test/Data/albums.json" >>= embedFile)
|
2022-04-10 07:47:15 +03:00
|
|
|
|
|
|
|
schemaTables :: [TableInfo]
|
|
|
|
schemaTables = sortOn dtiName . either error id . eitherDecodeStrict $ schemaBS
|
|
|
|
|
|
|
|
artists :: [Artist]
|
|
|
|
artists = sortOn _artistId . either error id . eitherDecodeStrict $ artistsBS
|
|
|
|
|
|
|
|
artistsAsJson :: [Object]
|
|
|
|
artistsAsJson = sortBy "id" . either error id . eitherDecodeStrict $ artistsBS
|
|
|
|
|
|
|
|
artistsAsJsonById :: HashMap Scientific Object
|
|
|
|
artistsAsJsonById =
|
|
|
|
HashMap.fromList $ mapMaybe (\artist -> (,artist) <$> artist ^? ix "id" . _Number) artistsAsJson
|
|
|
|
|
|
|
|
albums :: [Album]
|
|
|
|
albums = sortOn _albumId . either error id . eitherDecodeStrict $ albumsBS
|
|
|
|
|
|
|
|
albumsAsJson :: [Object]
|
|
|
|
albumsAsJson = sortBy "id" . either error id . eitherDecodeStrict $ albumsBS
|
|
|
|
|
2022-06-08 18:31:28 +03:00
|
|
|
sortBy :: K.Key -> [Object] -> [Object]
|
2022-04-10 07:47:15 +03:00
|
|
|
sortBy propName = sortOn (^? ix propName)
|