{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Stack.Types.DownloadInfo
( DownloadInfo (..)
, parseDownloadInfoFromObject
) where
import Data.Aeson.Types ( FromJSON (..), Object )
import Data.Aeson.WarningParser
( WarningParser, WithJSONWarnings (..), (..:), (..:?)
, withObjectWarnings
)
import Stack.Prelude
data DownloadInfo = DownloadInfo
{ DownloadInfo -> Text
downloadInfoUrl :: Text
, DownloadInfo -> Maybe Int
downloadInfoContentLength :: Maybe Int
, DownloadInfo -> Maybe ByteString
downloadInfoSha1 :: Maybe ByteString
, DownloadInfo -> Maybe ByteString
downloadInfoSha256 :: Maybe ByteString
}
deriving Int -> DownloadInfo -> ShowS
[DownloadInfo] -> ShowS
DownloadInfo -> String
(Int -> DownloadInfo -> ShowS)
-> (DownloadInfo -> String)
-> ([DownloadInfo] -> ShowS)
-> Show DownloadInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DownloadInfo -> ShowS
showsPrec :: Int -> DownloadInfo -> ShowS
$cshow :: DownloadInfo -> String
show :: DownloadInfo -> String
$cshowList :: [DownloadInfo] -> ShowS
showList :: [DownloadInfo] -> ShowS
Show
instance FromJSON (WithJSONWarnings DownloadInfo) where
parseJSON :: Value -> Parser (WithJSONWarnings DownloadInfo)
parseJSON = String
-> (Object -> WarningParser DownloadInfo)
-> Value
-> Parser (WithJSONWarnings DownloadInfo)
forall a.
String
-> (Object -> WarningParser a)
-> Value
-> Parser (WithJSONWarnings a)
withObjectWarnings String
"DownloadInfo" Object -> WarningParser DownloadInfo
parseDownloadInfoFromObject
parseDownloadInfoFromObject :: Object -> WarningParser DownloadInfo
parseDownloadInfoFromObject :: Object -> WarningParser DownloadInfo
parseDownloadInfoFromObject Object
o = do
Text
url <- Object
o Object -> Text -> WarningParser Text
forall a. FromJSON a => Object -> Text -> WarningParser a
..: Text
"url"
Maybe Int
contentLength <- Object
o Object -> Text -> WarningParser (Maybe Int)
forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"content-length"
Maybe Text
sha1TextMay <- Object
o Object -> Text -> WarningParser (Maybe Text)
forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"sha1"
Maybe Text
sha256TextMay <- Object
o Object -> Text -> WarningParser (Maybe Text)
forall a. FromJSON a => Object -> Text -> WarningParser (Maybe a)
..:? Text
"sha256"
DownloadInfo -> WarningParser DownloadInfo
forall a. a -> WriterT WarningParserMonoid Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
DownloadInfo
{ downloadInfoUrl :: Text
downloadInfoUrl = Text
url
, downloadInfoContentLength :: Maybe Int
downloadInfoContentLength = Maybe Int
contentLength
, downloadInfoSha1 :: Maybe ByteString
downloadInfoSha1 = (Text -> ByteString) -> Maybe Text -> Maybe ByteString
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
encodeUtf8 Maybe Text
sha1TextMay
, downloadInfoSha256 :: Maybe ByteString
downloadInfoSha256 = (Text -> ByteString) -> Maybe Text -> Maybe ByteString
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
encodeUtf8 Maybe Text
sha256TextMay
}