module Hydra.Utils where import Hydra.Prelude import Crypto.Random (getRandomBytes) import Data.Aeson qualified as Aeson import Data.Aeson.Types qualified as Aeson import GHC.IO.Exception (userError) import Hydra.Cardano.Api (File (..), FileError (FileIOError), Key (SigningKey), getVerificationKey, writeFileTextEnvelope) import Hydra.Options (GenerateKeyPair (..)) import Hydra.Tx.Crypto (HydraKey, generateSigningKey) import System.Directory (doesFileExist) import System.FilePath ((<.>)) genHydraKeys :: GenerateKeyPair -> IO (Either (FileError ()) ()) genHydraKeys :: GenerateKeyPair -> IO (Either (FileError ()) ()) genHydraKeys GenerateKeyPair{FilePath outputFile :: FilePath $sel:outputFile:GenerateKeyPair :: GenerateKeyPair -> FilePath outputFile} = do Bool fileExists <- FilePath -> IO Bool doesFileExist FilePath outputFile if Bool fileExists then Either (FileError ()) () -> IO (Either (FileError ()) ()) forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pure (Either (FileError ()) () -> IO (Either (FileError ()) ())) -> Either (FileError ()) () -> IO (Either (FileError ()) ()) forall a b. (a -> b) -> a -> b $ FileError () -> Either (FileError ()) () forall a b. a -> Either a b Left (FileError () -> Either (FileError ()) ()) -> FileError () -> Either (FileError ()) () forall a b. (a -> b) -> a -> b $ FilePath -> IOException -> FileError () forall e. FilePath -> IOException -> FileError e FileIOError FilePath outputFile (FilePath -> IOException userError FilePath "File already exists! Please remove it in order to generate new hydra keys.") else do SigningKey HydraKey sk :: SigningKey HydraKey <- ByteString -> SigningKey HydraKey generateSigningKey (ByteString -> SigningKey HydraKey) -> IO ByteString -> IO (SigningKey HydraKey) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Int -> IO ByteString forall byteArray. ByteArray byteArray => Int -> IO byteArray forall (m :: * -> *) byteArray. (MonadRandom m, ByteArray byteArray) => Int -> m byteArray getRandomBytes Int 16 ExceptT (FileError ()) IO () -> IO (Either (FileError ()) ()) forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a) runExceptT (ExceptT (FileError ()) IO () -> IO (Either (FileError ()) ())) -> ExceptT (FileError ()) IO () -> IO (Either (FileError ()) ()) forall a b. (a -> b) -> a -> b $ do IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO () forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a ExceptT (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()) -> IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO () forall a b. (a -> b) -> a -> b $ File Any 'Out -> Maybe TextEnvelopeDescr -> SigningKey HydraKey -> IO (Either (FileError ()) ()) forall a content. HasTextEnvelope a => File content 'Out -> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ()) writeFileTextEnvelope (FilePath -> File Any 'Out forall content (direction :: FileDirection). FilePath -> File content direction File (FilePath outputFile FilePath -> FilePath -> FilePath <.> FilePath "sk")) Maybe TextEnvelopeDescr forall a. Maybe a Nothing SigningKey HydraKey sk IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO () forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a ExceptT (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()) -> IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO () forall a b. (a -> b) -> a -> b $ File Any 'Out -> Maybe TextEnvelopeDescr -> VerificationKey HydraKey -> IO (Either (FileError ()) ()) forall a content. HasTextEnvelope a => File content 'Out -> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ()) writeFileTextEnvelope (FilePath -> File Any 'Out forall content (direction :: FileDirection). FilePath -> File content direction File (FilePath outputFile FilePath -> FilePath -> FilePath <.> FilePath "vk")) Maybe TextEnvelopeDescr forall a. Maybe a Nothing (SigningKey HydraKey -> VerificationKey HydraKey forall keyrole. (Key keyrole, HasTypeProxy keyrole) => SigningKey keyrole -> VerificationKey keyrole getVerificationKey SigningKey HydraKey sk) readJsonFileThrow :: (Aeson.Value -> Aeson.Parser a) -> FilePath -> IO a readJsonFileThrow :: forall a. (Value -> Parser a) -> FilePath -> IO a readJsonFileThrow Value -> Parser a parser FilePath filepath = do Value value <- FilePath -> IO (Either FilePath Value) forall a. FromJSON a => FilePath -> IO (Either FilePath a) Aeson.eitherDecodeFileStrict FilePath filepath IO (Either FilePath Value) -> (Either FilePath Value -> IO Value) -> IO Value forall a b. IO a -> (a -> IO b) -> IO b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= (FilePath -> IO Value) -> (Value -> IO Value) -> Either FilePath Value -> IO Value forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either FilePath -> IO Value forall a. FilePath -> IO a forall (m :: * -> *) a. MonadFail m => FilePath -> m a fail Value -> IO Value forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pure case (Value -> Parser a) -> Value -> Either FilePath a forall a b. (a -> Parser b) -> a -> Either FilePath b Aeson.parseEither Value -> Parser a parser Value value of Left FilePath e -> FilePath -> IO a forall a. FilePath -> IO a forall (m :: * -> *) a. MonadFail m => FilePath -> m a fail FilePath e Right a a -> a -> IO a forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pure a a