{-# LANGUAGE CPP #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}

#if !defined(mingw32_HOST_OS)
#define UNIX
#endif

-- | TextEnvelope Serialisation
--
module Cardano.Api.SerialiseTextEnvelope
  ( HasTextEnvelope(..)
  , TextEnvelope(..)
  , TextEnvelopeType(..)
  , TextEnvelopeDescr(..)
  , textEnvelopeRawCBOR
  , TextEnvelopeError(..)
  , serialiseToTextEnvelope
  , deserialiseFromTextEnvelope
  , readFileTextEnvelope
  , writeFileTextEnvelope
  , writeFileTextEnvelopeWithOwnerPermissions
  , readTextEnvelopeFromFile
  , readTextEnvelopeOfTypeFromFile
  , textEnvelopeToJSON

    -- * Reading one of several key types
  , FromSomeType(..)
  , deserialiseFromTextEnvelopeAnyOf
  , readFileTextEnvelopeAnyOf

    -- * Data family instances
  , AsType(..)
  ) where

import           Prelude

import           Data.Bifunctor (first)
import           Data.ByteString (ByteString)
import qualified Data.ByteString.Base16 as Base16
import qualified Data.ByteString.Lazy as LBS
import qualified Data.List as List
import           Data.Maybe (fromMaybe)
import           Data.String (IsString)
import           Data.Text (Text)
import qualified Data.Text.Encoding as Text

import           Data.Aeson (FromJSON (..), ToJSON (..), object, withObject, (.:), (.=))
import qualified Data.Aeson as Aeson
import           Data.Aeson.Encode.Pretty (Config (..), defConfig, encodePretty', keyOrder)

import           Control.Monad (unless)
import           Control.Monad.Trans.Except (ExceptT (..), runExceptT)
import           Control.Monad.Trans.Except.Extra (firstExceptT, handleIOExceptT, hoistEither)


import           Cardano.Binary (DecoderError)

import           Cardano.Api.Error
import           Cardano.Api.HasTypeProxy
import           Cardano.Api.SerialiseCBOR
import           Cardano.Api.Utils (readFileBlocking)

#ifdef UNIX
import           Control.Exception (IOException, bracket, bracketOnError, try)
import           System.Directory ()
import           System.Posix.Files (ownerModes, setFdOwnerAndGroup)
import           System.Posix.IO (OpenMode (..), closeFd, openFd, fdToHandle, defaultFileFlags)
import           System.Posix.User (getRealUserID)
import           System.IO (hClose)
#else
import           Control.Exception (bracketOnError)
import           System.Directory (removeFile, renameFile)
import           System.FilePath (splitFileName, (<.>))
import           System.IO (hClose, openTempFile)
#endif


-- ----------------------------------------------------------------------------
-- Text envelopes
--

newtype TextEnvelopeType = TextEnvelopeType String
  deriving (TextEnvelopeType -> TextEnvelopeType -> Bool
(TextEnvelopeType -> TextEnvelopeType -> Bool)
-> (TextEnvelopeType -> TextEnvelopeType -> Bool)
-> Eq TextEnvelopeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextEnvelopeType -> TextEnvelopeType -> Bool
$c/= :: TextEnvelopeType -> TextEnvelopeType -> Bool
== :: TextEnvelopeType -> TextEnvelopeType -> Bool
$c== :: TextEnvelopeType -> TextEnvelopeType -> Bool
Eq, Int -> TextEnvelopeType -> ShowS
[TextEnvelopeType] -> ShowS
TextEnvelopeType -> String
(Int -> TextEnvelopeType -> ShowS)
-> (TextEnvelopeType -> String)
-> ([TextEnvelopeType] -> ShowS)
-> Show TextEnvelopeType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextEnvelopeType] -> ShowS
$cshowList :: [TextEnvelopeType] -> ShowS
show :: TextEnvelopeType -> String
$cshow :: TextEnvelopeType -> String
showsPrec :: Int -> TextEnvelopeType -> ShowS
$cshowsPrec :: Int -> TextEnvelopeType -> ShowS
Show)
  deriving newtype (String -> TextEnvelopeType
(String -> TextEnvelopeType) -> IsString TextEnvelopeType
forall a. (String -> a) -> IsString a
fromString :: String -> TextEnvelopeType
$cfromString :: String -> TextEnvelopeType
IsString, b -> TextEnvelopeType -> TextEnvelopeType
NonEmpty TextEnvelopeType -> TextEnvelopeType
TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
(TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType)
-> (NonEmpty TextEnvelopeType -> TextEnvelopeType)
-> (forall b.
    Integral b =>
    b -> TextEnvelopeType -> TextEnvelopeType)
-> Semigroup TextEnvelopeType
forall b. Integral b => b -> TextEnvelopeType -> TextEnvelopeType
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> TextEnvelopeType -> TextEnvelopeType
$cstimes :: forall b. Integral b => b -> TextEnvelopeType -> TextEnvelopeType
sconcat :: NonEmpty TextEnvelopeType -> TextEnvelopeType
$csconcat :: NonEmpty TextEnvelopeType -> TextEnvelopeType
<> :: TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
$c<> :: TextEnvelopeType -> TextEnvelopeType -> TextEnvelopeType
Semigroup, [TextEnvelopeType] -> Encoding
[TextEnvelopeType] -> Value
TextEnvelopeType -> Encoding
TextEnvelopeType -> Value
(TextEnvelopeType -> Value)
-> (TextEnvelopeType -> Encoding)
-> ([TextEnvelopeType] -> Value)
-> ([TextEnvelopeType] -> Encoding)
-> ToJSON TextEnvelopeType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TextEnvelopeType] -> Encoding
$ctoEncodingList :: [TextEnvelopeType] -> Encoding
toJSONList :: [TextEnvelopeType] -> Value
$ctoJSONList :: [TextEnvelopeType] -> Value
toEncoding :: TextEnvelopeType -> Encoding
$ctoEncoding :: TextEnvelopeType -> Encoding
toJSON :: TextEnvelopeType -> Value
$ctoJSON :: TextEnvelopeType -> Value
ToJSON, Value -> Parser [TextEnvelopeType]
Value -> Parser TextEnvelopeType
(Value -> Parser TextEnvelopeType)
-> (Value -> Parser [TextEnvelopeType])
-> FromJSON TextEnvelopeType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TextEnvelopeType]
$cparseJSONList :: Value -> Parser [TextEnvelopeType]
parseJSON :: Value -> Parser TextEnvelopeType
$cparseJSON :: Value -> Parser TextEnvelopeType
FromJSON)

newtype TextEnvelopeDescr = TextEnvelopeDescr String
  deriving (TextEnvelopeDescr -> TextEnvelopeDescr -> Bool
(TextEnvelopeDescr -> TextEnvelopeDescr -> Bool)
-> (TextEnvelopeDescr -> TextEnvelopeDescr -> Bool)
-> Eq TextEnvelopeDescr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextEnvelopeDescr -> TextEnvelopeDescr -> Bool
$c/= :: TextEnvelopeDescr -> TextEnvelopeDescr -> Bool
== :: TextEnvelopeDescr -> TextEnvelopeDescr -> Bool
$c== :: TextEnvelopeDescr -> TextEnvelopeDescr -> Bool
Eq, Int -> TextEnvelopeDescr -> ShowS
[TextEnvelopeDescr] -> ShowS
TextEnvelopeDescr -> String
(Int -> TextEnvelopeDescr -> ShowS)
-> (TextEnvelopeDescr -> String)
-> ([TextEnvelopeDescr] -> ShowS)
-> Show TextEnvelopeDescr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextEnvelopeDescr] -> ShowS
$cshowList :: [TextEnvelopeDescr] -> ShowS
show :: TextEnvelopeDescr -> String
$cshow :: TextEnvelopeDescr -> String
showsPrec :: Int -> TextEnvelopeDescr -> ShowS
$cshowsPrec :: Int -> TextEnvelopeDescr -> ShowS
Show)
  deriving newtype (String -> TextEnvelopeDescr
(String -> TextEnvelopeDescr) -> IsString TextEnvelopeDescr
forall a. (String -> a) -> IsString a
fromString :: String -> TextEnvelopeDescr
$cfromString :: String -> TextEnvelopeDescr
IsString, b -> TextEnvelopeDescr -> TextEnvelopeDescr
NonEmpty TextEnvelopeDescr -> TextEnvelopeDescr
TextEnvelopeDescr -> TextEnvelopeDescr -> TextEnvelopeDescr
(TextEnvelopeDescr -> TextEnvelopeDescr -> TextEnvelopeDescr)
-> (NonEmpty TextEnvelopeDescr -> TextEnvelopeDescr)
-> (forall b.
    Integral b =>
    b -> TextEnvelopeDescr -> TextEnvelopeDescr)
-> Semigroup TextEnvelopeDescr
forall b. Integral b => b -> TextEnvelopeDescr -> TextEnvelopeDescr
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> TextEnvelopeDescr -> TextEnvelopeDescr
$cstimes :: forall b. Integral b => b -> TextEnvelopeDescr -> TextEnvelopeDescr
sconcat :: NonEmpty TextEnvelopeDescr -> TextEnvelopeDescr
$csconcat :: NonEmpty TextEnvelopeDescr -> TextEnvelopeDescr
<> :: TextEnvelopeDescr -> TextEnvelopeDescr -> TextEnvelopeDescr
$c<> :: TextEnvelopeDescr -> TextEnvelopeDescr -> TextEnvelopeDescr
Semigroup, [TextEnvelopeDescr] -> Encoding
[TextEnvelopeDescr] -> Value
TextEnvelopeDescr -> Encoding
TextEnvelopeDescr -> Value
(TextEnvelopeDescr -> Value)
-> (TextEnvelopeDescr -> Encoding)
-> ([TextEnvelopeDescr] -> Value)
-> ([TextEnvelopeDescr] -> Encoding)
-> ToJSON TextEnvelopeDescr
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TextEnvelopeDescr] -> Encoding
$ctoEncodingList :: [TextEnvelopeDescr] -> Encoding
toJSONList :: [TextEnvelopeDescr] -> Value
$ctoJSONList :: [TextEnvelopeDescr] -> Value
toEncoding :: TextEnvelopeDescr -> Encoding
$ctoEncoding :: TextEnvelopeDescr -> Encoding
toJSON :: TextEnvelopeDescr -> Value
$ctoJSON :: TextEnvelopeDescr -> Value
ToJSON, Value -> Parser [TextEnvelopeDescr]
Value -> Parser TextEnvelopeDescr
(Value -> Parser TextEnvelopeDescr)
-> (Value -> Parser [TextEnvelopeDescr])
-> FromJSON TextEnvelopeDescr
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TextEnvelopeDescr]
$cparseJSONList :: Value -> Parser [TextEnvelopeDescr]
parseJSON :: Value -> Parser TextEnvelopeDescr
$cparseJSON :: Value -> Parser TextEnvelopeDescr
FromJSON)

-- | A 'TextEnvelope' is a structured envelope for serialised binary values
-- with an external format with a semi-readable textual format.
--
-- It contains a \"type\" field, e.g. \"PublicKeyByron\" or \"TxSignedShelley\"
-- to indicate the type of the encoded data. This is used as a sanity check
-- and to help readers.
--
-- It also contains a \"title\" field which is free-form, and could be used
-- to indicate the role or purpose to a reader.
--
data TextEnvelope = TextEnvelope
  { TextEnvelope -> TextEnvelopeType
teType        :: !TextEnvelopeType
  , TextEnvelope -> TextEnvelopeDescr
teDescription :: !TextEnvelopeDescr
  , TextEnvelope -> ByteString
teRawCBOR     :: !ByteString
  } deriving (TextEnvelope -> TextEnvelope -> Bool
(TextEnvelope -> TextEnvelope -> Bool)
-> (TextEnvelope -> TextEnvelope -> Bool) -> Eq TextEnvelope
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextEnvelope -> TextEnvelope -> Bool
$c/= :: TextEnvelope -> TextEnvelope -> Bool
== :: TextEnvelope -> TextEnvelope -> Bool
$c== :: TextEnvelope -> TextEnvelope -> Bool
Eq, Int -> TextEnvelope -> ShowS
[TextEnvelope] -> ShowS
TextEnvelope -> String
(Int -> TextEnvelope -> ShowS)
-> (TextEnvelope -> String)
-> ([TextEnvelope] -> ShowS)
-> Show TextEnvelope
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextEnvelope] -> ShowS
$cshowList :: [TextEnvelope] -> ShowS
show :: TextEnvelope -> String
$cshow :: TextEnvelope -> String
showsPrec :: Int -> TextEnvelope -> ShowS
$cshowsPrec :: Int -> TextEnvelope -> ShowS
Show)

instance HasTypeProxy TextEnvelope where
    data AsType TextEnvelope = AsTextEnvelope
    proxyToAsType :: Proxy TextEnvelope -> AsType TextEnvelope
proxyToAsType Proxy TextEnvelope
_ = AsType TextEnvelope
AsTextEnvelope

instance ToJSON TextEnvelope where
  toJSON :: TextEnvelope -> Value
toJSON TextEnvelope {TextEnvelopeType
teType :: TextEnvelopeType
teType :: TextEnvelope -> TextEnvelopeType
teType, TextEnvelopeDescr
teDescription :: TextEnvelopeDescr
teDescription :: TextEnvelope -> TextEnvelopeDescr
teDescription, ByteString
teRawCBOR :: ByteString
teRawCBOR :: TextEnvelope -> ByteString
teRawCBOR} =
    [Pair] -> Value
object [ Key
"type"        Key -> TextEnvelopeType -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TextEnvelopeType
teType
           , Key
"description" Key -> TextEnvelopeDescr -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TextEnvelopeDescr
teDescription
           , Key
"cborHex"     Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ByteString -> Text
Text.decodeUtf8 (ByteString -> ByteString
Base16.encode ByteString
teRawCBOR)
           ]

instance FromJSON TextEnvelope where
  parseJSON :: Value -> Parser TextEnvelope
parseJSON = String
-> (Object -> Parser TextEnvelope) -> Value -> Parser TextEnvelope
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TextEnvelope" ((Object -> Parser TextEnvelope) -> Value -> Parser TextEnvelope)
-> (Object -> Parser TextEnvelope) -> Value -> Parser TextEnvelope
forall a b. (a -> b) -> a -> b
$ \Object
v ->
                TextEnvelopeType -> TextEnvelopeDescr -> ByteString -> TextEnvelope
TextEnvelope (TextEnvelopeType
 -> TextEnvelopeDescr -> ByteString -> TextEnvelope)
-> Parser TextEnvelopeType
-> Parser (TextEnvelopeDescr -> ByteString -> TextEnvelope)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
v Object -> Key -> Parser TextEnvelopeType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type")
                             Parser (TextEnvelopeDescr -> ByteString -> TextEnvelope)
-> Parser TextEnvelopeDescr -> Parser (ByteString -> TextEnvelope)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
v Object -> Key -> Parser TextEnvelopeDescr
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"description")
                             Parser (ByteString -> TextEnvelope)
-> Parser ByteString -> Parser TextEnvelope
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Value -> Parser ByteString
parseJSONBase16 (Value -> Parser ByteString) -> Parser Value -> Parser ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
v Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"cborHex")
    where
      parseJSONBase16 :: Value -> Parser ByteString
parseJSONBase16 Value
v =
        (String -> Parser ByteString)
-> (ByteString -> Parser ByteString)
-> Either String ByteString
-> Parser ByteString
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Parser ByteString
forall (m :: * -> *) a. MonadFail m => String -> m a
fail ByteString -> Parser ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String ByteString -> Parser ByteString)
-> (Text -> Either String ByteString) -> Text -> Parser ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String ByteString
Base16.decode (ByteString -> Either String ByteString)
-> (Text -> ByteString) -> Text -> Either String ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf8 (Text -> Parser ByteString) -> Parser Text -> Parser ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v

textEnvelopeJSONConfig :: Config
textEnvelopeJSONConfig :: Config
textEnvelopeJSONConfig = Config
defConfig { confCompare :: Text -> Text -> Ordering
confCompare = Text -> Text -> Ordering
textEnvelopeJSONKeyOrder }

textEnvelopeJSONKeyOrder :: Text -> Text -> Ordering
textEnvelopeJSONKeyOrder :: Text -> Text -> Ordering
textEnvelopeJSONKeyOrder = [Text] -> Text -> Text -> Ordering
keyOrder [Text
"type", Text
"description", Text
"cborHex"]


textEnvelopeRawCBOR :: TextEnvelope -> ByteString
textEnvelopeRawCBOR :: TextEnvelope -> ByteString
textEnvelopeRawCBOR = TextEnvelope -> ByteString
teRawCBOR


-- | The errors that the pure 'TextEnvelope' parsing\/decoding functions can return.
--
data TextEnvelopeError
  = TextEnvelopeTypeError   ![TextEnvelopeType] !TextEnvelopeType -- ^ expected, actual
  | TextEnvelopeDecodeError !DecoderError
  | TextEnvelopeAesonDecodeError !String
  deriving (TextEnvelopeError -> TextEnvelopeError -> Bool
(TextEnvelopeError -> TextEnvelopeError -> Bool)
-> (TextEnvelopeError -> TextEnvelopeError -> Bool)
-> Eq TextEnvelopeError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextEnvelopeError -> TextEnvelopeError -> Bool
$c/= :: TextEnvelopeError -> TextEnvelopeError -> Bool
== :: TextEnvelopeError -> TextEnvelopeError -> Bool
$c== :: TextEnvelopeError -> TextEnvelopeError -> Bool
Eq, Int -> TextEnvelopeError -> ShowS
[TextEnvelopeError] -> ShowS
TextEnvelopeError -> String
(Int -> TextEnvelopeError -> ShowS)
-> (TextEnvelopeError -> String)
-> ([TextEnvelopeError] -> ShowS)
-> Show TextEnvelopeError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextEnvelopeError] -> ShowS
$cshowList :: [TextEnvelopeError] -> ShowS
show :: TextEnvelopeError -> String
$cshow :: TextEnvelopeError -> String
showsPrec :: Int -> TextEnvelopeError -> ShowS
$cshowsPrec :: Int -> TextEnvelopeError -> ShowS
Show)

instance Error TextEnvelopeError where
  displayError :: TextEnvelopeError -> String
displayError TextEnvelopeError
tee =
    case TextEnvelopeError
tee of
      TextEnvelopeTypeError [TextEnvelopeType String
expType]
                            (TextEnvelopeType String
actType) ->
          String
"TextEnvelope type error: "
       String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" Expected: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
expType
       String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" Actual: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
actType

      TextEnvelopeTypeError [TextEnvelopeType]
expTypes (TextEnvelopeType String
actType) ->
          String
"TextEnvelope type error: "
       String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" Expected one of: "
       String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
List.intercalate String
", "
            [ String
expType | TextEnvelopeType String
expType <- [TextEnvelopeType]
expTypes ]
       String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" Actual: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
actType
      TextEnvelopeAesonDecodeError String
decErr -> String
"TextEnvelope aeson decode error: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
decErr
      TextEnvelopeDecodeError DecoderError
decErr -> String
"TextEnvelope decode error: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> DecoderError -> String
forall a. Show a => a -> String
show DecoderError
decErr


-- | Check that the \"type\" of the 'TextEnvelope' is as expected.
--
-- For example, one might check that the type is \"TxSignedShelley\".
--
expectTextEnvelopeOfType :: TextEnvelopeType -> TextEnvelope -> Either TextEnvelopeError ()
expectTextEnvelopeOfType :: TextEnvelopeType -> TextEnvelope -> Either TextEnvelopeError ()
expectTextEnvelopeOfType TextEnvelopeType
expectedType TextEnvelope { teType :: TextEnvelope -> TextEnvelopeType
teType = TextEnvelopeType
actualType } =
    Bool -> Either TextEnvelopeError () -> Either TextEnvelopeError ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (TextEnvelopeType
expectedType TextEnvelopeType -> TextEnvelopeType -> Bool
forall a. Eq a => a -> a -> Bool
== TextEnvelopeType
actualType) (Either TextEnvelopeError () -> Either TextEnvelopeError ())
-> Either TextEnvelopeError () -> Either TextEnvelopeError ()
forall a b. (a -> b) -> a -> b
$
      TextEnvelopeError -> Either TextEnvelopeError ()
forall a b. a -> Either a b
Left ([TextEnvelopeType] -> TextEnvelopeType -> TextEnvelopeError
TextEnvelopeTypeError [TextEnvelopeType
expectedType] TextEnvelopeType
actualType)


-- ----------------------------------------------------------------------------
-- Serialisation in text envelope format
--

class SerialiseAsCBOR a => HasTextEnvelope a where
    textEnvelopeType :: AsType a -> TextEnvelopeType

    textEnvelopeDefaultDescr :: a -> TextEnvelopeDescr
    textEnvelopeDefaultDescr a
_ = TextEnvelopeDescr
""


serialiseToTextEnvelope :: forall a. HasTextEnvelope a
                        => Maybe TextEnvelopeDescr -> a -> TextEnvelope
serialiseToTextEnvelope :: Maybe TextEnvelopeDescr -> a -> TextEnvelope
serialiseToTextEnvelope Maybe TextEnvelopeDescr
mbDescr a
a =
    TextEnvelope :: TextEnvelopeType -> TextEnvelopeDescr -> ByteString -> TextEnvelope
TextEnvelope {
      teType :: TextEnvelopeType
teType    = AsType a -> TextEnvelopeType
forall a. HasTextEnvelope a => AsType a -> TextEnvelopeType
textEnvelopeType AsType a
ttoken
    , teDescription :: TextEnvelopeDescr
teDescription   = TextEnvelopeDescr -> Maybe TextEnvelopeDescr -> TextEnvelopeDescr
forall a. a -> Maybe a -> a
fromMaybe (a -> TextEnvelopeDescr
forall a. HasTextEnvelope a => a -> TextEnvelopeDescr
textEnvelopeDefaultDescr a
a) Maybe TextEnvelopeDescr
mbDescr
    , teRawCBOR :: ByteString
teRawCBOR = a -> ByteString
forall a. SerialiseAsCBOR a => a -> ByteString
serialiseToCBOR a
a
    }
  where
    ttoken :: AsType a
    ttoken :: AsType a
ttoken = Proxy a -> AsType a
forall t. HasTypeProxy t => Proxy t -> AsType t
proxyToAsType Proxy a
forall k (t :: k). Proxy t
Proxy


deserialiseFromTextEnvelope :: HasTextEnvelope a
                            => AsType a
                            -> TextEnvelope
                            -> Either TextEnvelopeError a
deserialiseFromTextEnvelope :: AsType a -> TextEnvelope -> Either TextEnvelopeError a
deserialiseFromTextEnvelope AsType a
ttoken TextEnvelope
te = do
    TextEnvelopeType -> TextEnvelope -> Either TextEnvelopeError ()
expectTextEnvelopeOfType (AsType a -> TextEnvelopeType
forall a. HasTextEnvelope a => AsType a -> TextEnvelopeType
textEnvelopeType AsType a
ttoken) TextEnvelope
te
    (DecoderError -> TextEnvelopeError)
-> Either DecoderError a -> Either TextEnvelopeError a
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first DecoderError -> TextEnvelopeError
TextEnvelopeDecodeError (Either DecoderError a -> Either TextEnvelopeError a)
-> Either DecoderError a -> Either TextEnvelopeError a
forall a b. (a -> b) -> a -> b
$
      AsType a -> ByteString -> Either DecoderError a
forall a.
SerialiseAsCBOR a =>
AsType a -> ByteString -> Either DecoderError a
deserialiseFromCBOR AsType a
ttoken (TextEnvelope -> ByteString
teRawCBOR TextEnvelope
te) --TODO: You have switched from CBOR to JSON


deserialiseFromTextEnvelopeAnyOf :: [FromSomeType HasTextEnvelope b]
                                 -> TextEnvelope
                                 -> Either TextEnvelopeError b
deserialiseFromTextEnvelopeAnyOf :: [FromSomeType HasTextEnvelope b]
-> TextEnvelope -> Either TextEnvelopeError b
deserialiseFromTextEnvelopeAnyOf [FromSomeType HasTextEnvelope b]
types TextEnvelope
te =
    case (FromSomeType HasTextEnvelope b -> Bool)
-> [FromSomeType HasTextEnvelope b]
-> Maybe (FromSomeType HasTextEnvelope b)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
List.find FromSomeType HasTextEnvelope b -> Bool
matching [FromSomeType HasTextEnvelope b]
types of
      Maybe (FromSomeType HasTextEnvelope b)
Nothing ->
        TextEnvelopeError -> Either TextEnvelopeError b
forall a b. a -> Either a b
Left ([TextEnvelopeType] -> TextEnvelopeType -> TextEnvelopeError
TextEnvelopeTypeError [TextEnvelopeType]
expectedTypes TextEnvelopeType
actualType)

      Just (FromSomeType AsType a
ttoken a -> b
f) ->
        (DecoderError -> TextEnvelopeError)
-> Either DecoderError b -> Either TextEnvelopeError b
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first DecoderError -> TextEnvelopeError
TextEnvelopeDecodeError (Either DecoderError b -> Either TextEnvelopeError b)
-> Either DecoderError b -> Either TextEnvelopeError b
forall a b. (a -> b) -> a -> b
$
          a -> b
f (a -> b) -> Either DecoderError a -> Either DecoderError b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AsType a -> ByteString -> Either DecoderError a
forall a.
SerialiseAsCBOR a =>
AsType a -> ByteString -> Either DecoderError a
deserialiseFromCBOR AsType a
ttoken (TextEnvelope -> ByteString
teRawCBOR TextEnvelope
te)
  where
    actualType :: TextEnvelopeType
actualType    = TextEnvelope -> TextEnvelopeType
teType TextEnvelope
te
    expectedTypes :: [TextEnvelopeType]
expectedTypes = [ AsType a -> TextEnvelopeType
forall a. HasTextEnvelope a => AsType a -> TextEnvelopeType
textEnvelopeType AsType a
ttoken
                    | FromSomeType AsType a
ttoken a -> b
_f <- [FromSomeType HasTextEnvelope b]
types ]

    matching :: FromSomeType HasTextEnvelope b -> Bool
matching (FromSomeType AsType a
ttoken a -> b
_f) = TextEnvelopeType
actualType TextEnvelopeType -> TextEnvelopeType -> Bool
forall a. Eq a => a -> a -> Bool
== AsType a -> TextEnvelopeType
forall a. HasTextEnvelope a => AsType a -> TextEnvelopeType
textEnvelopeType AsType a
ttoken

writeFileWithOwnerPermissions
  :: FilePath
  -> LBS.ByteString
  -> IO (Either (FileError ()) ())
#ifdef UNIX
-- On a unix based system, we grab a file descriptor and set ourselves as owner.
-- Since we're holding the file descriptor at this point, we can be sure that
-- what we're about to write to is owned by us if an error didn't occur.
writeFileWithOwnerPermissions :: String -> ByteString -> IO (Either (FileError ()) ())
writeFileWithOwnerPermissions String
path ByteString
a = do
    UserID
user <- IO UserID
getRealUserID
    Either IOException Fd
ownedFile <- IO Fd -> IO (Either IOException Fd)
forall e a. Exception e => IO a -> IO (Either e a)
try (IO Fd -> IO (Either IOException Fd))
-> IO Fd -> IO (Either IOException Fd)
forall a b. (a -> b) -> a -> b
$
      -- We only close the FD on error here, otherwise we let it leak out, since
      -- it will be immediately turned into a Handle (which will be closed when
      -- the Handle is closed)
      IO Fd -> (Fd -> IO ()) -> (Fd -> IO Fd) -> IO Fd
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracketOnError
        (String -> OpenMode -> Maybe FileMode -> OpenFileFlags -> IO Fd
openFd String
path OpenMode
WriteOnly (FileMode -> Maybe FileMode
forall a. a -> Maybe a
Just FileMode
ownerModes) OpenFileFlags
defaultFileFlags)
        Fd -> IO ()
closeFd
        (\Fd
fd -> Fd -> UserID -> GroupID -> IO ()
setFdOwnerAndGroup Fd
fd UserID
user (-GroupID
1) IO () -> IO Fd -> IO Fd
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Fd -> IO Fd
forall (f :: * -> *) a. Applicative f => a -> f a
pure Fd
fd)
    case Either IOException Fd
ownedFile of
      Left (IOException
err :: IOException) -> do
        Either (FileError ()) () -> IO (Either (FileError ()) ())
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
$ String -> IOException -> FileError ()
forall e. String -> IOException -> FileError e
FileIOError String
path IOException
err
      Right Fd
fd -> do
        IO Handle
-> (Handle -> IO ())
-> (Handle -> IO (Either (FileError ()) ()))
-> IO (Either (FileError ()) ())
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
          (Fd -> IO Handle
fdToHandle Fd
fd)
          Handle -> IO ()
hClose
          (\Handle
handle -> 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
$ (IOException -> FileError ())
-> IO () -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a.
MonadIO m =>
(IOException -> x) -> IO a -> ExceptT x m a
handleIOExceptT (String -> IOException -> FileError ()
forall e. String -> IOException -> FileError e
FileIOError String
path) (IO () -> ExceptT (FileError ()) IO ())
-> IO () -> ExceptT (FileError ()) IO ()
forall a b. (a -> b) -> a -> b
$ Handle -> ByteString -> IO ()
LBS.hPut Handle
handle ByteString
a)
#else
-- On something other than unix, we make a _new_ file, and since we created it,
-- we must own it. We then place it at the target location. Unfortunately this
-- won't work correctly with pseudo-files.
writeFileWithOwnerPermissions targetPath a =
    bracketOnError
      (openTempFile targetDir $ targetFile <.> "tmp")
      (\(tmpPath, fHandle) -> do
        hClose fHandle >> removeFile tmpPath
        return . Left $ FileErrorTempFile targetPath tmpPath fHandle)
      (\(tmpPath, fHandle) -> do
          LBS.hPut fHandle a
          hClose fHandle
          renameFile tmpPath targetPath
          return $ Right ())
  where
    (targetDir, targetFile) = splitFileName targetPath
#endif

writeFileTextEnvelope :: HasTextEnvelope a
                      => FilePath
                      -> Maybe TextEnvelopeDescr
                      -> a
                      -> IO (Either (FileError ()) ())
writeFileTextEnvelope :: String
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelope String
path Maybe TextEnvelopeDescr
mbDescr a
a =
    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
      (IOException -> FileError ())
-> IO () -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a.
MonadIO m =>
(IOException -> x) -> IO a -> ExceptT x m a
handleIOExceptT (String -> IOException -> FileError ()
forall e. String -> IOException -> FileError e
FileIOError String
path) (IO () -> ExceptT (FileError ()) IO ())
-> IO () -> ExceptT (FileError ()) IO ()
forall a b. (a -> b) -> a -> b
$ String -> ByteString -> IO ()
LBS.writeFile String
path ByteString
content
  where
    content :: ByteString
content = Maybe TextEnvelopeDescr -> a -> ByteString
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
mbDescr a
a


writeFileTextEnvelopeWithOwnerPermissions
  :: HasTextEnvelope a
  => FilePath
  -> Maybe TextEnvelopeDescr
  -> a
  -> IO (Either (FileError ()) ())
writeFileTextEnvelopeWithOwnerPermissions :: String
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelopeWithOwnerPermissions String
targetPath Maybe TextEnvelopeDescr
mbDescr a
a =
  String -> ByteString -> IO (Either (FileError ()) ())
writeFileWithOwnerPermissions String
targetPath ByteString
content
 where
  content :: ByteString
content = Maybe TextEnvelopeDescr -> a -> ByteString
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
mbDescr a
a


textEnvelopeToJSON :: HasTextEnvelope a =>  Maybe TextEnvelopeDescr -> a -> LBS.ByteString
textEnvelopeToJSON :: Maybe TextEnvelopeDescr -> a -> ByteString
textEnvelopeToJSON Maybe TextEnvelopeDescr
mbDescr a
a  =
  Config -> TextEnvelope -> ByteString
forall a. ToJSON a => Config -> a -> ByteString
encodePretty' Config
textEnvelopeJSONConfig (Maybe TextEnvelopeDescr -> a -> TextEnvelope
forall a.
HasTextEnvelope a =>
Maybe TextEnvelopeDescr -> a -> TextEnvelope
serialiseToTextEnvelope Maybe TextEnvelopeDescr
mbDescr a
a) ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"\n"

readFileTextEnvelope :: HasTextEnvelope a
                     => AsType a
                     -> FilePath
                     -> IO (Either (FileError TextEnvelopeError) a)
readFileTextEnvelope :: AsType a -> String -> IO (Either (FileError TextEnvelopeError) a)
readFileTextEnvelope AsType a
ttoken String
path =
    ExceptT (FileError TextEnvelopeError) IO a
-> IO (Either (FileError TextEnvelopeError) a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT (FileError TextEnvelopeError) IO a
 -> IO (Either (FileError TextEnvelopeError) a))
-> ExceptT (FileError TextEnvelopeError) IO a
-> IO (Either (FileError TextEnvelopeError) a)
forall a b. (a -> b) -> a -> b
$ do
      ByteString
content <- (IOException -> FileError TextEnvelopeError)
-> IO ByteString
-> ExceptT (FileError TextEnvelopeError) IO ByteString
forall (m :: * -> *) x a.
MonadIO m =>
(IOException -> x) -> IO a -> ExceptT x m a
handleIOExceptT (String -> IOException -> FileError TextEnvelopeError
forall e. String -> IOException -> FileError e
FileIOError String
path) (IO ByteString
 -> ExceptT (FileError TextEnvelopeError) IO ByteString)
-> IO ByteString
-> ExceptT (FileError TextEnvelopeError) IO ByteString
forall a b. (a -> b) -> a -> b
$ String -> IO ByteString
readFileBlocking String
path
      (TextEnvelopeError -> FileError TextEnvelopeError)
-> ExceptT TextEnvelopeError IO a
-> ExceptT (FileError TextEnvelopeError) IO a
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT (String -> TextEnvelopeError -> FileError TextEnvelopeError
forall e. String -> e -> FileError e
FileError String
path) (ExceptT TextEnvelopeError IO a
 -> ExceptT (FileError TextEnvelopeError) IO a)
-> ExceptT TextEnvelopeError IO a
-> ExceptT (FileError TextEnvelopeError) IO a
forall a b. (a -> b) -> a -> b
$ Either TextEnvelopeError a -> ExceptT TextEnvelopeError IO a
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither (Either TextEnvelopeError a -> ExceptT TextEnvelopeError IO a)
-> Either TextEnvelopeError a -> ExceptT TextEnvelopeError IO a
forall a b. (a -> b) -> a -> b
$ do
        TextEnvelope
te <- (String -> TextEnvelopeError)
-> Either String TextEnvelope
-> Either TextEnvelopeError TextEnvelope
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first String -> TextEnvelopeError
TextEnvelopeAesonDecodeError (Either String TextEnvelope
 -> Either TextEnvelopeError TextEnvelope)
-> Either String TextEnvelope
-> Either TextEnvelopeError TextEnvelope
forall a b. (a -> b) -> a -> b
$ ByteString -> Either String TextEnvelope
forall a. FromJSON a => ByteString -> Either String a
Aeson.eitherDecodeStrict' ByteString
content
        AsType a -> TextEnvelope -> Either TextEnvelopeError a
forall a.
HasTextEnvelope a =>
AsType a -> TextEnvelope -> Either TextEnvelopeError a
deserialiseFromTextEnvelope AsType a
ttoken TextEnvelope
te


readFileTextEnvelopeAnyOf :: [FromSomeType HasTextEnvelope b]
                          -> FilePath
                          -> IO (Either (FileError TextEnvelopeError) b)
readFileTextEnvelopeAnyOf :: [FromSomeType HasTextEnvelope b]
-> String -> IO (Either (FileError TextEnvelopeError) b)
readFileTextEnvelopeAnyOf [FromSomeType HasTextEnvelope b]
types String
path =
    ExceptT (FileError TextEnvelopeError) IO b
-> IO (Either (FileError TextEnvelopeError) b)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT (FileError TextEnvelopeError) IO b
 -> IO (Either (FileError TextEnvelopeError) b))
-> ExceptT (FileError TextEnvelopeError) IO b
-> IO (Either (FileError TextEnvelopeError) b)
forall a b. (a -> b) -> a -> b
$ do
      ByteString
content <- (IOException -> FileError TextEnvelopeError)
-> IO ByteString
-> ExceptT (FileError TextEnvelopeError) IO ByteString
forall (m :: * -> *) x a.
MonadIO m =>
(IOException -> x) -> IO a -> ExceptT x m a
handleIOExceptT (String -> IOException -> FileError TextEnvelopeError
forall e. String -> IOException -> FileError e
FileIOError String
path) (IO ByteString
 -> ExceptT (FileError TextEnvelopeError) IO ByteString)
-> IO ByteString
-> ExceptT (FileError TextEnvelopeError) IO ByteString
forall a b. (a -> b) -> a -> b
$ String -> IO ByteString
readFileBlocking String
path
      (TextEnvelopeError -> FileError TextEnvelopeError)
-> ExceptT TextEnvelopeError IO b
-> ExceptT (FileError TextEnvelopeError) IO b
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT (String -> TextEnvelopeError -> FileError TextEnvelopeError
forall e. String -> e -> FileError e
FileError String
path) (ExceptT TextEnvelopeError IO b
 -> ExceptT (FileError TextEnvelopeError) IO b)
-> ExceptT TextEnvelopeError IO b
-> ExceptT (FileError TextEnvelopeError) IO b
forall a b. (a -> b) -> a -> b
$ Either TextEnvelopeError b -> ExceptT TextEnvelopeError IO b
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither (Either TextEnvelopeError b -> ExceptT TextEnvelopeError IO b)
-> Either TextEnvelopeError b -> ExceptT TextEnvelopeError IO b
forall a b. (a -> b) -> a -> b
$ do
        TextEnvelope
te <- (String -> TextEnvelopeError)
-> Either String TextEnvelope
-> Either TextEnvelopeError TextEnvelope
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first String -> TextEnvelopeError
TextEnvelopeAesonDecodeError (Either String TextEnvelope
 -> Either TextEnvelopeError TextEnvelope)
-> Either String TextEnvelope
-> Either TextEnvelopeError TextEnvelope
forall a b. (a -> b) -> a -> b
$ ByteString -> Either String TextEnvelope
forall a. FromJSON a => ByteString -> Either String a
Aeson.eitherDecodeStrict' ByteString
content
        [FromSomeType HasTextEnvelope b]
-> TextEnvelope -> Either TextEnvelopeError b
forall b.
[FromSomeType HasTextEnvelope b]
-> TextEnvelope -> Either TextEnvelopeError b
deserialiseFromTextEnvelopeAnyOf [FromSomeType HasTextEnvelope b]
types TextEnvelope
te


readTextEnvelopeFromFile :: FilePath
                         -> IO (Either (FileError TextEnvelopeError) TextEnvelope)
readTextEnvelopeFromFile :: String -> IO (Either (FileError TextEnvelopeError) TextEnvelope)
readTextEnvelopeFromFile String
path =
  ExceptT (FileError TextEnvelopeError) IO TextEnvelope
-> IO (Either (FileError TextEnvelopeError) TextEnvelope)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT (FileError TextEnvelopeError) IO TextEnvelope
 -> IO (Either (FileError TextEnvelopeError) TextEnvelope))
-> ExceptT (FileError TextEnvelopeError) IO TextEnvelope
-> IO (Either (FileError TextEnvelopeError) TextEnvelope)
forall a b. (a -> b) -> a -> b
$ do
    ByteString
bs <- (IOException -> FileError TextEnvelopeError)
-> IO ByteString
-> ExceptT (FileError TextEnvelopeError) IO ByteString
forall (m :: * -> *) x a.
MonadIO m =>
(IOException -> x) -> IO a -> ExceptT x m a
handleIOExceptT (String -> IOException -> FileError TextEnvelopeError
forall e. String -> IOException -> FileError e
FileIOError String
path) (IO ByteString
 -> ExceptT (FileError TextEnvelopeError) IO ByteString)
-> IO ByteString
-> ExceptT (FileError TextEnvelopeError) IO ByteString
forall a b. (a -> b) -> a -> b
$
            String -> IO ByteString
readFileBlocking String
path
    (String -> FileError TextEnvelopeError)
-> ExceptT String IO TextEnvelope
-> ExceptT (FileError TextEnvelopeError) IO TextEnvelope
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT (String -> TextEnvelopeError -> FileError TextEnvelopeError
forall e. String -> e -> FileError e
FileError String
path (TextEnvelopeError -> FileError TextEnvelopeError)
-> (String -> TextEnvelopeError)
-> String
-> FileError TextEnvelopeError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> TextEnvelopeError
TextEnvelopeAesonDecodeError)
      (ExceptT String IO TextEnvelope
 -> ExceptT (FileError TextEnvelopeError) IO TextEnvelope)
-> (Either String TextEnvelope -> ExceptT String IO TextEnvelope)
-> Either String TextEnvelope
-> ExceptT (FileError TextEnvelopeError) IO TextEnvelope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either String TextEnvelope -> ExceptT String IO TextEnvelope
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither (Either String TextEnvelope
 -> ExceptT (FileError TextEnvelopeError) IO TextEnvelope)
-> Either String TextEnvelope
-> ExceptT (FileError TextEnvelopeError) IO TextEnvelope
forall a b. (a -> b) -> a -> b
$ ByteString -> Either String TextEnvelope
forall a. FromJSON a => ByteString -> Either String a
Aeson.eitherDecodeStrict' ByteString
bs


readTextEnvelopeOfTypeFromFile
  :: TextEnvelopeType
  -> FilePath
  -> IO (Either (FileError TextEnvelopeError) TextEnvelope)
readTextEnvelopeOfTypeFromFile :: TextEnvelopeType
-> String -> IO (Either (FileError TextEnvelopeError) TextEnvelope)
readTextEnvelopeOfTypeFromFile TextEnvelopeType
expectedType String
path =
  ExceptT (FileError TextEnvelopeError) IO TextEnvelope
-> IO (Either (FileError TextEnvelopeError) TextEnvelope)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT (FileError TextEnvelopeError) IO TextEnvelope
 -> IO (Either (FileError TextEnvelopeError) TextEnvelope))
-> ExceptT (FileError TextEnvelopeError) IO TextEnvelope
-> IO (Either (FileError TextEnvelopeError) TextEnvelope)
forall a b. (a -> b) -> a -> b
$ do
    TextEnvelope
te <- IO (Either (FileError TextEnvelopeError) TextEnvelope)
-> ExceptT (FileError TextEnvelopeError) IO TextEnvelope
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (String -> IO (Either (FileError TextEnvelopeError) TextEnvelope)
readTextEnvelopeFromFile String
path)
    (TextEnvelopeError -> FileError TextEnvelopeError)
-> ExceptT TextEnvelopeError IO ()
-> ExceptT (FileError TextEnvelopeError) IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT (String -> TextEnvelopeError -> FileError TextEnvelopeError
forall e. String -> e -> FileError e
FileError String
path) (ExceptT TextEnvelopeError IO ()
 -> ExceptT (FileError TextEnvelopeError) IO ())
-> ExceptT TextEnvelopeError IO ()
-> ExceptT (FileError TextEnvelopeError) IO ()
forall a b. (a -> b) -> a -> b
$ Either TextEnvelopeError () -> ExceptT TextEnvelopeError IO ()
forall (m :: * -> *) x a. Monad m => Either x a -> ExceptT x m a
hoistEither (Either TextEnvelopeError () -> ExceptT TextEnvelopeError IO ())
-> Either TextEnvelopeError () -> ExceptT TextEnvelopeError IO ()
forall a b. (a -> b) -> a -> b
$
      TextEnvelopeType -> TextEnvelope -> Either TextEnvelopeError ()
expectTextEnvelopeOfType TextEnvelopeType
expectedType TextEnvelope
te
    TextEnvelope
-> ExceptT (FileError TextEnvelopeError) IO TextEnvelope
forall (m :: * -> *) a. Monad m => a -> m a
return TextEnvelope
te