s3-signer: Pre-signed Amazon S3 URLs

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

s3-signer creates cryptographically secure Amazon S3 URLs that expire within a user-defined period. It allows uploading and downloading of content from Amazon S3. Ideal for AJAX direct-to-s3 uploads via CORS and secure downloads. Web framework agnostic with minimal dependencies.

module Main where
import           Network.S3
main :: IO ()
main = print =<< generateS3URL credentials request
  where
    credentials = S3Keys "<public-key-goes-here>" "<secret-key-goes-here>"
    request     = S3Request S3GET "application/extension" "bucket-name" "file-name.extension" 3 -- three seconds until expiration

Result

S3URL "https://bucket-name.s3.amazonaws.com/file-name.extension?AWSAccessKeyId=<public-key-goes-here>&Expires=1402346638&Signature=1XraY%2Bhp117I5CTKNKPc6%2BiihRA%3D"

[Skip to Readme]

Properties

Versions 0.1.0.0, 0.2.0.0, 0.3.0.0, 0.4.0.0, 0.4.0.0, 0.5.0.0
Change log None available
Dependencies base (>=4 && <5), base64-bytestring, blaze-builder (>=0.4), byteable, bytestring, case-insensitive (>=1.2), cryptohash, http-types, time, utf8-string [details]
License BSD-3-Clause
Copyright David Johnson (c) 2014-2018
Author David Johnson <djohnson.m@gmail.com>, William Casarin <jb55@jb55.com>
Maintainer David Johnson <djohnson.m@gmail.com>
Category AWS, Network
Home page https://github.com/dmjio/s3-signer
Bug tracker https://github.com/dmjio/s3-signer/issues
Source repo head: git clone https://github.com/dmjio/s3-signer
Uploaded by DavidJohnson at 2018-03-26T22:25:05Z

Modules

[Index]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for s3-signer-0.4.0.0

[back to package description]

s3-signer

Hackage Hackage Dependencies Haskell Programming Language BSD3 License Build Status

s3-signer is intended to be an aid in building secure cloud-based services with AWS. This library generates cryptographically secure URLs that expire at a user-defined interval. These URLs can be used to offload the process of uploading and downloading large files, freeing your webserver to focus on other things.

Features

Documentation

S3 Query String Request Authentication

Implementation

AWS Specification

Signature = URL-Encode( Base64( HMAC-SHA1( YourSecretAccessKeyID,UTF-8-Encoding-Of( StringToSign ) ) ) );

Haskell Implementation

module Network.S3.Sign  ( sign ) where

import           Crypto.Hash.SHA1       (hash)
import           Crypto.MAC.HMAC        (hmac)
import qualified Data.ByteString.Base64 as B64
import           Data.ByteString.UTF8   (ByteString)
import           Network.HTTP.Types.URI (urlEncode)

-- | HMAC-SHA1 Encrypted Signature
sign :: ByteString -> ByteString -> ByteString
sign secretKey url = urlEncode True . B64.encode $ hmac hash 64 secretKey url

Use Case

{-# LANGUAGE OverloadedStrings #-}

module Main where

import           Network.S3

main :: IO ()
main = print =<< generateS3URL credentials request
  where
     credentials = S3Keys "<public-key-goes-here>" "<secret-key-goes-here>"
     request     = S3Request S3GET "application/zip" "bucket-name" "file-name.extension" 3 -- 3 secs until expired

Result

S3URL {
      signedRequest =
         "https://bucket-name.s3.amazonaws.com/file-name.extension?AWSAccessKeyId=<public-key-goes-here>&Expires=1402346638&Signature=1XraY%2Bhp117I5CTKNKPc6%2BiihRA%3D"
     }

Snap integration - Downloads

-- Quick and dirty example
type FileID = ByteString

makeS3URL :: FileID -> IO S3URL
makeS3URL fileId = generateS3URL credentials request
  where
    credentials = S3Keys "<public-key-goes-here>" "<secret-key-goes-here>"
    request     = S3Request S3GET "application/zip" "bucket-name" (fileId <> ".zip") 3 

downloadFile :: Handler App (AuthManager App) ()
downloadFile = method POST $ currentUserId >>= maybe the404 handleDownload
  where handleDownload uid = do
          Just fileId <- getParam "fileId"
          -- Ensure file being requested belongs to user else 403...
          S3URL url <- liftIO $ makeS3URL fileId
          redirect' url 302

Direct to S3 AJAX Uploads

<?xml version="1.0" encoding="UTF-8"?>
<CORSConfiguration xmlns="http://s3.amazonaws.com/doc/2006-03-01/">
    <CORSRule>
        <AllowedOrigin>https://my-url-goes-here.com</AllowedOrigin>
        <AllowedMethod>PUT</AllowedMethod>
        <AllowedHeader>*</AllowedHeader>
    </CORSRule>
</CORSConfiguration>
type FileID = ByteString

makeS3URL :: FileID -> IO S3URL
makeS3URL fileId = generateS3URL credentials request
  where
    credentials = S3Keys "<public-key-goes-here>" "<secret-key-goes-here>"
    request     = S3Request S3PUT "application/zip" "bucket-name" (fileId <> ".zip") 3 

getUploadURL :: Handler App (AuthManager App) ()
getUploadURL = method POST $ currentUserId >>= maybe the404 handleDownload
  where handleDownload _ = do
          Just fileId <- getParam "fileId"
          writeJSON =<< Data.Text.Encoding.decodeUtf8 <$> liftIO (makeS3URL fileId)
var xhr = new XMLHttpRequest();
xhr.open('PUT', url /* S3-URL generated from server */);
xhr.setRequestHeader('Content-Type', 'application/zip'); /* whatever http-content-type makes sense */
xhr.setRequestHeader('x-amz-acl', 'public-read');

/* upload completion check */
xhr.onreadystatechange = function(e) {
    if (this.readyState === 4 && this.status === 200) 
          console.log('upload complete');
};

/* Amazon gives you progress information on AJAX Uploads */
xhr.upload.addEventListener("progress", function(evt) {
       if (evt.lengthComputable) {
          var v = (evt.loaded / evt.total) * 100,
          val = Math.round(v) + '%',
          console.log('Completed: ' + val);
      }
}, false);

/* error handling */
xhr.upload.addEventListener("error", function(evt) {
   console.log("There has been an error :(");
}, false);

/* Commence upload */
xhr.send(file); // file here is a blob from the file reader API

File Reader Info

How to read file data from the browser

Troubleshoooting

FAQ

This attack builds on previous attacks on SHA-0 and SHA-1, and is a major, major cryptanalytic result. It pretty much puts a bullet into SHA-1 as a hash function for digital signatures (although it doesn't affect applications such as HMAC where collisions aren't important).