Skip to content

Commit

Permalink
Add C.D.Compat.Binary.{encodeFile,decodeFileOrFail'}
Browse files Browse the repository at this point in the history
  • Loading branch information
hvr committed Sep 20, 2016
1 parent f91e65a commit 31eddce
Showing 1 changed file with 17 additions and 2 deletions.
19 changes: 17 additions & 2 deletions Cabal/Distribution/Compat/Binary.hs
Expand Up @@ -9,11 +9,12 @@

module Distribution.Compat.Binary
( decodeOrFailIO
, decodeFileOrFail'
#if __GLASGOW_HASKELL__ >= 708 || MIN_VERSION_binary(0,7,0)
, module Data.Binary
#else
, Binary(..)
, decode, encode
, decode, encode, encodeFile
#endif
) where

Expand All @@ -33,15 +34,21 @@ import Data.ByteString.Lazy (ByteString)

import Data.Binary

-- | Lazily reconstruct a value previously written to a file.
decodeFileOrFail' :: Binary a => FilePath -> IO (Either String a)
decodeFileOrFail' f = either (Left . snd) Right `fmap` decodeFileOrFail f

#else

import Data.Binary.Get
import Data.Binary.Put
import qualified Data.ByteString.Lazy as BSL

import Distribution.Compat.Binary.Class
import Distribution.Compat.Binary.Generic ()

-- | Decode a value from a lazy ByteString, reconstructing the original structure.
-- | Decode a value from a lazy ByteString, reconstructing the
-- original structure.
--
decode :: Binary a => ByteString -> a
decode = runGet get
Expand All @@ -52,6 +59,14 @@ encode :: Binary a => a -> ByteString
encode = runPut . put
{-# INLINE encode #-}

-- | Lazily reconstruct a value previously written to a file.
decodeFileOrFail' :: Binary a => FilePath -> IO (Either String a)
decodeFileOrFail' f = decodeOrFailIO =<< BSL.readFile f

-- | Lazily serialise a value to a file
encodeFile :: Binary a => FilePath -> a -> IO ()
encodeFile f = BSL.writeFile f . encode

#endif

decodeOrFailIO :: Binary a => ByteString -> IO (Either String a)
Expand Down

0 comments on commit 31eddce

Please sign in to comment.