{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Network.S3
(
BucketId(..)
, BucketInfo(..)
, Acl(..)
, listBuckets
, createBucket
, deleteBucket
, listObjects
, listObjectsFold
, listObjectsChunk
, ObjKey(..), isNullObjKey, nullObjKey
, ObjMetaInfo(..)
, CType(..), noCType
, ETag(..)
, MD5Val
, md5hash
, md5hex
, md5unhex
, md5ToSBS
, md5FromSBS
, putObject
, copyObject
, getObject
, deleteObject
, Condition(..)
, putObjectCond
, getObjectCond
, deleteObjectCond
, ErrorCode(..)
, ProtocolError(..)
, Credentials(..), noCredentials
, S3Cfg(..), defaultS3Cfg
, SignatureVersion(..)
, Connection
, withConnection
, connect
, close
) where
import Internal
import Network.S3.Signature
import Network.S3.Types
import Network.S3.XML
import Control.Concurrent
import Control.Exception
import qualified Data.ByteString as BS
import qualified Data.ByteString.Builder as Builder
import qualified Data.ByteString.Char8 as BC8
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Short as BSS
import Data.Char
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Data.Text.Lazy.Encoding as TL
import qualified Data.Text.Short as TS
import Data.Time.Clock (getCurrentTime)
import qualified Network.Http.Client as HC
import qualified System.IO.Streams as Streams
import qualified Text.XML as X
data ProtocolError
= ProtocolInconsistency String
| HttpFailure !SomeException
| UnexpectedResponse !Int
!ShortByteString
!ShortByteString
BL.ByteString
deriving (Show, Typeable, Generic)
instance Exception ProtocolError
data ErrorCode
= AccessDenied
| BucketAlreadyExists
| BucketAlreadyOwnedByYou
| BucketNotEmpty
| MalformedXML
| NoSuchBucket
| NoSuchKey
| InvalidArgument
| InvalidDigest
| SignatureDoesNotMatch
| UnknownError !ShortText
deriving (Show, Typeable, Generic)
instance Exception ErrorCode
instance NFData ErrorCode
errorToErrorCode :: Error -> ErrorCode
errorToErrorCode (Error x) = case x of
"AccessDenied" -> AccessDenied
"BucketAlreadyExists" -> BucketAlreadyExists
"BucketAlreadyOwnedByYou" -> BucketAlreadyOwnedByYou
"BucketNotEmpty" -> BucketNotEmpty
"MalformedXML" -> MalformedXML
"NoSuchBucket" -> NoSuchBucket
"NoSuchKey" -> NoSuchKey
"InvalidArgument" -> InvalidArgument
"InvalidDigest" -> InvalidDigest
"SignatureDoesNotMatch" -> SignatureDoesNotMatch
_ -> UnknownError x
urlEncodeObjKey, urlEncodeObjKeyQry :: ObjKey -> ByteString
urlEncodeObjKey = urlEncode False . TS.toByteString . unObjKey
urlEncodeObjKeyQry = urlEncode True . TS.toByteString . unObjKey
s3'ObjKey :: X.LName -> Bool -> X.Element -> Either String ObjKey
s3'ObjKey ln False el = ObjKey <$> xsd'string (s3qname ln) el
s3'ObjKey ln True el = do
s <- xsd'string (s3qname ln) el
case TS.fromText <$> urlDecodeTextUtf8 s of
Just s' -> pure (ObjKey s')
Nothing -> Left ("<" <> showQN (X.elName el) <> "> failed to url-decode ObjKey")
objUrlPath :: BucketId -> ObjKey -> UrlPath
objUrlPath (BucketId bucketId) objkey = "/" <> BSS.fromShort bucketId <> "/" <> urlEncodeObjKey objkey
bucketUrlPath :: BucketId -> UrlPath
bucketUrlPath (BucketId bucketId) = "/" <> BSS.fromShort bucketId
withAWSHeaders :: Connection -> (AWSHeaders -> IO b) -> IO b
withAWSHeaders conn cont = do
now <- getCurrentTime
cont AWSHeaders
{ ahdrMethod = HC.GET
, ahdrUrlPath = "/"
, ahdrUrlQuery = mempty
, ahdrTimestamp = now
, ahdrContentType = noCType
, ahdrContentHashes = Nothing
, ahdrExtraHeaders = []
, ahdrSigType = s3cfgSigVersion $ s3connCfg conn
, ahdrHost = s3connHost conn
, ahdrRegion = s3cfgRegion $ s3connCfg conn
}
listBuckets :: Connection
-> Credentials
-> IO [BucketInfo]
listBuckets conn creds = withAWSHeaders conn $ \awsh -> do
let q = HC.buildRequest1 $
setAWSRequest creds awsh
{ ahdrMethod = HC.GET
, ahdrUrlPath = "/"
}
(resp,mtmp) <- doHttpReqXml conn q HC.emptyBody
case HC.getStatusCode resp of
200 -> pure ()
_ -> throwUnexpectedXmlResp resp mtmp
case maybe (Left "empty body") parseXML mtmp of
Right (ListAllMyBucketsResult bs) -> pure bs
Left err -> throwProtoFail $ "ListAllMyBucketsResult: " <> err
createBucket :: Connection
-> Credentials
-> BucketId
-> Maybe Acl
-> IO ()
createBucket conn creds bid macl = withAWSHeaders conn $ \awsh -> do
let q = HC.buildRequest1 $
setAWSRequest creds awsh
{ ahdrMethod = HC.PUT
, ahdrUrlPath = bucketUrlPath bid
, ahdrExtraHeaders = hdrs
}
(resp, mtmp) <- doHttpReqXml conn q HC.emptyBody
case HC.getStatusCode resp of
200 -> pure ()
_ -> throwUnexpectedXmlResp resp mtmp
where
hdrs = case macl of
Nothing -> []
Just acl -> [("x-amz-acl", acl2str acl)]
deleteBucket :: Connection
-> Credentials
-> BucketId
-> IO ()
deleteBucket conn creds bid = withAWSHeaders conn $ \awsh -> do
let q = HC.buildRequest1 $
setAWSRequest creds awsh
{ ahdrMethod = HC.DELETE
, ahdrUrlPath = bucketUrlPath bid
}
(resp, mtmp) <- doHttpReqXml conn q HC.emptyBody
case HC.getStatusCode resp of
204 -> pure ()
_ -> throwUnexpectedXmlResp resp mtmp
pure ()
data Connection = S3Conn (MVar HC.Connection) !ByteString !S3Cfg
s3connCfg :: Connection -> S3Cfg
s3connCfg (S3Conn _ _ cfg) = cfg
s3connHost :: Connection -> ByteString
s3connHost (S3Conn _ h _) = h
withConnection :: S3Cfg -> (Connection -> IO a) -> IO a
withConnection cfg@S3Cfg{..} = bracket (connect cfg) close
connect :: S3Cfg -> IO Connection
connect cfg@S3Cfg{..} = do
c <- HC.establishConnection s3cfgBaseUrl
c' <- newMVar c
pure (S3Conn c' (cHost c) cfg)
close :: Connection -> IO ()
close (S3Conn cref _ _) = withMVar cref HC.closeConnection
cHost :: HC.Connection -> ByteString
cHost c = HC.getHostname c (HC.buildRequest1 (pure ()))
doHttpReq :: Bool -> Connection -> HC.Request
-> (Streams.OutputStream Builder.Builder -> IO ())
-> IO (HC.Response, BL.ByteString)
doHttpReq isProtocol (S3Conn cref _ S3Cfg{..}) q body = withMVar cref $ \c -> do
when s3cfgDebug $ do
BS.putStrLn sep1
T.putStr (T.pack $ show q)
BS.putStrLn sep2
(resp,bs) <- handle exh $ do
() <- HC.sendRequest c q body
HC.receiveResponse c concatHandler
when s3cfgDebug $ do
T.putStr (T.pack $ show resp)
unless (BL.null bs) $ do
BS.putStrLn sep2
if isProtocol || HC.getStatusCode resp /= 200
then BL.putStrLn bs
else T.putStrLn (T.pack $ "[non-protocol body with size=" <> show (BL.length bs) <> "]")
BS.putStrLn sep3
pure (resp, bs)
where
sep1 = "/==========================================================================\\"
sep2 = "----------------------------------------------------------------------------"
sep3 = "\\==========================================================================/"
exh ex = throwIO (HttpFailure ex)
concatHandler :: HC.Response -> Streams.InputStream ByteString -> IO (HC.Response,BL.ByteString)
concatHandler res i1 = do
xs <- Streams.toList i1
return (res, BL.fromChunks xs)
doHttpReqXml :: Connection -> HC.Request
-> (Streams.OutputStream Builder.Builder -> IO ())
-> IO (HC.Response, Maybe X.Element)
doHttpReqXml cn rq body = do
(resp,bs) <- doHttpReq True cn rq body
case fromMaybe mempty $ HC.getHeader resp "content-type" of
ct | isXmlMimeType ct -> do
txt <- either (\_ -> throwProtoFail "failed to decode UTF-8 content from server") pure (TL.decodeUtf8' bs)
case X.parseXMLRoot txt of
Left _ -> throwProtoFail "received malformed XML response from server"
Right x -> pure (resp,Just $! X.rootElement x)
| HC.getStatusCode resp == 204 -> pure (resp, Nothing)
| HC.getStatusCode resp == 200, BL.null bs -> pure (resp, Nothing)
| otherwise -> throwUnexpectedResp resp bs
getCT :: HC.Response -> CType
getCT resp = case HC.getHeader resp "Content-Type" of
Nothing -> noCType
Just bs -> maybe noCType CType (TS.fromByteString bs)
isXmlMimeType :: ByteString -> Bool
isXmlMimeType bs = case type_subtype of
"application/xml" -> True
"text/xml" -> True
_ -> False
where
type_subtype = BC8.map toLower $ BC8.takeWhile (not . \c -> isSpace c || c == ';') bs
throwUnexpectedResp :: HC.Response -> BL.ByteString -> IO a
throwUnexpectedResp resp bs
= case fromMaybe mempty $ HC.getHeader resp "Content-Type" of
ct | isXmlMimeType ct
, Right e <- decodeXML bs -> throwIO $! errorToErrorCode e
| otherwise -> genEx ct
where
genEx ct = throwIO $! UnexpectedResponse (HC.getStatusCode resp) (BSS.toShort $ HC.getStatusMessage resp) (BSS.toShort ct) bs
throwUnexpectedXmlResp :: HC.Response -> Maybe X.Element -> IO a
throwUnexpectedXmlResp resp Nothing
= throwIO $! UnexpectedResponse (HC.getStatusCode resp)
(BSS.toShort $ HC.getStatusMessage resp)
(maybe mempty BSS.toShort $ HC.getHeader resp "Content-Type")
mempty
throwUnexpectedXmlResp resp (Just x) = case parseXML x of
Right e -> throwIO $! errorToErrorCode e
Left _ -> genEx
where
genEx = throwIO $! UnexpectedResponse (HC.getStatusCode resp) (BSS.toShort $ HC.getStatusMessage resp) "application/xml" (TL.encodeUtf8 (X.serializeXMLDoc x))
throwProtoFail :: String -> IO a
throwProtoFail = throwIO . ProtocolInconsistency
listObjects :: Connection
-> Credentials
-> BucketId
-> ObjKey
-> Maybe Char
-> IO ([ObjMetaInfo],[ObjKey])
listObjects conn creds bid pfx delim = go nullObjKey [] []
where
go marker acc1 acc2 = do
(marker', objs, pfxs) <- listObjectsChunk conn creds bid pfx delim marker 0
let acc1' = acc1 <> objs
acc2' = acc2 <> pfxs
case () of
_ | isNullObjKey marker' -> pure (acc1', acc2')
| otherwise -> go marker' acc1' acc2'
listObjectsFold :: Connection
-> Credentials
-> BucketId
-> ObjKey
-> Maybe Char
-> Word16
-> a
-> (a -> [ObjMetaInfo] -> [ObjKey] -> IO a)
-> IO a
listObjectsFold conn creds bid pfx delim maxKeys acc0 lbody = go nullObjKey acc0
where
go marker acc = do
(marker', objs, pfxs) <- listObjectsChunk conn creds bid pfx delim marker maxKeys
acc' <- lbody acc objs pfxs
case () of
_ | isNullObjKey marker' -> pure acc'
| otherwise -> go marker' acc'
data MetadataEntry = MetadataEntry ShortText ShortText
deriving Show
pMetadataEntry :: P MetadataEntry
pMetadataEntry = MetadataEntry <$> one (s3_xsd'string "Name") <*> one (s3_xsd'string "Value")
data ListBucketResult = LBR
{ lbrMetadata :: [MetadataEntry]
, lbrName :: BucketId
, lbrPrefix :: ObjKey
, lbrMarker :: ObjKey
, lbrNextMarker :: Maybe ObjKey
, lbrMaxKeys :: Int32
, lbrDelimiter :: Maybe Char
, lbrIsTruncated :: Bool
, lbrEncodingTypeUrl:: Bool
, lbrContents :: [ObjMetaInfo]
, lbrCommonPrefixes :: [ObjKey]
} deriving Show
instance FromXML ListBucketResult where
tagFromXML _ = s3qname "ListBucketResult"
parseXML_ = withChildren $ do
lbrMetadata <- unbounded (parseXML' (s3qname "Metadata") (withChildren pMetadataEntry))
lbrName <- one (s3_xsd'string "Name")
tmp <- aheadMaybeOne ((== s3qname "EncodingType") . X.elName)
(s3_xsd'string "EncodingType")
lbrEncodingTypeUrl <- case tmp :: Maybe Text of
Just "url" -> pure True
Nothing -> pure False
Just _ -> failP "unsupported <EncodingType> encoutered"
lbrPrefix <- one (s3'ObjKey "Prefix" lbrEncodingTypeUrl)
lbrMarker <- one (s3'ObjKey "Marker" lbrEncodingTypeUrl)
lbrNextMarker <- maybeOne (s3'ObjKey "NextMarker" lbrEncodingTypeUrl)
lbrMaxKeys <- one (s3_xsd'int "MaxKeys")
lbrDelimiter <- fmap T.head <$> maybeOne (s3_xsd'string "Delimiter")
lbrIsTruncated <- one (s3_xsd'boolean "IsTruncated")
lbrContents <- unbounded (parseXML' (s3qname "Contents") $
withChildren (pObjMetaInfo lbrEncodingTypeUrl))
lbrCommonPrefixes <- unbounded (parseXML' (s3qname "CommonPrefixes") $
withChildren (pCommonPrefixes lbrEncodingTypeUrl))
pure LBR{..}
where
pCommonPrefixes urlEnc = one (s3'ObjKey "Prefix" urlEnc)
listObjectsChunk :: Connection
-> Credentials
-> BucketId
-> ObjKey
-> Maybe Char
-> ObjKey
-> Word16
-> IO (ObjKey,[ObjMetaInfo],[ObjKey])
listObjectsChunk conn creds bid pfx delim marker maxKeys = withAWSHeaders conn $ \awsh -> do
let q = HC.buildRequest1 $
setAWSRequest creds awsh
{ ahdrMethod = HC.GET
, ahdrUrlPath = bucketUrlPath bid
, ahdrUrlQuery = urlq
}
(resp,mtmp) <- doHttpReqXml conn q HC.emptyBody
case HC.getStatusCode resp of
200 -> pure ()
_ -> throwUnexpectedXmlResp resp mtmp
LBR{..} <- case maybe (Left "empty body") parseXML mtmp of
Right lbr -> pure (lbr :: ListBucketResult)
Left err -> throwProtoFail $ "ListObjects: " <> err
let nextMarker' | lbrIsTruncated = fromMaybe nullObjKey (max (omiKey <$> last lbrContents) (last lbrCommonPrefixes))
| otherwise = nullObjKey
nextMarker | lbrIsTruncated = fromMaybe nextMarker' lbrNextMarker
| otherwise = nullObjKey
unless (lbrIsTruncated /= isNullObjKey nextMarker) $
throwProtoFail "NextMarker and isTruncated inconsistent"
unless (nextMarker == nextMarker') $
throwProtoFail "NextMarker inconsistent"
evaluate (force (nextMarker,lbrContents,lbrCommonPrefixes))
where
qryparms = mconcat
[ [ "delimiter=" <> urlEncode True (BC8.singleton d) | Just d <- [delim] ]
, [ "encoding-type=url" | s3cfgEncodingUrl (s3connCfg conn) ]
, [ "marker=" <> urlEncodeObjKeyQry marker | not (isNullObjKey marker) ]
, [ "max-keys=" <> BC8.pack (show maxKeys) | maxKeys > 0 ]
, [ "prefix=" <> urlEncodeObjKeyQry pfx | not (isNullObjKey pfx) ]
]
urlq | null qryparms = mempty
| otherwise = "?" <> BC8.intercalate "&" qryparms
data Acl = AclPrivate
| AclPublicRead
| AclPublicReadWrite
| AclPublicAuthenticatedRead
deriving (Show,Typeable,Generic)
instance NFData Acl
acl2str :: Acl -> ByteString
acl2str acl = case acl of
AclPrivate -> "private"
AclPublicRead -> "public-read"
AclPublicReadWrite -> "public-read-write"
AclPublicAuthenticatedRead -> "authenticated-read"
data CopyObjectResult = CopyObjectResult
{ _corLastModified :: UTCTime
, corETag :: ETag
} deriving Show
instance FromXML CopyObjectResult where
tagFromXML _ = s3qname "CopyObjectResult"
parseXML_ = withChildren $
CopyObjectResult <$> one (s3_xsd'dateTime "LastModified")
<*> (mkETag <$> one (s3_xsd'string "ETag"))
copyObject :: Connection
-> Credentials
-> BucketId
-> ObjKey
-> (BucketId,ObjKey)
-> Maybe Acl
-> IO ETag
copyObject conn creds bid objkey (srcBid,srcObjKey) macl = withAWSHeaders conn $ \awsh -> do
let q = HC.buildRequest1 $
setAWSRequest creds awsh
{ ahdrMethod = HC.PUT
, ahdrUrlPath = objUrlPath bid objkey
, ahdrExtraHeaders = hdrs
}
(resp, mtmp) <- doHttpReqXml conn q HC.emptyBody
case (HC.getStatusCode resp,mtmp) of
(200,Just x) | Right v <- parseXML x -> pure (corETag v)
_ -> throwUnexpectedXmlResp resp mtmp
where
hdrs = ("x-amz-copy-source", objUrlPath srcBid srcObjKey)
: case macl of
Nothing -> []
Just acl -> [("x-amz-acl", acl2str acl)]
putObject :: Connection
-> Credentials
-> BucketId
-> ObjKey
-> BL.ByteString
-> CType
-> Maybe Acl
-> IO ETag
putObject conn creds bid objkey objdata ctype macl
= fromMaybe undefined <$> putObjectX conn creds bid objkey objdata ctype macl Nothing
putObjectCond :: Connection
-> Credentials
-> BucketId
-> ObjKey
-> BL.ByteString
-> CType
-> Maybe Acl
-> Condition
-> IO (Maybe ETag)
putObjectCond conn creds bid objkey objdata ctype macl cond
= putObjectX conn creds bid objkey objdata ctype macl (Just cond)
putObjectX :: Connection
-> Credentials
-> BucketId
-> ObjKey
-> BL.ByteString
-> CType
-> Maybe Acl
-> Maybe Condition
-> IO (Maybe ETag)
putObjectX conn creds bid objkey objdata ctype macl mcond = withAWSHeaders conn $ \awsh -> do
let q = HC.buildRequest1 $ do
setAWSRequest creds awsh
{ ahdrMethod = HC.PUT
, ahdrUrlPath = objUrlPath bid objkey
, ahdrContentType = ctype
, ahdrContentHashes = Just (md5,sha256,BL.length objdata)
, ahdrExtraHeaders = hdrs
}
forM_ mcond setConditionHeader
(resp, bs) <- doHttpReq True conn q (bsBody objdata)
case HC.getStatusCode resp of
200 -> case mkETag <$> HC.getHeader resp "ETag" of
Just x -> pure (Just x)
Nothing -> throwProtoFail "ETag"
412 | Just _ <- mcond -> pure Nothing
_ -> throwUnexpectedResp resp bs
where
hdrs = case macl of
Nothing -> []
Just acl -> [("x-amz-acl", acl2str acl)]
md5 = md5hash objdata
sha256 = sha256hash objdata
bsBody :: BL.ByteString -> Streams.OutputStream Builder.Builder -> IO ()
bsBody bs = Streams.write (Just (Builder.lazyByteString bs))
getObject :: Connection
-> Credentials
-> BucketId
-> ObjKey
-> IO (ETag, CType, BL.ByteString)
getObject conn creds bid objkey = withAWSHeaders conn $ \awsh -> do
let q = HC.buildRequest1 $
setAWSRequest creds awsh
{ ahdrMethod = HC.GET
, ahdrUrlPath = objUrlPath bid objkey
}
(resp, bs) <- doHttpReq False conn q HC.emptyBody
case HC.getStatusCode resp of
200 -> case mkETag <$> HC.getHeader resp "ETag" of
Just x -> pure (x, getCT resp, bs)
Nothing -> throwProtoFail "ETag"
_ -> throwUnexpectedResp resp bs
getObjectCond :: Connection
-> Credentials
-> BucketId
-> ObjKey
-> Condition
-> IO (Maybe (ETag, CType, BL.ByteString))
getObjectCond conn creds bid objkey cond = withAWSHeaders conn $ \awsh -> do
let q = HC.buildRequest1 $ do
setAWSRequest creds awsh
{ ahdrMethod = HC.GET
, ahdrUrlPath = objUrlPath bid objkey
}
setConditionHeader cond
(resp, bs) <- doHttpReq False conn q HC.emptyBody
case HC.getStatusCode resp of
200 -> case mkETag <$> HC.getHeader resp "ETag" of
Just x -> pure $ Just (x, getCT resp, bs)
Nothing -> throwProtoFail "ETag"
304 | IfNotMatch _ <- cond -> pure Nothing
| IfNotExists <- cond -> pure Nothing
412 | IfMatch _ <- cond -> pure Nothing
| IfExists <- cond -> pure Nothing
_ -> throwUnexpectedResp resp bs
deleteObject :: Connection -> Credentials -> BucketId -> ObjKey -> IO ()
deleteObject conn creds bid objkey = withAWSHeaders conn $ \awsh -> do
let q = HC.buildRequest1 $
setAWSRequest creds awsh
{ ahdrMethod = HC.DELETE
, ahdrUrlPath = objUrlPath bid objkey
}
(resp, bs) <- doHttpReq True conn q HC.emptyBody
case HC.getStatusCode resp of
204 -> pure ()
_ -> throwUnexpectedResp resp bs
deleteObjectCond :: Connection -> Credentials -> BucketId -> ObjKey -> Condition -> IO Bool
deleteObjectCond conn creds bid objkey cond = withAWSHeaders conn $ \awsh -> do
let q = HC.buildRequest1 $ do
setAWSRequest creds awsh
{ ahdrMethod = HC.DELETE
, ahdrUrlPath = objUrlPath bid objkey
}
setConditionHeader cond
(resp, bs) <- doHttpReq True conn q HC.emptyBody
case HC.getStatusCode resp of
204 -> pure True
412 -> pure False
_ -> throwUnexpectedResp resp bs
data BucketInfo = BucketInfo !BucketId !UTCTime
deriving (Show,Typeable,Generic)
instance NFData BucketInfo
instance FromXML BucketInfo where
tagFromXML _ = s3qname "Bucket"
parseXML_ = withChildren $
BucketInfo <$> one (s3_xsd'string "Name")
<*> one (s3_xsd'dateTime "CreationDate")
pObjMetaInfo :: Bool -> P ObjMetaInfo
pObjMetaInfo urlEnc = do
omiKey <- one (s3'ObjKey "Key" urlEnc)
omiLastModified <- one (s3_xsd'dateTime "LastModified")
omiEtag <- mkETag <$> one (s3_xsd'string "ETag")
omiSize <- one (s3_xsd'long "Size")
let sc = \case
"DEEP_ARCHIVE" -> Just ()
"GLACIER" -> Just ()
"INTELLIGENT_TIERING"-> Just ()
"ONEZONE_IA" -> Just ()
"REDUCED_REDUNDANCY" -> Just ()
"STANDARD" -> Just ()
"STANDARD_IA" -> Just ()
"UNKNOWN" -> Just ()
_ -> Nothing
let s3_storageClass = s3_xsd'enum "StorageClass" sc
msc <- maybeOne s3_storageClass
(own,()) <- case msc of
Nothing -> (,) <$> (Just <$> one parseXML) <*> one s3_storageClass
Just sc' -> (,) <$> maybeOne parseXML <*> pure sc'
let omiOwnerId = fmap ownerID own
pure $! (OMI {..})
data Owner = Owner { ownerID :: ShortText
, _ownerDisplayName :: Maybe ShortText
} deriving Show
instance FromXML Owner where
tagFromXML _ = s3qname "Owner"
parseXML_ = withChildren $
Owner <$> one (s3_xsd'string "ID")
<*> maybeOne (s3_xsd'string "DisplayName")
newtype ListAllMyBucketsResult = ListAllMyBucketsResult [BucketInfo]
instance FromXML ListAllMyBucketsResult where
tagFromXML _ = s3qname "ListAllMyBucketsResult"
parseXML_ = withChildren $ do
_ <- one pure
ListAllMyBucketsResult <$> one (fmap unBuckets . parseXML)
newtype Buckets = Buckets { unBuckets :: [BucketInfo] }
instance FromXML Buckets where
tagFromXML _ = s3qname "Buckets"
parseXML_ = withChildren $ Buckets <$> unbounded parseXML
newtype Error = Error ShortText
deriving Show
instance FromXML Error where
tagFromXML _ = X.unqual "Error"
parseXML_ = withChildren $ do
code <- one (xsd'string (X.unqual "Code"))
void unboundedAny
pure (Error code)