module Network.AWS.CloudFront.SignedCookies.CLI.Decode
  ( main, mainOpts, Opts (..), optsParser, mainParserInfo
  ) where
import Network.AWS.CloudFront.SignedCookies.CLI.Internal (text)
import Network.AWS.CloudFront.SignedCookies.Encoding (base64Decode)
import Network.AWS.CloudFront.SignedCookies.Types (PolicyCookie (..), Text)
import qualified Data.Aeson as A
import Data.Aeson.Encode.Pretty (encodePrettyToTextBuilder)
import Data.Coerce (coerce)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LBS
import qualified Options.Applicative as Opt
import qualified Data.Text.Lazy as LText
import Data.Text.Lazy.Builder as Text (toLazyText)
import qualified Data.Text.Lazy.IO as LText
main :: IO ()
main :: IO ()
main = do
  Opts
opts <- ParserInfo Opts -> IO Opts
forall a. ParserInfo a -> IO a
Opt.execParser (ParserInfo Opts -> IO Opts) -> ParserInfo Opts -> IO Opts
forall a b. (a -> b) -> a -> b
$ Parser Opts -> InfoMod Opts -> ParserInfo Opts
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info (Parser (Opts -> Opts)
forall a. Parser (a -> a)
Opt.helper Parser (Opts -> Opts) -> Parser Opts -> Parser Opts
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Opts
optsParser) InfoMod Opts
forall a. InfoMod a
infoMod
  Opts -> IO ()
mainOpts Opts
opts
mainOpts :: Opts -> IO ()
mainOpts :: Opts -> IO ()
mainOpts Opts{PolicyCookie
opt_policyCookie :: PolicyCookie
opt_policyCookie :: Opts -> PolicyCookie
..} = do
  ByteString
bs :: BS.ByteString <-
    case Text -> Either String ByteString
base64Decode (Text -> Either String ByteString)
-> Text -> Either String ByteString
forall a b. (a -> b) -> a -> b
$ forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @PolicyCookie @Text PolicyCookie
opt_policyCookie of
      Left String
e  -> String -> IO ByteString
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
e
      Right ByteString
x -> ByteString -> IO ByteString
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
x
  Value
value <-
    case ByteString -> Either String Value
forall a. FromJSON a => ByteString -> Either String a
A.eitherDecode' (ByteString -> ByteString
LBS.fromStrict ByteString
bs) of
      Left String
e  -> String -> IO Value
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
e
      Right Value
x -> Value -> IO Value
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value
x
  let
    Text
result :: LText.Text =
      Builder -> Text
Text.toLazyText (Builder -> Text) -> Builder -> Text
forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Builder
encodePrettyToTextBuilder @A.Value Value
value
  
  Text -> IO ()
LText.putStr Text
result
data Opts =
  Opts
    { Opts -> PolicyCookie
opt_policyCookie :: PolicyCookie
        
    }
optsParser :: Opt.Parser Opts
optsParser :: Parser Opts
optsParser =
  PolicyCookie -> Opts
Opts
    (PolicyCookie -> Opts) -> Parser PolicyCookie -> Parser Opts
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> String -> Parser PolicyCookie
forall a. Coercible Text a => String -> String -> Parser a
text String
"policy-cookie" String
"The value of a CloudFront-Policy cookie"
mainParserInfo :: Opt.ParserInfo (IO ())
mainParserInfo :: ParserInfo (IO ())
mainParserInfo =
  Opts -> IO ()
mainOpts (Opts -> IO ()) -> ParserInfo Opts -> ParserInfo (IO ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Opts -> InfoMod Opts -> ParserInfo Opts
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info Parser Opts
optsParser InfoMod Opts
forall a. InfoMod a
infoMod
infoMod :: Opt.InfoMod a
infoMod :: forall a. InfoMod a
infoMod =
  String -> InfoMod a
forall a. String -> InfoMod a
Opt.header String
"Decode signed AWS CloudFront policy cookies"