Skip to content

Commit

Permalink
Check for overflow in Jörmungandr.Binary
Browse files Browse the repository at this point in the history
- Particulary in encoders (putX)
- Somewhat for decoders (getX)
  • Loading branch information
Anviking committed Jul 1, 2019
1 parent 0129cb2 commit 96d09ee
Showing 1 changed file with 12 additions and 6 deletions.
18 changes: 12 additions & 6 deletions lib/jormungandr/src/Cardano/Wallet/Jormungandr/Binary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,7 @@ import Cardano.Wallet.Primitive.Types
import Control.Applicative
( many )
import Control.Monad
( replicateM )
( replicateM, unless )
import Data.Binary.Get
( Get
, bytesRead
Expand Down Expand Up @@ -133,7 +133,7 @@ getBlockHeader = label "getBlockHeader" $
version <- getWord16be
contentSize <- getWord32be
slotEpoch <- fromIntegral <$> getWord32be
slotId <- fromIntegral <$> getWord32be
slotId <- toEnum . fromEnum <$> getWord32be
chainLength <- getWord32be
contentHash <- Hash <$> getByteString 32 -- or 256 bits
parentHeaderHash <- Hash <$> getByteString 32
Expand Down Expand Up @@ -259,9 +259,11 @@ getTransaction = label "getTransaction" $ do
putSignedTx :: (Tx, [TxWitness]) -> Put
putSignedTx (tx@(Tx inputs outputs), witnesses) = withSizeHeader16be $ do
putWord8 2
putWord8 $ fromIntegral $ length inputs
putWord8 $ fromIntegral $ length outputs
putWord8 $ toEnum $ length inputs
putWord8 $ toEnum $ length outputs
putTx tx
unless (length inputs == length witnesses) $
fail "number of witnesses must equal number of inputs"
mapM_ putWitness witnesses
where
-- Assumes the `TxWitness` has been faithfully constructed
Expand All @@ -272,13 +274,17 @@ putSignedTx (tx@(Tx inputs outputs), witnesses) = withSizeHeader16be $ do

putTx :: Tx -> Put
putTx (Tx inputs outputs) = do
unless (length inputs <= fromIntegral (maxBound :: Word8)) $
fail "number of inputs cannot be greater than 255"
unless (length outputs <= fromIntegral (maxBound :: Word8)) $
fail "number of outputs cannot be greater than 255"
mapM_ putInput inputs
mapM_ putOutput outputs
where
putInput (TxIn inputId inputIx, coin) = do
-- NOTE: special value 0xff indicates account spending
-- only old utxo/address scheme supported for now
putWord8 $ fromIntegral inputIx
putWord8 . toEnum . fromEnum $ inputIx
putWord64be $ getCoin coin
putByteString $ getHash inputId

Expand Down Expand Up @@ -454,7 +460,7 @@ isolatePut l x = do
withSizeHeader16be :: Put -> Put
withSizeHeader16be x = do
let bs = BL.toStrict $ runPut x
putWord16be (fromIntegral $ BS.length bs)
putWord16be (toEnum $ BS.length bs)
putByteString bs

{-------------------------------------------------------------------------------
Expand Down

0 comments on commit 96d09ee

Please sign in to comment.