Refactor Aeson instances

This commit is contained in:
Paul Brinkmeier 2022-08-25 21:47:40 +02:00
parent d603d9a1b4
commit f8bfff0538

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ImpredicativeTypes #-} {-# LANGUAGE ImpredicativeTypes #-}
@ -6,11 +7,14 @@ module Lisa.Squeak where
import Control.Applicative ((<|>)) import Control.Applicative ((<|>))
import Control.Monad.IO.Class (MonadIO, liftIO) import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Aeson (FromJSON(parseJSON), ToJSON(toJSON), Value, (.:), (.:?), (.=), object, withObject) import Data.Aeson (FromJSON(parseJSON), FromJSONKey(fromJSONKey), Options(fieldLabelModifier), ToJSON(toJSON), Value, (.:), (.:?), (.=), defaultOptions, genericParseJSON, genericToJSON, object, withObject)
import Data.Text (Text) import Data.Text (Text)
import Data.Time.Calendar (Day) import Data.Time.Calendar (Day)
import GHC.Generics (Generic)
import Network.HTTP.Req (Option, Scheme(..), POST(..), ReqBodyJson(..), Req, Scheme, Url, defaultHttpConfig, http, https, port, jsonResponse, responseBody, req, runReq) import Network.HTTP.Req (Option, Scheme(..), POST(..), ReqBodyJson(..), Req, Scheme, Url, defaultHttpConfig, http, https, port, jsonResponse, responseBody, req, runReq)
import qualified Data.Char as Char
-- | Dependency Inversion for monads that can run requests. -- | Dependency Inversion for monads that can run requests.
-- By requiring 'HasEndpointInfo' and 'MonadIO' for functions that perform requests we don't need to import anything from Scotty. -- By requiring 'HasEndpointInfo' and 'MonadIO' for functions that perform requests we don't need to import anything from Scotty.
class HasEndpointInfo m where class HasEndpointInfo m where
@ -49,25 +53,23 @@ joinErrors (Left errors) = Left $ GQLErrors errors
joinErrors (Right (SqueakErrorOr inner)) = inner joinErrors (Right (SqueakErrorOr inner)) = inner
-- ^ A GraphQL query with a bunch of variables. -- ^ A GraphQL query with a bunch of variables.
data GQLQuery v = GQLQuery Text v data GQLQuery v = GQLQuery
deriving (Show) { gqlQueryQuery :: Text
, gqlQueryVariables :: v
}
deriving (Generic, Show)
instance ToJSON v => ToJSON (GQLQuery v) where instance ToJSON v => ToJSON (GQLQuery v) where
toJSON (GQLQuery query variables) = object toJSON = genericToJSON $ removePrefixOpts "gqlQuery"
[ "query" .= query
, "variables" .= variables
]
data GQLReply a = GQLReply data GQLReply a = GQLReply
{ gqlReplyData :: Maybe a { gqlReplyData :: Maybe a
, gqlReplyErrors :: Maybe [GQLError] , gqlReplyErrors :: Maybe [GQLError]
} }
deriving (Show) deriving (Generic, Show)
instance FromJSON a => FromJSON (GQLReply a) where instance FromJSON a => FromJSON (GQLReply a) where
parseJSON = withObject "GQLReply" $ \v -> GQLReply parseJSON = genericParseJSON $ removePrefixOpts "gqlReply"
<$> v .: "data"
<*> v .:? "errors"
replyToEither :: GQLReply a -> Either [GQLError] a replyToEither :: GQLReply a -> Either [GQLError] a
replyToEither (GQLReply (Just data') _) = Right data' replyToEither (GQLReply (Just data') _) = Right data'
@ -77,19 +79,38 @@ replyToEither _ = error "Invalid GQLReply: Neither 'dat
data GQLError = GQLError data GQLError = GQLError
{ gqlErrorMessage :: Text { gqlErrorMessage :: Text
} }
deriving (Show) deriving (Generic, Show)
instance FromJSON GQLError where instance FromJSON GQLError where
parseJSON = withObject "GQLError" $ \v -> GQLError parseJSON = genericParseJSON $ removePrefixOpts "gqlError"
<$> v .: "message"
-- TODO: doc
data Documents = Documents { unDocuments :: [Document] } data Documents = Documents { unDocuments :: [Document] }
deriving (Show) deriving (Show)
-- TODO: doc
instance FromJSON Documents where instance FromJSON Documents where
parseJSON = withObject "Documents" $ \v -> Documents parseJSON = withObject "Documents" $ \v -> Documents
<$> ((v .: "documents") >>= (.: "results")) <$> ((v .: "documents") >>= (.: "results"))
-- | Helper for automatically writing 'FromJSON' instances.
--
-- >>> removePrefixModifier "document" "documentId"
-- "id"
-- >>> removePrefixModifier "document" "documentPublicComment"
-- "publicComment"
removePrefixModifier :: String -> String -> String
removePrefixModifier prefix = lowercaseFirst . stripPrefix prefix
where
stripPrefix [] word = word
stripPrefix (p:ps) (c:cs)
| p == c = stripPrefix ps cs
| otherwise = error $ "Invalid prefix " ++ ps ++ " (" ++ prefix ++ ") for key " ++ cs
stripPrefix _ [] = error $ "Prefix " ++ prefix ++ " is too long"
lowercaseFirst (c:cs) = Char.toLower c : cs
removePrefixOpts prefix = defaultOptions { fieldLabelModifier = removePrefixModifier prefix }
data Document = Document data Document = Document
{ documentId :: Text { documentId :: Text
, documentDate :: Day , documentDate :: Day
@ -99,48 +120,35 @@ data Document = Document
, documentLectures :: [Lecture] , documentLectures :: [Lecture]
, documentDownloadable :: Bool , documentDownloadable :: Bool
} }
deriving (Show) deriving (Show, Generic)
instance FromJSON Document where instance FromJSON Document where
parseJSON = withObject "Document" $ \v -> Document parseJSON = genericParseJSON $ removePrefixOpts "document"
<$> v .: "id"
<*> v .: "date"
<*> v .: "semester"
<*> v .: "publicComment"
<*> v .: "faculty"
<*> v .: "lectures"
<*> v .: "downloadable"
data Faculty = Faculty data Faculty = Faculty
{ facultyId :: Text { facultyId :: Text
, facultyDisplayName :: Text , facultyDisplayName :: Text
} }
deriving (Show) deriving (Generic, Show)
instance FromJSON Faculty where instance FromJSON Faculty where
parseJSON = withObject "Faculty" $ \v -> Faculty parseJSON = genericParseJSON $ removePrefixOpts "faculty"
<$> v .: "id"
<*> v .: "displayName"
data Lectures = Lectures { unLectures :: [Lecture] } data Lectures = Lectures { unLectures :: [Lecture] }
deriving (Show) deriving (Generic, Show)
instance FromJSON Lectures where instance FromJSON Lectures where
parseJSON = withObject "Lectures" $ \v -> Lectures parseJSON = genericParseJSON $ removePrefixOpts "un"
<$> v .: "lectures"
data Lecture = Lecture data Lecture = Lecture
{ lectureId :: Text { lectureId :: Text
, lectureDisplayName :: Text , lectureDisplayName :: Text
, lectureAliases :: [Text] , lectureAliases :: [Text]
} }
deriving (Show) deriving (Generic, Show)
instance FromJSON Lecture where instance FromJSON Lecture where
parseJSON = withObject "Lecture" $ \v -> Lecture parseJSON = genericParseJSON $ removePrefixOpts "lecture"
<$> v .: "id"
<*> v .: "displayName"
<*> v .: "aliases"
getAllLectures :: (HasEndpointInfo m, MonadIO m) => m (Either SqueakError [Lecture]) getAllLectures :: (HasEndpointInfo m, MonadIO m) => m (Either SqueakError [Lecture])
getAllLectures = fmap unLectures <$> joinErrors <$> mkQuery getAllLectures = fmap unLectures <$> joinErrors <$> mkQuery
@ -168,22 +176,18 @@ instance FromJSON LoginResult where
data Credentials = Credentials data Credentials = Credentials
{ credentialsToken :: Text { credentialsToken :: Text
, credentialsUser :: User , credentialsUser :: User
} deriving (Show) } deriving (Generic, Show)
instance FromJSON Credentials where instance FromJSON Credentials where
parseJSON = withObject "Credentials" $ \v -> Credentials parseJSON = genericParseJSON $ removePrefixOpts "credentials"
<$> v .: "token"
<*> v .: "user"
data User = User data User = User
{ userUsername :: Text { userUsername :: Text
, userDisplayName :: Text , userDisplayName :: Text
} deriving (Show) } deriving (Generic, Show)
instance FromJSON User where instance FromJSON User where
parseJSON = withObject "User" $ \v -> User parseJSON = genericParseJSON $ removePrefixOpts "user"
<$> v .: "username"
<*> v .: "displayName"
{- {-
login :: Text -> Text -> Req (Either [GQLError] Credentials) login :: Text -> Text -> Req (Either [GQLError] Credentials)
@ -212,6 +216,7 @@ data SqueakError
| GQLErrors [GQLError] | GQLErrors [GQLError]
deriving (Show) deriving (Show)
-- TODO: doc
instance FromJSON SqueakError where instance FromJSON SqueakError where
parseJSON = withObject "SqueakError" $ \v -> SqueakError parseJSON = withObject "SqueakError" $ \v -> SqueakError
<$> v .: "errorCode" <$> v .: "errorCode"
@ -220,6 +225,7 @@ instance FromJSON SqueakError where
newtype SqueakErrorOr a = SqueakErrorOr (Either SqueakError a) newtype SqueakErrorOr a = SqueakErrorOr (Either SqueakError a)
deriving (Show) deriving (Show)
-- TODO: doc
instance FromJSON a => FromJSON (SqueakErrorOr a) where instance FromJSON a => FromJSON (SqueakErrorOr a) where
-- | Parse 'SqueakError' if @errorCode@ and @msg@ are present; otherwise, parse an 'a'. -- | Parse 'SqueakError' if @errorCode@ and @msg@ are present; otherwise, parse an 'a'.
parseJSON v = SqueakErrorOr parseJSON v = SqueakErrorOr
@ -238,13 +244,10 @@ data Order = Order
, orderTag :: Text , orderTag :: Text
, orderNumPages :: Int , orderNumPages :: Int
} }
deriving (Show) deriving (Generic, Show)
instance FromJSON Order where instance FromJSON Order where
parseJSON = withObject "Order" $ \v -> Order parseJSON = genericParseJSON $ removePrefixOpts "order"
<$> v .: "id"
<*> v .: "tag"
<*> v .: "numPages"
createOrder :: (HasEndpointInfo m, MonadIO m) => Text -> [Text] -> m (Either SqueakError Order) createOrder :: (HasEndpointInfo m, MonadIO m) => Text -> [Text] -> m (Either SqueakError Order)
createOrder tag documents = joinErrors <$> fmap unCreateOrderResult <$> mkQueryWithVars createOrder tag documents = joinErrors <$> fmap unCreateOrderResult <$> mkQueryWithVars