{-# LANGUAGE OverloadedStrings #-} module Network.Cloudflare.Types where import Data.Aeson import Data.Text -- | Cloudflare API token -- see https://developers.cloudflare.com/fundamentals/api/get-started/create-token/ for instructions on creating a token data CloudflareAuth = CloudflareAuth { cloudflareAuthToken :: Text } -- | Cloudflare account information data Account = Account { accountId :: Text -- ^ Cloudflare account ID , accountName :: Text -- ^ Cloudflare account name } deriving (Eq, Ord, Show) instance FromJSON Account where parseJSON = withObject "Account" $ \o -> do id' <- o .: "id" name <- o .: "name" pure $ Account id' name -- | Result type for Cloudflare API calls that don't return any extra data -- and wrap the result in a "result" field newtype ResultOnly a = ResultOnly { resultOnlyResult :: a } deriving (Eq, Ord, Show) instance FromJSON a => FromJSON (ResultOnly a) where parseJSON = withObject "ResultOnly" $ \o -> do result <- o .: "result" pure $ ResultOnly result -- | Result type for Cloudflare API call errors data ResponseError = ResponseError { responseErrorCode :: Int , responseErrorMessage :: Text } deriving (Eq, Ord, Show) instance FromJSON ResponseError where parseJSON = withObject "ResponseError" $ \o -> do code <- o .: "code" message <- o .: "message" pure $ ResponseError code message -- | Additional messages from Cloudflare API calls data ResponseMessage = ResponseMessage { responseMessageCode :: Int , responseMessageMessage :: Text } deriving (Eq, Ord, Show) instance FromJSON ResponseMessage where parseJSON = withObject "ResponseMessage" $ \o -> do code <- o .: "code" message <- o .: "message" pure $ ResponseMessage code message -- | Result information for Cloudflare API calls that return a list of results data ResultInfo = ResultInfo { resultInfoCount :: Int , resultInfoPage :: Int , resultInfoPerPage :: Int , resultInfoTotalCount :: Int } deriving (Eq, Ord, Show) instance FromJSON ResultInfo where parseJSON = withObject "ResultInfo" $ \o -> do c <- o .: "count" page <- o .: "page" perPage <- o .: "per_page" totalCount <- o .: "total_count" pure $ ResultInfo c page perPage totalCount -- TODO this could use a better name that doesn't conflict with the Result type from aeson -- | Result type for Cloudflare API calls that returns a result with a list of errors, a list of messages, and a success flag data ResultResponse a = ResultResponse { resultErrors :: [ResponseError] , resultMessages :: [ResponseMessage] , resultSuccess :: Bool , resultResult :: a } deriving (Eq, Ord, Show) instance FromJSON a => FromJSON (ResultResponse a) where parseJSON = withObject "Result" $ \o -> do errors <- o .: "errors" messages <- o .: "messages" success <- o .: "success" result <- o .: "result" pure $ ResultResponse errors messages success result -- | Result type for Cloudflare API calls that returns a result with meta information about the result, -- a list of errors, a list of messages, and a success flag data ResultWithInfo a = ResultWithInfo { resultWithInfoInfo :: ResultInfo , resultWithInfoErrors :: [ResponseError] , resultWithInfoMessages :: [ResponseMessage] , resultWithInfoSuccess :: Bool , resultWithInfoResult :: a } deriving (Eq, Ord, Show) instance FromJSON a => FromJSON (ResultWithInfo a) where parseJSON = withObject "ResultWithInfo" $ \o -> do errors <- o .: "errors" messages <- o .: "messages" success <- o .: "success" resultInfo <- o .: "result_info" result <- o .: "result" pure $ ResultWithInfo resultInfo errors messages success result