aws-cloudfront-signed-cookies-0.2.0.8: Generate signed cookies for AWS CloudFront
Safe HaskellNone
LanguageHaskell2010

Network.AWS.CloudFront.SignedCookies.Types

Synopsis

Policy

data Policy Source #

A policy specifies what resource is being granted, for what time period, and to what IP addresses.

For AWS's documentation on what going into a CloudFront policy statement, see Values That You Specify in the Policy Statement for a Custom Policy for Signed Cookies.

Constructors

Policy 

Fields

Instances

Instances details
Eq Policy Source # 
Instance details

Defined in Network.AWS.CloudFront.SignedCookies.Types

Methods

(==) :: Policy -> Policy -> Bool #

(/=) :: Policy -> Policy -> Bool #

Show Policy Source # 
Instance details

Defined in Network.AWS.CloudFront.SignedCookies.Types

newtype Resource Source #

URL that a policy will grant access to, optionally containing asterisks for wildcards.

Examples:

  • "https://d123example.cloudfront.net/index.html"
  • "https://d123example.cloudfront.net/*.jpeg"

Constructors

Resource Text 

Instances

Instances details
Eq Resource Source # 
Instance details

Defined in Network.AWS.CloudFront.SignedCookies.Types

Show Resource Source # 
Instance details

Defined in Network.AWS.CloudFront.SignedCookies.Types

Crypto

newtype PemFilePath Source #

Location in the filesystem where a .pem file containing an RSA secret key can be found.

The filename downloaded from AWS looks like this:

  • "pk-APKAIATXN3RCIOVT5WRQ.pem"

Constructors

PemFilePath Text 

newtype KeyPairId Source #

CloudFront key pair ID for the key pair that you are using to generate signature.

The key pair ID can be found in the name of key files that you download, and looks like this:

  • APKAIATXN3RCIOVT5WRQ

Constructors

KeyPairId Text 

Instances

Instances details
Eq KeyPairId Source # 
Instance details

Defined in Network.AWS.CloudFront.SignedCookies.Types

Show KeyPairId Source # 
Instance details

Defined in Network.AWS.CloudFront.SignedCookies.Types

Cookies

type CookiesText = [(Text, Text)] #

Textual cookies. Functions assume UTF8 encoding.

data SetCookie #

Data type representing the key-value pair to use for a cookie, as well as configuration options for it.

Creating a SetCookie

SetCookie does not export a constructor; instead, use defaultSetCookie and override values (see http://www.yesodweb.com/book/settings-types for details):

import Web.Cookie
:set -XOverloadedStrings
let cookie = defaultSetCookie { setCookieName = "cookieName", setCookieValue = "cookieValue" }

Cookie Configuration

Cookies have several configuration options; a brief summary of each option is given below. For more information, see RFC 6265 or Wikipedia.

Instances

Instances details
Eq SetCookie 
Instance details

Defined in Web.Cookie

Show SetCookie 
Instance details

Defined in Web.Cookie

NFData SetCookie 
Instance details

Defined in Web.Cookie

Methods

rnf :: SetCookie -> () #

Default SetCookie
def = defaultSetCookie
Instance details

Defined in Web.Cookie

Methods

def :: SetCookie #

newtype CookieDomain Source #

Examples:

  • "d123example.cloudfront.net"
  • "cloudfrontalias.example.com"

Constructors

CookieDomain Text 

newtype CookiePath Source #

Usually "/"

Constructors

CookiePath Text 

newtype PolicyCookie Source #

The value of a CloudFront-Policy cookie.

Constructors

PolicyCookie Text 

newtype SignatureCookie Source #

The value of a CloudFront-Signature cookie.

Constructors

SignatureCookie Text 

Time

data NominalDiffTime #

This is a length of time, as measured by UTC. It has a precision of 10^-12 s.

Conversion functions will treat it as seconds. For example, (0.010 :: NominalDiffTime) corresponds to 10 milliseconds.

It ignores leap-seconds, so it's not necessarily a fixed amount of clock time. For instance, 23:00 UTC + 2 hours of NominalDiffTime = 01:00 UTC (+ 1 day), regardless of whether a leap-second intervened.

Instances

Instances details
Enum NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Eq NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Fractional NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Data NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NominalDiffTime -> c NominalDiffTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NominalDiffTime #

toConstr :: NominalDiffTime -> Constr #

dataTypeOf :: NominalDiffTime -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NominalDiffTime) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NominalDiffTime) #

gmapT :: (forall b. Data b => b -> b) -> NominalDiffTime -> NominalDiffTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NominalDiffTime -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NominalDiffTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> NominalDiffTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NominalDiffTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NominalDiffTime -> m NominalDiffTime #

Num NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Ord NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Real NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

RealFrac NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Show NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

ToJSON NominalDiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON NominalDiffTime

This instance includes a bounds check to prevent maliciously large inputs to fill up the memory of the target system. You can newtype Scientific and provide your own instance using withScientific if you want to allow larger inputs.

Instance details

Defined in Data.Aeson.Types.FromJSON

NFData NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Methods

rnf :: NominalDiffTime -> () #

type POSIXTime = NominalDiffTime #

POSIX time is the nominal time since 1970-01-01 00:00 UTC

To convert from a CTime or System.Posix.EpochTime, use realToFrac.

newtype Lifespan Source #

How long from now the credentials expire

Instances

Instances details
Eq Lifespan Source # 
Instance details

Defined in Network.AWS.CloudFront.SignedCookies.Types

Show Lifespan Source # 
Instance details

Defined in Network.AWS.CloudFront.SignedCookies.Types

data StartTime Source #

The time at which credentials begin to take effect

Instances

Instances details
Eq StartTime Source # 
Instance details

Defined in Network.AWS.CloudFront.SignedCookies.Types

Show StartTime Source # 
Instance details

Defined in Network.AWS.CloudFront.SignedCookies.Types

newtype EndTime Source #

The time at which credentials expire

Constructors

EndTime POSIXTime 

Instances

Instances details
Eq EndTime Source # 
Instance details

Defined in Network.AWS.CloudFront.SignedCookies.Types

Methods

(==) :: EndTime -> EndTime -> Bool #

(/=) :: EndTime -> EndTime -> Bool #

Show EndTime Source # 
Instance details

Defined in Network.AWS.CloudFront.SignedCookies.Types

IP address

data IpAddress Source #

The IP address or address range of clients allowed to make requests

Constructors

AnyIp 
IpAddress Text 

Instances

Instances details
Eq IpAddress Source # 
Instance details

Defined in Network.AWS.CloudFront.SignedCookies.Types

Show IpAddress Source # 
Instance details

Defined in Network.AWS.CloudFront.SignedCookies.Types

Strings

data Text #

A space efficient, packed, unboxed Unicode text type.

Instances

Instances details
Hashable Text 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

KeyValue Object

Constructs a singleton HashMap. For calling functions that demand an Object for constructing objects. To be used in conjunction with mconcat. Prefer to use object where possible.

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Text -> v -> Object #

KeyValue Pair 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Text -> v -> Pair #

ToJSONKey Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

Chunk Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem Text #

Ixed Text 
Instance details

Defined in Control.Lens.At

AsNumber Text 
Instance details

Defined in Data.Aeson.Lens

AsPrimitive Text 
Instance details

Defined in Data.Aeson.Lens

AsValue Text 
Instance details

Defined in Data.Aeson.Lens

AsJSON Text 
Instance details

Defined in Data.Aeson.Lens

Methods

_JSON :: (FromJSON a, ToJSON b) => Prism Text Text a b #

FromPairs Value (DList Pair) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

fromPairs :: DList Pair -> Value

v ~ Value => KeyValuePair v (DList Pair) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

pair :: String -> v -> DList Pair

type State Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State Text = Buffer
type ChunkElem Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

type Item Text 
Instance details

Defined in Data.Text

type Item Text = Char
type Index Text 
Instance details

Defined in Control.Lens.At

type Index Text = Int
type IxValue Text 
Instance details

Defined in Control.Lens.At

data ByteString #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Char8 it can be interpreted as containing 8-bit characters.

Instances

Instances details
Eq ByteString 
Instance details

Defined in Data.ByteString.Internal

Data ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString #

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) #

gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

Ord ByteString 
Instance details

Defined in Data.ByteString.Internal

Read ByteString 
Instance details

Defined in Data.ByteString.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Internal

IsString ByteString 
Instance details

Defined in Data.ByteString.Internal

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal

Hashable ByteString 
Instance details

Defined in Data.Hashable.Class

Chunk ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem ByteString #

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

rnf :: ByteString -> () #

Ixed ByteString 
Instance details

Defined in Control.Lens.At

AsNumber ByteString 
Instance details

Defined in Data.Aeson.Lens

AsPrimitive ByteString 
Instance details

Defined in Data.Aeson.Lens

AsValue ByteString 
Instance details

Defined in Data.Aeson.Lens

AsJSON ByteString 
Instance details

Defined in Data.Aeson.Lens

Methods

_JSON :: (FromJSON a, ToJSON b) => Prism ByteString ByteString a b #

type State ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State ByteString = Buffer
type ChunkElem ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

type Index ByteString 
Instance details

Defined in Control.Lens.At

type IxValue ByteString 
Instance details

Defined in Control.Lens.At

Crypto

data PrivateKey #

Represent a RSA private key.

Only the pub, d fields are mandatory to fill.

p, q, dP, dQ, qinv are by-product during RSA generation, but are useful to record here to speed up massively the decrypt and sign operation.

implementations can leave optional fields to 0.

Instances

Instances details
Eq PrivateKey 
Instance details

Defined in Crypto.PubKey.RSA.Types

Data PrivateKey 
Instance details

Defined in Crypto.PubKey.RSA.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrivateKey -> c PrivateKey #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrivateKey #

toConstr :: PrivateKey -> Constr #

dataTypeOf :: PrivateKey -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrivateKey) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrivateKey) #

gmapT :: (forall b. Data b => b -> b) -> PrivateKey -> PrivateKey #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrivateKey -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrivateKey -> r #

gmapQ :: (forall d. Data d => d -> u) -> PrivateKey -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrivateKey -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey #

Read PrivateKey 
Instance details

Defined in Crypto.PubKey.RSA.Types

Show PrivateKey 
Instance details

Defined in Crypto.PubKey.RSA.Types

NFData PrivateKey 
Instance details

Defined in Crypto.PubKey.RSA.Types

Methods

rnf :: PrivateKey -> () #