{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
module Network.AWS.S3.Internal
( Region (..)
, BucketName (..)
, ETag (..)
, ObjectVersionId (..)
, LocationConstraint (..)
, _LocationConstraint
, Delimiter
, ObjectKey (..)
, _ObjectKey
, keyPrefix
, keyName
, keyComponents
, getWebsiteEndpoint
) where
import Data.String (IsString)
import Network.AWS.Data.Log
import Network.AWS.Data.XML
import Network.AWS.Lens (IndexedTraversal', Iso', Prism', Traversal')
import Network.AWS.Lens (iso, prism, traversed, _1, _2)
import Network.AWS.Prelude
import qualified Data.Text as Text
newtype BucketName = BucketName Text
deriving
( Eq
, Ord
, Read
, Show
, Data
, Typeable
, Generic
, IsString
, FromText
, ToText
, ToByteString
, FromXML
, ToXML
, ToQuery
, ToLog
, FromJSON
)
instance Hashable BucketName
instance NFData BucketName
newtype ETag = ETag ByteString
deriving
( Eq
, Ord
, Read
, Show
, Data
, Typeable
, Generic
, IsString
, FromText
, ToText
, ToByteString
, FromXML
, ToXML
, ToQuery
, ToLog
)
instance Hashable ETag
instance NFData ETag
newtype ObjectVersionId = ObjectVersionId Text
deriving
( Eq
, Ord
, Read
, Show
, Data
, Typeable
, Generic
, IsString
, FromText
, ToText
, ToByteString
, FromXML
, ToXML
, ToQuery
, ToLog
)
instance Hashable ObjectVersionId
instance NFData ObjectVersionId
newtype LocationConstraint = LocationConstraint { constraintRegion :: Region }
deriving
( Eq
, Ord
, Read
, Show
, Data
, Typeable
, Generic
, ToText
, ToByteString
, ToLog
)
_LocationConstraint :: Iso' LocationConstraint Region
_LocationConstraint = iso constraintRegion LocationConstraint
instance Hashable LocationConstraint
instance NFData LocationConstraint
instance FromText LocationConstraint where
parser = LocationConstraint <$> (parser <|> go)
where
go = takeLowerText >>= \case
"" -> pure NorthVirginia
"eu" -> pure Ireland
e -> fromTextError $
"Failure parsing LocationConstraint from " <> e
instance FromXML LocationConstraint where
parseXML = \case
[] -> pure (LocationConstraint NorthVirginia)
ns -> parseXMLText "LocationConstraint" ns
instance ToXML LocationConstraint where
toXML = \case
LocationConstraint NorthVirginia -> XNull
LocationConstraint r -> toXMLText r
newtype ObjectKey = ObjectKey Text
deriving
( Eq
, Ord
, Read
, Show
, Data
, Typeable
, Generic
, IsString
, FromText
, ToText
, ToByteString
, FromXML
, ToXML
, ToQuery
, ToPath
, ToLog
)
instance Hashable ObjectKey
instance NFData ObjectKey
type Delimiter = Char
_ObjectKey :: Iso' ObjectKey Text
_ObjectKey = iso (\(ObjectKey k) -> k) ObjectKey
{-# INLINE _ObjectKey #-}
keyPrefix :: Delimiter -> Traversal' ObjectKey Text
keyPrefix c = _ObjectKeySnoc True c . _1
{-# INLINE keyPrefix #-}
keyName :: Delimiter -> Traversal' ObjectKey Text
keyName c = _ObjectKeySnoc False c . _2
{-# INLINE keyName #-}
keyComponents :: Delimiter -> IndexedTraversal' Int ObjectKey Text
keyComponents !c f (ObjectKey k) = cat <$> traversed f split
where
split = Text.split (== c) k
cat = ObjectKey . Text.intercalate (Text.singleton c)
{-# INLINE keyComponents #-}
_ObjectKeySnoc :: Bool -> Delimiter -> Prism' ObjectKey (Text, Text)
_ObjectKeySnoc dir !c = prism (ObjectKey . uncurry cat) split
where
split x@(ObjectKey k) =
let (h, t) = Text.breakOnEnd suf k
in if | Text.length h <= 1, dir -> Left x
| otherwise -> Right (Text.dropEnd 1 h, t)
cat h t
| Text.null h = t
| Text.null t = h
| suf `Text.isSuffixOf` h = h <> t
| suf `Text.isPrefixOf` t = h <> t
| otherwise = h <> suf <> t
suf = Text.singleton c
getWebsiteEndpoint :: Region -> Text
getWebsiteEndpoint reg = "s3-website-" <> toText reg <> ".amazonaws.com"