11{-# LANGUAGE DataKinds #-}
22{-# LANGUAGE LambdaCase #-}
3+ {-# LANGUAGE NamedFieldPuns #-}
4+
5+ {- HLINT ignore "Redundant id" -}
36
47module Cardano.CLI.EraBased.TextView.Run
58 ( runTextViewCmds
@@ -10,23 +13,42 @@ where
1013import Cardano.Api
1114
1215import Cardano.CLI.EraBased.TextView.Command
13- import Cardano.CLI.Helper (pPrintCBOR )
16+ import Cardano.CLI.Helper (cborToText )
17+ import Cardano.CLI.Type.Common
1418import Cardano.CLI.Type.Error.TextViewFileError
1519
1620import Data.ByteString.Lazy.Char8 qualified as LBS
21+ import Data.Function ((&) )
22+ import Data.Text.Encoding qualified as Text
23+ import System.IO qualified as IO
24+ import Vary qualified
1725
1826runTextViewCmds :: TextViewCmds era -> ExceptT TextViewFileError IO ()
1927runTextViewCmds = \ case
20- TextViewInfo fpath mOutfile -> runTextViewInfoCmd fpath mOutfile
28+ TextViewDecodeCborCmd cmd -> runTextViewInfoCmd cmd
2129
2230runTextViewInfoCmd
2331 :: ()
24- => FilePath
25- -> Maybe (File () Out )
32+ => TextViewDecodeCborCmdArgs
2633 -> ExceptT TextViewFileError IO ()
27- runTextViewInfoCmd fpath mOutFile = do
28- tv <- firstExceptT TextViewReadFileError $ newExceptT (readTextEnvelopeFromFile fpath)
29- let lbCBOR = LBS. fromStrict (textEnvelopeRawCBOR tv)
30- case mOutFile of
31- Just (File oFpath) -> liftIO $ LBS. writeFile oFpath lbCBOR
32- Nothing -> firstExceptT TextViewCBORPrettyPrintError $ pPrintCBOR lbCBOR
34+ runTextViewInfoCmd
35+ TextViewDecodeCborCmdArgs
36+ { inputFile
37+ , outputFormat
38+ , mOutFile
39+ } = do
40+ tv <- firstExceptT TextViewReadFileError $ newExceptT (readTextEnvelopeFromFile inputFile)
41+ let lbCBOR = LBS. fromStrict (textEnvelopeRawCBOR tv)
42+
43+ outputContent <-
44+ outputFormat
45+ & ( id
46+ . Vary. on (\ FormatCbor -> pure lbCBOR)
47+ . Vary. on (\ FormatText -> LBS. fromStrict . Text. encodeUtf8 <$> cborToText lbCBOR)
48+ $ Vary. exhaustiveCase
49+ )
50+ & firstExceptT TextViewCBORPrettyPrintError
51+
52+ let writeOutput = maybe (LBS. hPut IO. stdout) (LBS. writeFile . unFile) mOutFile
53+
54+ liftIO $ writeOutput outputContent
0 commit comments