@@ -53,19 +53,34 @@ module Cardano.CLI.Shelley.Run.Read
53
53
, RequiredSignerError (.. )
54
54
, categoriseSomeWitness
55
55
, readRequiredSigner
56
+
57
+ -- * FileOrPipe
58
+ , FileOrPipe
59
+ , fileOrPipe
60
+ , fileOrPipePath
61
+ , fileOrPipeCache
62
+ , readFileOrPipe
56
63
) where
57
64
58
65
import Prelude
59
66
67
+ import Control.Exception (bracket )
68
+ import Control.Monad (unless )
60
69
import Control.Monad.Trans.Except (ExceptT (.. ), runExceptT )
61
- import Control.Monad.Trans.Except.Extra (firstExceptT , handleIOExceptT , hoistEither , left )
70
+ import Control.Monad.Trans.Except.Extra (firstExceptT , handleIOExceptT , hoistEither , left ,
71
+ newExceptT )
62
72
import qualified Data.Aeson as Aeson
63
73
import Data.Bifunctor (first )
74
+ import qualified Data.ByteString.Builder as Builder
64
75
import qualified Data.ByteString.Char8 as BS
65
76
import qualified Data.ByteString.Lazy.Char8 as LBS
77
+ import Data.IORef (IORef , newIORef , readIORef , writeIORef )
66
78
import qualified Data.List as List
67
79
import qualified Data.Text as Text
68
80
import Data.Word
81
+ import GHC.IO.Handle (hClose , hIsSeekable )
82
+ import GHC.IO.Handle.FD (openFileBlocking )
83
+ import System.IO (IOMode (ReadMode ))
69
84
70
85
71
86
import Cardano.Api
@@ -447,11 +462,11 @@ deserialiseScriptInAnyLang bs =
447
462
448
463
newtype CddlTx = CddlTx { unCddlTx :: InAnyCardanoEra Tx } deriving (Show , Eq )
449
464
450
- readFileTx :: FilePath -> IO (Either CddlError (InAnyCardanoEra Tx ))
451
- readFileTx fp = do
452
- eAnyTx <- readFileInAnyCardanoEra AsTx fp
465
+ readFileTx :: FileOrPipe -> IO (Either CddlError (InAnyCardanoEra Tx ))
466
+ readFileTx file = do
467
+ eAnyTx <- readFileInAnyCardanoEra AsTx file
453
468
case eAnyTx of
454
- Left e -> fmap unCddlTx <$> acceptTxCDDLSerialisation e
469
+ Left e -> fmap unCddlTx <$> acceptTxCDDLSerialisation file e
455
470
Right tx -> return $ Right tx
456
471
457
472
-- IncompleteCddlFormattedTx is an CDDL formatted tx or partial tx
@@ -463,11 +478,11 @@ data IncompleteTx
463
478
= UnwitnessedCliFormattedTxBody (InAnyCardanoEra TxBody )
464
479
| IncompleteCddlFormattedTx (InAnyCardanoEra Tx )
465
480
466
- readFileTxBody :: FilePath -> IO (Either CddlError IncompleteTx )
467
- readFileTxBody fp = do
468
- eTxBody <- readFileInAnyCardanoEra AsTxBody fp
481
+ readFileTxBody :: FileOrPipe -> IO (Either CddlError IncompleteTx )
482
+ readFileTxBody file = do
483
+ eTxBody <- readFileInAnyCardanoEra AsTxBody file
469
484
case eTxBody of
470
- Left e -> fmap (IncompleteCddlFormattedTx . unCddlTx) <$> acceptTxCDDLSerialisation e
485
+ Left e -> fmap (IncompleteCddlFormattedTx . unCddlTx) <$> acceptTxCDDLSerialisation file e
471
486
Right txBody -> return $ Right $ UnwitnessedCliFormattedTxBody txBody
472
487
473
488
data CddlError = CddlErrorTextEnv
@@ -484,21 +499,22 @@ renderCddlError (CddlErrorTextEnv textEnvErr cddlErr) = mconcat
484
499
renderCddlError (CddlIOError e) = Text. pack $ displayError e
485
500
486
501
acceptTxCDDLSerialisation
487
- :: FileError TextEnvelopeError
502
+ :: FileOrPipe
503
+ -> FileError TextEnvelopeError
488
504
-> IO (Either CddlError CddlTx )
489
- acceptTxCDDLSerialisation err =
505
+ acceptTxCDDLSerialisation file err =
490
506
case err of
491
- e@ (FileError fp (TextEnvelopeDecodeError _)) ->
492
- first (CddlErrorTextEnv e) <$> readCddlTx fp
493
- e@ (FileError fp (TextEnvelopeAesonDecodeError _)) ->
494
- first (CddlErrorTextEnv e) <$> readCddlTx fp
495
- e@ (FileError fp (TextEnvelopeTypeError _ _)) ->
496
- first (CddlErrorTextEnv e) <$> readCddlTx fp
507
+ e@ (FileError _ (TextEnvelopeDecodeError _)) ->
508
+ first (CddlErrorTextEnv e) <$> readCddlTx file
509
+ e@ (FileError _ (TextEnvelopeAesonDecodeError _)) ->
510
+ first (CddlErrorTextEnv e) <$> readCddlTx file
511
+ e@ (FileError _ (TextEnvelopeTypeError _ _)) ->
512
+ first (CddlErrorTextEnv e) <$> readCddlTx file
497
513
e@ FileErrorTempFile {} -> return . Left $ CddlIOError e
498
514
e@ FileIOError {} -> return . Left $ CddlIOError e
499
515
500
- readCddlTx :: FilePath -> IO (Either (FileError TextEnvelopeCddlError ) CddlTx )
501
- readCddlTx = readFileTextEnvelopeCddlAnyOf teTypes
516
+ readCddlTx :: FileOrPipe -> IO (Either (FileError TextEnvelopeCddlError ) CddlTx )
517
+ readCddlTx = readFileOrPipeTextEnvelopeCddlAnyOf teTypes
502
518
where
503
519
teTypes = [ FromCDDLTx " Witnessed Tx ByronEra" CddlTx
504
520
, FromCDDLTx " Witnessed Tx ShelleyEra" CddlTx
@@ -521,7 +537,8 @@ newtype CddlWitness = CddlWitness { unCddlWitness :: InAnyCardanoEra KeyWitness}
521
537
readFileTxKeyWitness :: FilePath
522
538
-> IO (Either CddlWitnessError (InAnyCardanoEra KeyWitness ))
523
539
readFileTxKeyWitness fp = do
524
- eWitness <- readFileInAnyCardanoEra AsKeyWitness fp
540
+ file <- fileOrPipe fp
541
+ eWitness <- readFileInAnyCardanoEra AsKeyWitness file
525
542
case eWitness of
526
543
Left e -> fmap unCddlWitness <$> acceptKeyWitnessCDDLSerialisation e
527
544
Right keyWit -> return $ Right keyWit
@@ -727,14 +744,99 @@ readFileInAnyCardanoEra
727
744
, HasTextEnvelope (thing BabbageEra )
728
745
)
729
746
=> (forall era . AsType era -> AsType (thing era ))
730
- -> FilePath
747
+ -> FileOrPipe
731
748
-> IO (Either (FileError TextEnvelopeError ) (InAnyCardanoEra thing ))
732
749
readFileInAnyCardanoEra asThing =
733
- readFileTextEnvelopeAnyOf
750
+ readFileOrPipeTextEnvelopeAnyOf
734
751
[ FromSomeType (asThing AsByronEra ) (InAnyCardanoEra ByronEra )
735
752
, FromSomeType (asThing AsShelleyEra ) (InAnyCardanoEra ShelleyEra )
736
753
, FromSomeType (asThing AsAllegraEra ) (InAnyCardanoEra AllegraEra )
737
754
, FromSomeType (asThing AsMaryEra ) (InAnyCardanoEra MaryEra )
738
755
, FromSomeType (asThing AsAlonzoEra ) (InAnyCardanoEra AlonzoEra )
739
756
, FromSomeType (asThing AsBabbageEra ) (InAnyCardanoEra BabbageEra )
740
757
]
758
+
759
+ -- | We need a type for handling files that may be actually be things like
760
+ -- pipes. Currently the CLI makes no guarantee that a "file" will only
761
+ -- be read once. This is a problem for a user who who expects to be able to pass
762
+ -- a pipe. To handle this, we have a type for representing either files or pipes
763
+ -- where the contents will be saved in memory if what we're reading is a pipe (so
764
+ -- it can be re-read later). Unfortunately this means we can't easily stream data
765
+ -- from pipes, but at present that's not an issue.
766
+ data FileOrPipe = FileOrPipe FilePath (IORef (Maybe LBS. ByteString ))
767
+
768
+
769
+ instance Show FileOrPipe where
770
+ show (FileOrPipe fp _) = show fp
771
+
772
+ fileOrPipe :: FilePath -> IO FileOrPipe
773
+ fileOrPipe fp = FileOrPipe fp <$> newIORef Nothing
774
+
775
+ -- | Get the path backing a FileOrPipe. This should primarily be used when
776
+ -- generating error messages for a user. A user should not call directly
777
+ -- call a function like readFile on the result of this function
778
+ fileOrPipePath :: FileOrPipe -> FilePath
779
+ fileOrPipePath (FileOrPipe fp _) = fp
780
+
781
+ fileOrPipeCache :: FileOrPipe -> IO (Maybe LBS. ByteString )
782
+ fileOrPipeCache (FileOrPipe _ c) = readIORef c
783
+
784
+ -- | Get the contents of a file or pipe. This function reads the entire
785
+ -- contents of the file or pipe, and is blocking.
786
+ readFileOrPipe :: FileOrPipe -> IO LBS. ByteString
787
+ readFileOrPipe (FileOrPipe fp cacheRef) = do
788
+ cached <- readIORef cacheRef
789
+ case cached of
790
+ Just dat -> pure dat
791
+ Nothing -> bracket
792
+ (openFileBlocking fp ReadMode )
793
+ hClose
794
+ (\ handle -> do
795
+ -- An arbitrary block size.
796
+ let blockSize = 4096
797
+ let go acc = do
798
+ next <- BS. hGet handle blockSize
799
+ if BS. null next
800
+ then pure acc
801
+ else go (acc <> Builder. byteString next)
802
+ contents <- go mempty
803
+ let dat = Builder. toLazyByteString contents
804
+ -- If our file is not seekable, it's likely a pipe, so we need to
805
+ -- save the result for subsequent calls
806
+ seekable <- hIsSeekable handle
807
+ unless seekable (writeIORef cacheRef (Just dat))
808
+ pure dat)
809
+
810
+ readFileOrPipeTextEnvelopeAnyOf
811
+ :: [FromSomeType HasTextEnvelope b ]
812
+ -> FileOrPipe
813
+ -> IO (Either (FileError TextEnvelopeError ) b )
814
+ readFileOrPipeTextEnvelopeAnyOf types file = do
815
+ let path = fileOrPipePath file
816
+ runExceptT $ do
817
+ content <- handleIOExceptT (FileIOError path) $ readFileOrPipe file
818
+ firstExceptT (FileError path) $ hoistEither $ do
819
+ te <- first TextEnvelopeAesonDecodeError $ Aeson. eitherDecode' content
820
+ deserialiseFromTextEnvelopeAnyOf types te
821
+
822
+ readFileOrPipeTextEnvelopeCddlAnyOf
823
+ :: [FromSomeTypeCDDL TextEnvelopeCddl b ]
824
+ -> FileOrPipe
825
+ -> IO (Either (FileError TextEnvelopeCddlError ) b )
826
+ readFileOrPipeTextEnvelopeCddlAnyOf types file = do
827
+ let path = fileOrPipePath file
828
+ runExceptT $ do
829
+ te <- newExceptT $ readTextEnvelopeCddlFromFileOrPipe file
830
+ firstExceptT (FileError path) $ hoistEither $ do
831
+ deserialiseFromTextEnvelopeCddlAnyOf types te
832
+
833
+ readTextEnvelopeCddlFromFileOrPipe
834
+ :: FileOrPipe
835
+ -> IO (Either (FileError TextEnvelopeCddlError ) TextEnvelopeCddl )
836
+ readTextEnvelopeCddlFromFileOrPipe file = do
837
+ let path = fileOrPipePath file
838
+ runExceptT $ do
839
+ bs <- handleIOExceptT (FileIOError path) $
840
+ readFileOrPipe file
841
+ firstExceptT (FileError path . TextEnvelopeCddlAesonDecodeError path)
842
+ . hoistEither $ Aeson. eitherDecode' bs
0 commit comments