{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE OverloadedStrings #-}
module Cardano.Chain.UTxO.Compact (
CompactTxIn (..),
toCompactTxIn,
fromCompactTxIn,
CompactTxId,
toCompactTxId,
fromCompactTxId,
CompactTxOut (..),
toCompactTxOut,
fromCompactTxOut,
)
where
import Cardano.Chain.Common.Compact (
CompactAddress,
fromCompactAddress,
toCompactAddress,
)
import Cardano.Chain.Common.Lovelace (Lovelace)
import Cardano.Chain.UTxO.Tx (TxId, TxIn (..), TxOut (..))
import Cardano.Crypto.Hashing (hashToBytes, unsafeHashFromBytes)
import Cardano.HeapWords (HeapWords (..), heapWordsUnpacked)
import Cardano.Ledger.Binary (
DecCBOR (..),
EncCBOR (..),
FromCBOR (..),
ToCBOR (..),
encodeListLen,
enforceSize,
fromByronCBOR,
toByronCBOR,
)
import Cardano.Prelude
import Data.Binary.Get (Get, getWord64le, runGet)
import Data.Binary.Put (Put, putWord64le, runPut)
import qualified Data.ByteString.Lazy as BSL (fromStrict, toStrict)
import NoThunks.Class (NoThunks (..))
data CompactTxIn
= CompactTxInUtxo
{-# UNPACK #-} !CompactTxId
{-# UNPACK #-} !Word16
deriving (CompactTxIn -> CompactTxIn -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompactTxIn -> CompactTxIn -> Bool
$c/= :: CompactTxIn -> CompactTxIn -> Bool
== :: CompactTxIn -> CompactTxIn -> Bool
$c== :: CompactTxIn -> CompactTxIn -> Bool
Eq, Eq CompactTxIn
CompactTxIn -> CompactTxIn -> Bool
CompactTxIn -> CompactTxIn -> Ordering
CompactTxIn -> CompactTxIn -> CompactTxIn
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CompactTxIn -> CompactTxIn -> CompactTxIn
$cmin :: CompactTxIn -> CompactTxIn -> CompactTxIn
max :: CompactTxIn -> CompactTxIn -> CompactTxIn
$cmax :: CompactTxIn -> CompactTxIn -> CompactTxIn
>= :: CompactTxIn -> CompactTxIn -> Bool
$c>= :: CompactTxIn -> CompactTxIn -> Bool
> :: CompactTxIn -> CompactTxIn -> Bool
$c> :: CompactTxIn -> CompactTxIn -> Bool
<= :: CompactTxIn -> CompactTxIn -> Bool
$c<= :: CompactTxIn -> CompactTxIn -> Bool
< :: CompactTxIn -> CompactTxIn -> Bool
$c< :: CompactTxIn -> CompactTxIn -> Bool
compare :: CompactTxIn -> CompactTxIn -> Ordering
$ccompare :: CompactTxIn -> CompactTxIn -> Ordering
Ord, forall x. Rep CompactTxIn x -> CompactTxIn
forall x. CompactTxIn -> Rep CompactTxIn x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CompactTxIn x -> CompactTxIn
$cfrom :: forall x. CompactTxIn -> Rep CompactTxIn x
Generic, Int -> CompactTxIn -> ShowS
[CompactTxIn] -> ShowS
CompactTxIn -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompactTxIn] -> ShowS
$cshowList :: [CompactTxIn] -> ShowS
show :: CompactTxIn -> String
$cshow :: CompactTxIn -> String
showsPrec :: Int -> CompactTxIn -> ShowS
$cshowsPrec :: Int -> CompactTxIn -> ShowS
Show)
deriving anyclass (CompactTxIn -> ()
forall a. (a -> ()) -> NFData a
rnf :: CompactTxIn -> ()
$crnf :: CompactTxIn -> ()
NFData, Context -> CompactTxIn -> IO (Maybe ThunkInfo)
Proxy CompactTxIn -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy CompactTxIn -> String
$cshowTypeOf :: Proxy CompactTxIn -> String
wNoThunks :: Context -> CompactTxIn -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> CompactTxIn -> IO (Maybe ThunkInfo)
noThunks :: Context -> CompactTxIn -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> CompactTxIn -> IO (Maybe ThunkInfo)
NoThunks)
instance HeapWords CompactTxIn where
heapWords :: CompactTxIn -> Int
heapWords CompactTxIn
_ =
Int
6
instance ToCBOR CompactTxIn where
toCBOR :: CompactTxIn -> Encoding
toCBOR = forall a. EncCBOR a => a -> Encoding
toByronCBOR
instance FromCBOR CompactTxIn where
fromCBOR :: forall s. Decoder s CompactTxIn
fromCBOR = forall a s. DecCBOR a => Decoder s a
fromByronCBOR
instance DecCBOR CompactTxIn where
decCBOR :: forall s. Decoder s CompactTxIn
decCBOR = do
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"CompactTxIn" Int
2
CompactTxId -> Word16 -> CompactTxIn
CompactTxInUtxo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a s. DecCBOR a => Decoder s a
decCBOR
instance EncCBOR CompactTxIn where
encCBOR :: CompactTxIn -> Encoding
encCBOR (CompactTxInUtxo CompactTxId
txId Word16
txIndex) =
Word -> Encoding
encodeListLen Word
2
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR CompactTxId
txId
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR Word16
txIndex
toCompactTxIn :: TxIn -> CompactTxIn
toCompactTxIn :: TxIn -> CompactTxIn
toCompactTxIn (TxInUtxo TxId
txId Word16
txIndex) =
CompactTxId -> Word16 -> CompactTxIn
CompactTxInUtxo (TxId -> CompactTxId
toCompactTxId TxId
txId) Word16
txIndex
fromCompactTxIn :: CompactTxIn -> TxIn
fromCompactTxIn :: CompactTxIn -> TxIn
fromCompactTxIn (CompactTxInUtxo CompactTxId
compactTxId Word16
txIndex) =
TxId -> Word16 -> TxIn
TxInUtxo (CompactTxId -> TxId
fromCompactTxId CompactTxId
compactTxId) Word16
txIndex
data CompactTxId
= CompactTxId
{-# UNPACK #-} !Word64
{-# UNPACK #-} !Word64
{-# UNPACK #-} !Word64
{-# UNPACK #-} !Word64
deriving (CompactTxId -> CompactTxId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompactTxId -> CompactTxId -> Bool
$c/= :: CompactTxId -> CompactTxId -> Bool
== :: CompactTxId -> CompactTxId -> Bool
$c== :: CompactTxId -> CompactTxId -> Bool
Eq, forall x. Rep CompactTxId x -> CompactTxId
forall x. CompactTxId -> Rep CompactTxId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CompactTxId x -> CompactTxId
$cfrom :: forall x. CompactTxId -> Rep CompactTxId x
Generic, Eq CompactTxId
CompactTxId -> CompactTxId -> Bool
CompactTxId -> CompactTxId -> Ordering
CompactTxId -> CompactTxId -> CompactTxId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CompactTxId -> CompactTxId -> CompactTxId
$cmin :: CompactTxId -> CompactTxId -> CompactTxId
max :: CompactTxId -> CompactTxId -> CompactTxId
$cmax :: CompactTxId -> CompactTxId -> CompactTxId
>= :: CompactTxId -> CompactTxId -> Bool
$c>= :: CompactTxId -> CompactTxId -> Bool
> :: CompactTxId -> CompactTxId -> Bool
$c> :: CompactTxId -> CompactTxId -> Bool
<= :: CompactTxId -> CompactTxId -> Bool
$c<= :: CompactTxId -> CompactTxId -> Bool
< :: CompactTxId -> CompactTxId -> Bool
$c< :: CompactTxId -> CompactTxId -> Bool
compare :: CompactTxId -> CompactTxId -> Ordering
$ccompare :: CompactTxId -> CompactTxId -> Ordering
Ord, Int -> CompactTxId -> ShowS
[CompactTxId] -> ShowS
CompactTxId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompactTxId] -> ShowS
$cshowList :: [CompactTxId] -> ShowS
show :: CompactTxId -> String
$cshow :: CompactTxId -> String
showsPrec :: Int -> CompactTxId -> ShowS
$cshowsPrec :: Int -> CompactTxId -> ShowS
Show)
deriving anyclass (CompactTxId -> ()
forall a. (a -> ()) -> NFData a
rnf :: CompactTxId -> ()
$crnf :: CompactTxId -> ()
NFData, Context -> CompactTxId -> IO (Maybe ThunkInfo)
Proxy CompactTxId -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy CompactTxId -> String
$cshowTypeOf :: Proxy CompactTxId -> String
wNoThunks :: Context -> CompactTxId -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> CompactTxId -> IO (Maybe ThunkInfo)
noThunks :: Context -> CompactTxId -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> CompactTxId -> IO (Maybe ThunkInfo)
NoThunks)
instance HeapWords CompactTxId where
heapWords :: CompactTxId -> Int
heapWords CompactTxId
_ =
Int
5
instance ToCBOR CompactTxId where
toCBOR :: CompactTxId -> Encoding
toCBOR = forall a. EncCBOR a => a -> Encoding
toByronCBOR
instance FromCBOR CompactTxId where
fromCBOR :: forall s. Decoder s CompactTxId
fromCBOR = forall a s. DecCBOR a => Decoder s a
fromByronCBOR
instance DecCBOR CompactTxId where
decCBOR :: forall s. Decoder s CompactTxId
decCBOR = do
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"CompactTxId" Int
4
Word64 -> Word64 -> Word64 -> Word64 -> CompactTxId
CompactTxId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a s. DecCBOR a => Decoder s a
decCBOR
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a s. DecCBOR a => Decoder s a
decCBOR
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a s. DecCBOR a => Decoder s a
decCBOR
instance EncCBOR CompactTxId where
encCBOR :: CompactTxId -> Encoding
encCBOR (CompactTxId Word64
a Word64
b Word64
c Word64
d) =
Word -> Encoding
encodeListLen Word
4
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR Word64
a
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR Word64
b
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR Word64
c
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR Word64
d
getCompactTxId :: Get CompactTxId
getCompactTxId :: Get CompactTxId
getCompactTxId =
Word64 -> Word64 -> Word64 -> Word64 -> CompactTxId
CompactTxId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word64
getWord64le
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word64
getWord64le
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word64
getWord64le
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word64
getWord64le
putCompactTxId :: CompactTxId -> Put
putCompactTxId :: CompactTxId -> Put
putCompactTxId (CompactTxId Word64
a Word64
b Word64
c Word64
d) =
Word64 -> Put
putWord64le Word64
a
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Word64 -> Put
putWord64le Word64
b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Word64 -> Put
putWord64le Word64
c
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Word64 -> Put
putWord64le Word64
d
toCompactTxId :: TxId -> CompactTxId
toCompactTxId :: TxId -> CompactTxId
toCompactTxId =
forall a. Get a -> ByteString -> a
runGet Get CompactTxId
getCompactTxId forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
BSL.fromStrict forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall algo a. AbstractHash algo a -> ByteString
hashToBytes
fromCompactTxId :: CompactTxId -> TxId
fromCompactTxId :: CompactTxId -> TxId
fromCompactTxId =
forall a. ByteString -> Hash a
unsafeHashFromBytes forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
BSL.toStrict forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Put -> ByteString
runPut forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. CompactTxId -> Put
putCompactTxId
data CompactTxOut
= CompactTxOut
{-# UNPACK #-} !CompactAddress
{-# UNPACK #-} !Lovelace
deriving (CompactTxOut -> CompactTxOut -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompactTxOut -> CompactTxOut -> Bool
$c/= :: CompactTxOut -> CompactTxOut -> Bool
== :: CompactTxOut -> CompactTxOut -> Bool
$c== :: CompactTxOut -> CompactTxOut -> Bool
Eq, Eq CompactTxOut
CompactTxOut -> CompactTxOut -> Bool
CompactTxOut -> CompactTxOut -> Ordering
CompactTxOut -> CompactTxOut -> CompactTxOut
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CompactTxOut -> CompactTxOut -> CompactTxOut
$cmin :: CompactTxOut -> CompactTxOut -> CompactTxOut
max :: CompactTxOut -> CompactTxOut -> CompactTxOut
$cmax :: CompactTxOut -> CompactTxOut -> CompactTxOut
>= :: CompactTxOut -> CompactTxOut -> Bool
$c>= :: CompactTxOut -> CompactTxOut -> Bool
> :: CompactTxOut -> CompactTxOut -> Bool
$c> :: CompactTxOut -> CompactTxOut -> Bool
<= :: CompactTxOut -> CompactTxOut -> Bool
$c<= :: CompactTxOut -> CompactTxOut -> Bool
< :: CompactTxOut -> CompactTxOut -> Bool
$c< :: CompactTxOut -> CompactTxOut -> Bool
compare :: CompactTxOut -> CompactTxOut -> Ordering
$ccompare :: CompactTxOut -> CompactTxOut -> Ordering
Ord, forall x. Rep CompactTxOut x -> CompactTxOut
forall x. CompactTxOut -> Rep CompactTxOut x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CompactTxOut x -> CompactTxOut
$cfrom :: forall x. CompactTxOut -> Rep CompactTxOut x
Generic, Int -> CompactTxOut -> ShowS
[CompactTxOut] -> ShowS
CompactTxOut -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompactTxOut] -> ShowS
$cshowList :: [CompactTxOut] -> ShowS
show :: CompactTxOut -> String
$cshow :: CompactTxOut -> String
showsPrec :: Int -> CompactTxOut -> ShowS
$cshowsPrec :: Int -> CompactTxOut -> ShowS
Show)
deriving anyclass (CompactTxOut -> ()
forall a. (a -> ()) -> NFData a
rnf :: CompactTxOut -> ()
$crnf :: CompactTxOut -> ()
NFData, Context -> CompactTxOut -> IO (Maybe ThunkInfo)
Proxy CompactTxOut -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy CompactTxOut -> String
$cshowTypeOf :: Proxy CompactTxOut -> String
wNoThunks :: Context -> CompactTxOut -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> CompactTxOut -> IO (Maybe ThunkInfo)
noThunks :: Context -> CompactTxOut -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> CompactTxOut -> IO (Maybe ThunkInfo)
NoThunks)
instance HeapWords CompactTxOut where
heapWords :: CompactTxOut -> Int
heapWords (CompactTxOut CompactAddress
compactAddr Lovelace
_) =
Int
3 forall a. Num a => a -> a -> a
+ forall a. HeapWords a => a -> Int
heapWordsUnpacked CompactAddress
compactAddr
instance ToCBOR CompactTxOut where
toCBOR :: CompactTxOut -> Encoding
toCBOR = forall a. EncCBOR a => a -> Encoding
toByronCBOR
instance FromCBOR CompactTxOut where
fromCBOR :: forall s. Decoder s CompactTxOut
fromCBOR = forall a s. DecCBOR a => Decoder s a
fromByronCBOR
instance DecCBOR CompactTxOut where
decCBOR :: forall s. Decoder s CompactTxOut
decCBOR = do
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"CompactTxOut" Int
2
CompactAddress -> Lovelace -> CompactTxOut
CompactTxOut
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a s. DecCBOR a => Decoder s a
decCBOR
instance EncCBOR CompactTxOut where
encCBOR :: CompactTxOut -> Encoding
encCBOR (CompactTxOut CompactAddress
compactAddr Lovelace
lovelace) =
Word -> Encoding
encodeListLen Word
2
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR CompactAddress
compactAddr
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR Lovelace
lovelace
toCompactTxOut :: TxOut -> CompactTxOut
toCompactTxOut :: TxOut -> CompactTxOut
toCompactTxOut (TxOut Address
addr Lovelace
lovelace) =
CompactAddress -> Lovelace -> CompactTxOut
CompactTxOut (Address -> CompactAddress
toCompactAddress Address
addr) Lovelace
lovelace
fromCompactTxOut :: CompactTxOut -> TxOut
fromCompactTxOut :: CompactTxOut -> TxOut
fromCompactTxOut (CompactTxOut CompactAddress
compactAddr Lovelace
lovelace) =
Address -> Lovelace -> TxOut
TxOut (CompactAddress -> Address
fromCompactAddress CompactAddress
compactAddr) Lovelace
lovelace