-- SPDX-FileCopyrightText: 2021 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA -- | Parsers that are used in "Morley.Client.TezosClient.Impl" module Morley.Client.TezosClient.Parser ( parseBakerFeeFromOutput , parseSecretKeyEncryption ) where import Data.Scientific (Scientific) import Fmt (Buildable(..)) import Text.Megaparsec (choice, customFailure) import Text.Megaparsec qualified as P (Parsec, parse, skipManyTill) import Text.Megaparsec.Char (newline, printChar, space) import Text.Megaparsec.Char.Lexer (lexeme, scientific, symbol) import Text.Megaparsec.Error (ParseErrorBundle, ShowErrorComponent(..), errorBundlePretty) import Morley.Client.TezosClient.Types (SecretKeyEncryption(..)) import Morley.Micheline import Morley.Michelson.Parser.Helpers (count) import Morley.Tezos.Core import Morley.Util.SizedList.Types import Unsafe qualified (unsafeM) type Parser = P.Parsec Void Text data FeeParserException = FeeParserException (ParseErrorBundle Text Void) deriving stock (Eq, Show) instance Exception FeeParserException where displayException (FeeParserException bundle) = errorBundlePretty bundle instance Buildable FeeParserException where build = build . displayException -- this might seem backwards, but it's more efficient than converting to then from text -- which would have to happen in displayException if we define it in terms of build. data SecretKeyEncryptionParserException = SecretKeyEncryptionParserException (ParseErrorBundle Text UnexpectedEncryptionType) deriving stock (Eq, Show) instance Buildable SecretKeyEncryptionParserException where build (SecretKeyEncryptionParserException bundle) = build $ errorBundlePretty bundle data UnexpectedEncryptionType = UnexpectedEncryptionType deriving stock (Eq, Ord, Show) instance ShowErrorComponent UnexpectedEncryptionType where showErrorComponent UnexpectedEncryptionType = "Unexpected secret key encryption type occurred" -- | Function to parse baker fee from given @octez-client@ output. parseBakerFeeFromOutput :: forall n. (SingIPeano n) => Text -> Either FeeParserException (SizedList n TezosMutez) parseBakerFeeFromOutput output = first FeeParserException $ P.parse (count @n bakerFeeParser) "" output where bakerFeeParser :: Parser TezosMutez bakerFeeParser = do num <- P.skipManyTill (printChar <|> newline) $ do void $ symbol space "Fee to the baker: " P.skipManyTill printChar $ lexeme (newline >> pass) scientific Unsafe.unsafeM $ scientificToMutez num scientificToMutez :: Scientific -> Either Text TezosMutez scientificToMutez x = fmap TezosMutez $ mkMutez @Word64 $ floor $ x * 1e6 parseSecretKeyEncryption :: Text -> Either SecretKeyEncryptionParserException SecretKeyEncryption parseSecretKeyEncryption output = first SecretKeyEncryptionParserException $ P.parse secretKeyEncryptionParser "" output where secretKeyEncryptionParser :: P.Parsec UnexpectedEncryptionType Text SecretKeyEncryption secretKeyEncryptionParser = do P.skipManyTill (printChar <|> newline) $ do symbol space "Secret Key: " >> choice [ symbol space "unencrypted" >> pure UnencryptedKey , symbol space "encrypted" >> pure EncryptedKey , symbol space "ledger" >> pure LedgerKey , customFailure UnexpectedEncryptionType ]