Skip to content

Commit

Permalink
restructure modules
Browse files Browse the repository at this point in the history
  • Loading branch information
nitinprakash96 committed Aug 4, 2024
1 parent 78bdf69 commit c0bea6a
Show file tree
Hide file tree
Showing 7 changed files with 45 additions and 12 deletions.
13 changes: 7 additions & 6 deletions azure-blob-storage/azure-blob-storage.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -51,12 +51,13 @@ common common-options

library
import: common-options
exposed-modules: Azure.Blob.Types
Azure.GetBlob
Azure.DeleteBlob
Azure.PutBlob
Azure.UserDelegationKey
Azure.SharedAccessSignature
exposed-modules: Azure.Blob
Azure.Blob.GetBlob
Azure.Blob.DeleteBlob
Azure.Blob.Types
Azure.Blob.UserDelegationKey
Azure.Blob.PutBlob
Azure.Blob.SharedAccessSignature
build-depends: azure-auth
, aeson
, base64-bytestring
Expand Down
28 changes: 28 additions & 0 deletions azure-blob-storage/src/Azure/Blob.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,28 @@
module Azure.Blob
(
-- ** Variants to fetch a blob object
getBlobObject
, getBlobObjectEither

-- ** Variants to upload a blob to Blob storage
, putBlobObject
, putBlobObjectEither

-- ** Variants for deleting a blob object
, deleteBlobObject
, deleteBlobObjectEither

-- ** Generating a Shared Access Signature URI
, generateSas

-- ** Types for dealing with Blob storage functions
, AccountName (..)
, ContainerName (..)
, BlobName (..)
) where

import Azure.Blob.PutBlob
import Azure.Blob.GetBlob
import Azure.Blob.DeleteBlob
import Azure.Blob.SharedAccessSignature
import Azure.Blob.Types
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}

module Azure.DeleteBlob
module Azure.Blob.DeleteBlob
( deleteBlobObject
, deleteBlobObjectEither
) where
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}

module Azure.GetBlob
module Azure.Blob.GetBlob
( getBlobObject
, getBlobObjectEither
) where
Expand Down Expand Up @@ -74,6 +74,9 @@ type GetBlobApi =
:> Header' '[Required, Strict] "x-ms-version" Text
:> Get '[Blob] ByteString

-- TODO: this is more of a test at the moment.
-- GET endpoint should accept any blob that is available and not just
-- rely on certain mime types
instance Accept Blob where
contentTypes :: Proxy Blob -> NonEmpty MediaType
contentTypes _ =
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}

module Azure.PutBlob
module Azure.Blob.PutBlob
( putBlobObjectEither
, putBlobObject
) where
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}

module Azure.SharedAccessSignature
module Azure.Blob.SharedAccessSignature
( generateSas
) where

Expand All @@ -19,7 +19,7 @@ import Azure.Blob.Types
, sasPermissionsToText
, sasResourceToText
)
import Azure.UserDelegationKey (callGetUserDelegationKeyApi, getUserDelegationKeyApi)
import Azure.Blob.UserDelegationKey (callGetUserDelegationKeyApi, getUserDelegationKeyApi)
import Crypto.Hash.SHA256 (hmac)
import Data.Text (Text)
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
Expand All @@ -36,6 +36,7 @@ import qualified Data.Text as Text
blobStorageResourceUrl :: Text
blobStorageResourceUrl = "https://storage.azure.com/"

-- TODO: We need to add support for empty fields here. Eg: signedAuthorizedUserObjectId
generateSas ::
MonadIO m =>
AccountName ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}

module Azure.UserDelegationKey
module Azure.Blob.UserDelegationKey
( callGetUserDelegationKeyApi
, getUserDelegationKeyApi
) where
Expand Down

0 comments on commit c0bea6a

Please sign in to comment.