Skip to content

Commit

Permalink
Merge pull request #193 from fieldstrength/map-bug
Browse files Browse the repository at this point in the history
Fix Map decoding in presence of optional long byte-length marker
  • Loading branch information
HuwCampbell authored Nov 10, 2023
2 parents d363d5e + dac200b commit eb1e45e
Showing 1 changed file with 16 additions and 6 deletions.
22 changes: 16 additions & 6 deletions src/Data/Avro/Encoding/FromAvro.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ module Data.Avro.Encoding.FromAvro
where

import Control.DeepSeq (NFData)
import Control.Monad (forM, replicateM)
import Control.Monad (forM, replicateM, void, when)
import Control.Monad.Identity (Identity (..))
import qualified Data.Avro.Internal.Get as Get
import Data.Avro.Internal.Time
Expand Down Expand Up @@ -195,7 +195,6 @@ instance FromAvro Time.LocalTime where
Right $ millisToLocalTime (toInteger n)
fromAvro x = Left ("Unable to decode LocalTime from: " <> show (describeValue x))
{-# INLINE fromAvro #-}


instance FromAvro a => FromAvro [a] where
fromAvro (Array vec) = mapM fromAvro $ V.toList vec
Expand Down Expand Up @@ -301,22 +300,33 @@ getField env sch = case sch of
v <- getField env t
pure $ Union sch ix v


-- | Read a Map from blocks of KV pairs
getKVBlocks :: HashMap Schema.TypeName ReadSchema -> ReadSchema -> Get [[(Text, Value)]]
getKVBlocks env t = do
blockLength <- abs <$> Get.getLong
if blockLength == 0 then
lengthIndicator <- Get.getLong
if lengthIndicator == 0 then
return []
else do
-- When the block's count is negative, its absolute value is used, and the count is followed immediately by a
-- long block size indicating the number of bytes in the block.
when (lengthIndicator < 0) $ void Get.getLong -- number of bytes in block (ignored)
let blockLength = abs lengthIndicator
vs <- replicateM (fromIntegral blockLength) ((,) <$> Get.getString <*> getField env t)
(vs:) <$> getKVBlocks env t
{-# INLINE getKVBlocks #-}

-- | Read an array from blocks.
getBlocksOf :: HashMap Schema.TypeName ReadSchema -> ReadSchema -> Get [[Value]]
getBlocksOf env t = do
blockLength <- abs <$> Get.getLong
if blockLength == 0 then
lengthIndicator <- Get.getLong
if lengthIndicator == 0 then
return []
else do
-- When the block's count is negative, its absolute value is used, and the count is followed immediately by a
-- long block size indicating the number of bytes in the block.
when (lengthIndicator < 0) $ void Get.getLong -- number of bytes in block (ignored)
let blockLength = abs lengthIndicator
vs <- replicateM (fromIntegral blockLength) (getField env t)
(vs:) <$> getBlocksOf env t

Expand Down

0 comments on commit eb1e45e

Please sign in to comment.