[Haskell-cafe] Data.Binary, Data.Text and errors

Khudyakov Alexey alexey.skladnoy at gmail.com
Mon Mar 16 06:00:20 EDT 2009


On Monday 16 March 2009 06:40:12 Alexander Dunlap wrote:
> Hi all,
>
> I have noticed that in both Data.Binary and Data.Text (which is still
> experimental, but still), the "decode" functions can be undefined
> (i.e. bottom) if they encounter malformed input.
>
> What is the preferred way to use these functions in a safe way? For
> example, if one writes data to a disk using Data.Binary and wants to
> read it back in at a later date, how can one ensure that it is valid
> so that Data.Binary does not hit an error? Or do you just have to
> catch the exception in the IO Monad?
>

I've used ErrorT monad transformer for decoding. With that it's possible to 
work around this problem. As downside one is required to do all checks and 
throw errors manually. 

It would be nice to have some kind of error handling in Data.Binary


How it was done:
> import Control.Monad.Error
> 
> -- | Get monad with applied to it Error monad transformer
> type Decoder = ErrorT String Get
> 
> -- | Subequipment data
> data SubEq = SubEq { subeqID   :: Int
>                   , subeqData :: ByteString }
>
> -- | Abort execution if function evaluates to True
> dieIf :: (a -> Bool) -> String -> a -> Decoder ()
> dieIf f err x = when (f x) (throwError err)
>
> readSubEq :: Decoder SubEq
> readSubEq = do
>   lift remaining >>= dieIf (<4) "DATE: Too short subequipment data (<4)"
>   -- Read header
>   len  <- liftM (\x -> fromIntegral $ 2*x - 4) $ lift getWord16le
>   s_id <- liftM fromIntegral $ lift getWord16le
>   lift remaining >>= dieIf (< len) "DATE: Too short subequipment data"
>   buf  <- lift $ getLazyByteString len
>   return $! SubEq s_id buf
>
> -- Actual decoding
> decodeSubEq  = runGet (runErrorT readSubEq)


More information about the Haskell-Cafe mailing list