{-# LANGUAGE GADTs #-} module Bcc.CLI.Sophie.Run.Address.Info ( runAddressInfo , SophieAddressInfoError(..) ) where import Bcc.Api import Bcc.CLI.Sophie.Parsers (OutputFile (..)) import Bcc.Prelude import Control.Monad.Trans.Except.Extra (left) import Data.Aeson (ToJSON (..), object, (.=)) import Data.Aeson.Encode.Pretty (encodePretty) import qualified Data.ByteString.Lazy.Char8 as LBS newtype SophieAddressInfoError = SophieAddressInvalid Text deriving Int -> SophieAddressInfoError -> ShowS [SophieAddressInfoError] -> ShowS SophieAddressInfoError -> String (Int -> SophieAddressInfoError -> ShowS) -> (SophieAddressInfoError -> String) -> ([SophieAddressInfoError] -> ShowS) -> Show SophieAddressInfoError forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [SophieAddressInfoError] -> ShowS $cshowList :: [SophieAddressInfoError] -> ShowS show :: SophieAddressInfoError -> String $cshow :: SophieAddressInfoError -> String showsPrec :: Int -> SophieAddressInfoError -> ShowS $cshowsPrec :: Int -> SophieAddressInfoError -> ShowS Show instance Error SophieAddressInfoError where displayError :: SophieAddressInfoError -> String displayError (SophieAddressInvalid Text addrTxt) = String "Invalid address: " String -> ShowS forall a. Semigroup a => a -> a -> a <> Text -> String forall a b. (Show a, ConvertText String b) => a -> b show Text addrTxt data AddressInfo = AddressInfo { AddressInfo -> Text aiType :: !Text , AddressInfo -> Text aiEra :: !Text , AddressInfo -> Text aiEncoding :: !Text , AddressInfo -> Text aiAddress :: !Text , AddressInfo -> Text aiBase16 :: !Text } instance ToJSON AddressInfo where toJSON :: AddressInfo -> Value toJSON AddressInfo addrInfo = [Pair] -> Value object [ Text "type" Text -> Text -> Pair forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv .= AddressInfo -> Text aiType AddressInfo addrInfo , Text "era" Text -> Text -> Pair forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv .= AddressInfo -> Text aiEra AddressInfo addrInfo , Text "encoding" Text -> Text -> Pair forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv .= AddressInfo -> Text aiEncoding AddressInfo addrInfo , Text "address" Text -> Text -> Pair forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv .= AddressInfo -> Text aiAddress AddressInfo addrInfo , Text "base16" Text -> Text -> Pair forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv .= AddressInfo -> Text aiBase16 AddressInfo addrInfo ] runAddressInfo :: Text -> Maybe OutputFile -> ExceptT SophieAddressInfoError IO () runAddressInfo :: Text -> Maybe OutputFile -> ExceptT SophieAddressInfoError IO () runAddressInfo Text addrTxt Maybe OutputFile mOutputFp = do AddressInfo addrInfo <- case (AddressAny -> Either AddressAny StakeAddress forall a b. a -> Either a b Left (AddressAny -> Either AddressAny StakeAddress) -> Maybe AddressAny -> Maybe (Either AddressAny StakeAddress) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> AsType AddressAny -> Text -> Maybe AddressAny forall addr. SerialiseAddress addr => AsType addr -> Text -> Maybe addr deserialiseAddress AsType AddressAny AsAddressAny Text addrTxt) Maybe (Either AddressAny StakeAddress) -> Maybe (Either AddressAny StakeAddress) -> Maybe (Either AddressAny StakeAddress) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> (StakeAddress -> Either AddressAny StakeAddress forall a b. b -> Either a b Right (StakeAddress -> Either AddressAny StakeAddress) -> Maybe StakeAddress -> Maybe (Either AddressAny StakeAddress) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> AsType StakeAddress -> Text -> Maybe StakeAddress forall addr. SerialiseAddress addr => AsType addr -> Text -> Maybe addr deserialiseAddress AsType StakeAddress AsStakeAddress Text addrTxt) of Maybe (Either AddressAny StakeAddress) Nothing -> SophieAddressInfoError -> ExceptT SophieAddressInfoError IO AddressInfo forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a left (SophieAddressInfoError -> ExceptT SophieAddressInfoError IO AddressInfo) -> SophieAddressInfoError -> ExceptT SophieAddressInfoError IO AddressInfo forall a b. (a -> b) -> a -> b $ Text -> SophieAddressInfoError SophieAddressInvalid Text addrTxt Just (Left (AddressCole Address ColeAddr payaddr)) -> AddressInfo -> ExceptT SophieAddressInfoError IO AddressInfo forall (f :: * -> *) a. Applicative f => a -> f a pure (AddressInfo -> ExceptT SophieAddressInfoError IO AddressInfo) -> AddressInfo -> ExceptT SophieAddressInfoError IO AddressInfo forall a b. (a -> b) -> a -> b $ AddressInfo :: Text -> Text -> Text -> Text -> Text -> AddressInfo AddressInfo { aiType :: Text aiType = Text "payment" , aiEra :: Text aiEra = Text "cole" , aiEncoding :: Text aiEncoding = Text "base58" , aiAddress :: Text aiAddress = Text addrTxt , aiBase16 :: Text aiBase16 = Address ColeAddr -> Text forall a. SerialiseAsRawBytes a => a -> Text serialiseToRawBytesHexText Address ColeAddr payaddr } Just (Left (AddressSophie Address SophieAddr payaddr)) -> AddressInfo -> ExceptT SophieAddressInfoError IO AddressInfo forall (f :: * -> *) a. Applicative f => a -> f a pure (AddressInfo -> ExceptT SophieAddressInfoError IO AddressInfo) -> AddressInfo -> ExceptT SophieAddressInfoError IO AddressInfo forall a b. (a -> b) -> a -> b $ AddressInfo :: Text -> Text -> Text -> Text -> Text -> AddressInfo AddressInfo { aiType :: Text aiType = Text "payment" , aiEra :: Text aiEra = Text "sophie" , aiEncoding :: Text aiEncoding = Text "bech32" , aiAddress :: Text aiAddress = Text addrTxt , aiBase16 :: Text aiBase16 = Address SophieAddr -> Text forall a. SerialiseAsRawBytes a => a -> Text serialiseToRawBytesHexText Address SophieAddr payaddr } Just (Right StakeAddress addr) -> AddressInfo -> ExceptT SophieAddressInfoError IO AddressInfo forall (f :: * -> *) a. Applicative f => a -> f a pure (AddressInfo -> ExceptT SophieAddressInfoError IO AddressInfo) -> AddressInfo -> ExceptT SophieAddressInfoError IO AddressInfo forall a b. (a -> b) -> a -> b $ AddressInfo :: Text -> Text -> Text -> Text -> Text -> AddressInfo AddressInfo { aiType :: Text aiType = Text "stake" , aiEra :: Text aiEra = Text "sophie" , aiEncoding :: Text aiEncoding = Text "bech32" , aiAddress :: Text aiAddress = Text addrTxt , aiBase16 :: Text aiBase16 = StakeAddress -> Text forall a. SerialiseAsRawBytes a => a -> Text serialiseToRawBytesHexText StakeAddress addr } case Maybe OutputFile mOutputFp of Just (OutputFile String fpath) -> IO () -> ExceptT SophieAddressInfoError IO () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> ExceptT SophieAddressInfoError IO ()) -> IO () -> ExceptT SophieAddressInfoError IO () forall a b. (a -> b) -> a -> b $ String -> ByteString -> IO () LBS.writeFile String fpath (ByteString -> IO ()) -> ByteString -> IO () forall a b. (a -> b) -> a -> b $ AddressInfo -> ByteString forall a. ToJSON a => a -> ByteString encodePretty AddressInfo addrInfo Maybe OutputFile Nothing -> IO () -> ExceptT SophieAddressInfoError IO () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> ExceptT SophieAddressInfoError IO ()) -> IO () -> ExceptT SophieAddressInfoError IO () forall a b. (a -> b) -> a -> b $ ByteString -> IO () LBS.putStrLn (ByteString -> IO ()) -> ByteString -> IO () forall a b. (a -> b) -> a -> b $ AddressInfo -> ByteString forall a. ToJSON a => a -> ByteString encodePretty AddressInfo addrInfo