aws-arn-0.1.0.0: Types and optics for manipulating Amazon Resource Names (ARNs)
Copyright(C) 2020-2021 Bellroy Pty Ltd
LicenseBSD-3-Clause
MaintainerBellroy Tech Team <haskell@bellroy.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010
Extensions
  • TemplateHaskell
  • TemplateHaskellQuotes
  • OverloadedStrings
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • DeriveGeneric
  • DeriveAnyClass
  • RankNTypes
  • ExplicitForAll

Network.AWS.ARN

Description

Provides a type representing Amazon Resource Names (ARNs), and parsing/unparsing functions for them. The provided optics make it very convenient to rewrite parts of ARNs.

Example

API Gateway Lambda Authorizers are given the ARN of the requested endpoint and method, and are expected to respond with an IAM Policy Document. It is sometimes useful to manipulate the given ARN when describing which resources to authorize.

Here, we generalize authorizerSampleARN to cover every method of every endpoint in the stage:

-- Returns "arn:aws:execute-api:us-east-1:123456789012:my-spiffy-api/stage/*"
let
  authorizerSampleARN = "arn:aws:execute-api:us-east-1:123456789012:my-spiffy-api/stage/GET/some/deep/path"
in
  over (_ARN . arnResource . slashes) (\parts -> take 2 parts ++ ["*"]) authorizerSampleARN
Synopsis

Documentation

data ARN r Source #

A parsed ARN. Either use the _ARN Prism', or the toARN and fromARN functions to convert Text <-> ARN. The _arnResource part of an ARN will often contain colon- or slash-separated parts which precisely identify some resource. If there is no service-specific module (see below), the colons and slashes Iso's in this module can pick apart the _arnResource field.

Service-Specific Modules

Modules like Network.AWS.ARN.Lambda provide types to parse the resource part of an ARN into something more specific:

-- Remark: Lambda._Function :: Prism' Text Lambda.Function
-- Returns: Just "the-coolest-function-ever"
let
  functionARN = "arn:aws:lambda:us-east-1:123456789012:function:the-coolest-function-ever:Alias"
in
  functionARN ^? _ARN . arnResource . Lambda._Function . Lambda.fName

You can also use ARN's Traversable instance and below to create Prism's that indicate their resource type in ARN's type variable:

_ARN . below Lambda._Function :: Prism' Text (ARN Lambda.Function)

Constructors

ARN 

Instances

Instances details
Functor ARN Source # 
Instance details

Defined in Network.AWS.ARN

Methods

fmap :: (a -> b) -> ARN a -> ARN b #

(<$) :: a -> ARN b -> ARN a #

Foldable ARN Source # 
Instance details

Defined in Network.AWS.ARN

Methods

fold :: Monoid m => ARN m -> m #

foldMap :: Monoid m => (a -> m) -> ARN a -> m #

foldMap' :: Monoid m => (a -> m) -> ARN a -> m #

foldr :: (a -> b -> b) -> b -> ARN a -> b #

foldr' :: (a -> b -> b) -> b -> ARN a -> b #

foldl :: (b -> a -> b) -> b -> ARN a -> b #

foldl' :: (b -> a -> b) -> b -> ARN a -> b #

foldr1 :: (a -> a -> a) -> ARN a -> a #

foldl1 :: (a -> a -> a) -> ARN a -> a #

toList :: ARN a -> [a] #

null :: ARN a -> Bool #

length :: ARN a -> Int #

elem :: Eq a => a -> ARN a -> Bool #

maximum :: Ord a => ARN a -> a #

minimum :: Ord a => ARN a -> a #

sum :: Num a => ARN a -> a #

product :: Num a => ARN a -> a #

Traversable ARN Source # 
Instance details

Defined in Network.AWS.ARN

Methods

traverse :: Applicative f => (a -> f b) -> ARN a -> f (ARN b) #

sequenceA :: Applicative f => ARN (f a) -> f (ARN a) #

mapM :: Monad m => (a -> m b) -> ARN a -> m (ARN b) #

sequence :: Monad m => ARN (m a) -> m (ARN a) #

Eq1 ARN Source # 
Instance details

Defined in Network.AWS.ARN

Methods

liftEq :: (a -> b -> Bool) -> ARN a -> ARN b -> Bool #

Ord1 ARN Source # 
Instance details

Defined in Network.AWS.ARN

Methods

liftCompare :: (a -> b -> Ordering) -> ARN a -> ARN b -> Ordering #

Show1 ARN Source # 
Instance details

Defined in Network.AWS.ARN

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ARN a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ARN a] -> ShowS #

Hashable1 ARN Source # 
Instance details

Defined in Network.AWS.ARN

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> ARN a -> Int #

Eq r => Eq (ARN r) Source # 
Instance details

Defined in Network.AWS.ARN

Methods

(==) :: ARN r -> ARN r -> Bool #

(/=) :: ARN r -> ARN r -> Bool #

Ord r => Ord (ARN r) Source # 
Instance details

Defined in Network.AWS.ARN

Methods

compare :: ARN r -> ARN r -> Ordering #

(<) :: ARN r -> ARN r -> Bool #

(<=) :: ARN r -> ARN r -> Bool #

(>) :: ARN r -> ARN r -> Bool #

(>=) :: ARN r -> ARN r -> Bool #

max :: ARN r -> ARN r -> ARN r #

min :: ARN r -> ARN r -> ARN r #

Show r => Show (ARN r) Source # 
Instance details

Defined in Network.AWS.ARN

Methods

showsPrec :: Int -> ARN r -> ShowS #

show :: ARN r -> String #

showList :: [ARN r] -> ShowS #

Generic (ARN r) Source # 
Instance details

Defined in Network.AWS.ARN

Associated Types

type Rep (ARN r) :: Type -> Type #

Methods

from :: ARN r -> Rep (ARN r) x #

to :: Rep (ARN r) x -> ARN r #

Hashable r => Hashable (ARN r) Source # 
Instance details

Defined in Network.AWS.ARN

Methods

hashWithSalt :: Int -> ARN r -> Int #

hash :: ARN r -> Int #

Generic1 ARN Source # 
Instance details

Defined in Network.AWS.ARN

Associated Types

type Rep1 ARN :: k -> Type #

Methods

from1 :: forall (a :: k). ARN a -> Rep1 ARN a #

to1 :: forall (a :: k). Rep1 ARN a -> ARN a #

type Rep (ARN r) Source # 
Instance details

Defined in Network.AWS.ARN

type Rep1 ARN Source # 
Instance details

Defined in Network.AWS.ARN

ARN Optics

arnPartition :: forall r. Lens' (ARN r) Text Source #

arnService :: forall r. Lens' (ARN r) Text Source #

arnRegion :: forall r. Lens' (ARN r) Text Source #

arnAccount :: forall r. Lens' (ARN r) Text Source #

arnResource :: forall r r. Lens (ARN r) (ARN r) r r Source #

Utility Optics

colons :: Iso' Text [Text] Source #

Split a Text into colon-separated parts.

This is not truly a lawful Iso', but it is useful. The Iso' laws are violated for lists whose members contain ::

>>> [":"] ^. from colons . colons
["",""]

The laws are also violated on empty lists:

>>> [] ^. from colons . colons
[""]

However, it is still a useful tool:

>>> "foo:bar:baz" & colons . ix 1 .~ "quux"
"foo:quux:baz"

slashes :: Iso' Text [Text] Source #

Split a Text into slash-separated parts.

This is not truly a lawful Iso', but it is useful:

>>> "foo/bar/baz" ^. slashes
["foo","bar","baz"]

Similar caveats to colons apply here.