Copyright | (C) 2020-2022 Bellroy Pty Ltd |
---|---|
License | BSD-3-Clause |
Maintainer | Bellroy Tech Team <haskell@bellroy.com> |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Extensions |
|
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
Documentation
A parsed ARN. Either use the _ARN
Prism'
, or the parseARN
and
renderARN
functions to convert
. The
Text
<-> ARN
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
Instances
ARN Prism
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