aws-arn-0.3.1.0: Types and optics for manipulating Amazon Resource Names (ARNs)
Copyright(C) 2020-2022 Bellroy Pty Ltd
LicenseBSD-3-Clause
MaintainerBellroy Tech Team <haskell@bellroy.com>
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010
Extensions
  • TemplateHaskell
  • TemplateHaskellQuotes
  • OverloadedStrings
  • StandaloneDeriving
  • 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:

{-# LANGUAGE OverloadedLabels #-}
-- This provides the necessary instances from generic-lens
import Data.Generics.Labels ()

-- 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 . #resource . slashes) (\parts -> take 2 parts ++ ["*"]) authorizerSampleARN
Synopsis

Documentation

data ARN r Source #

A parsed ARN. Either use the _ARN Prism', or the parseARN and renderARN functions to convert Text <-> ARN. The resource 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 optics in this module can pick apart the resource field.

If you want lenses into individual fields, use the generic-lens or generic-optics libraries.

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 . #resource . Lambda._Function . #name

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)

Since: 0.1.0.0

Constructors

ARN 

Fields

Instances

Instances details
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 #

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 #

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) #

Functor ARN Source # 
Instance details

Defined in Network.AWS.ARN

Methods

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

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

Hashable1 ARN Source # 
Instance details

Defined in Network.AWS.ARN

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> ARN a -> 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 #

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 #

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 #

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 #

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

Defined in Network.AWS.ARN

Methods

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

hash :: ARN r -> Int #

type Rep1 ARN Source # 
Instance details

Defined in Network.AWS.ARN

type Rep (ARN r) Source # 
Instance details

Defined in Network.AWS.ARN

parseARN :: Text -> Maybe (ARN Text) Source #

Since: 0.2.0.0

renderARN :: ARN Text -> Text Source #

Since: 0.2.0.0

ARN Prism

_ARN :: Prism' Text (ARN Text) Source #

Since: 0.1.0.0

Utility Optics

colons :: Iso' Text [Text] Source #

Split a Text into colon-separated parts.

This is an improper Iso' (Text.intercalate ":" . Text.splitOn ":" = id, but Text.splitOn ":" . Text.intercalate ":" /= id). This causes violations of the Iso' laws for lists whose members contain ':':

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

The laws are also violated on empty lists:

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

Nevertheless, it is still useful:

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

Ed discusses improper optics in an old Reddit comment.

Since: 0.3.0.0

slashes :: Iso' Text [Text] Source #

Split a Text into slash-separated parts.

List colons, this is an improper Iso', but it is still useful:

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

Since: 0.3.0.0