[commit: packages/binary] master: Add since annotations (53ea7cb)
git at git.haskell.org
git at git.haskell.org
Wed Dec 16 09:43:40 UTC 2015
Repository : ssh://git@git.haskell.org/binary
On branch : master
Link : http://git.haskell.org/packages/binary.git/commitdiff/53ea7cb290d69a85b07dedfd51022c0684b2db48
>---------------------------------------------------------------
commit 53ea7cb290d69a85b07dedfd51022c0684b2db48
Author: Oleg Grenrus <oleg.grenrus at iki.fi>
Date: Fri Nov 13 07:35:25 2015 +0200
Add since annotations
>---------------------------------------------------------------
53ea7cb290d69a85b07dedfd51022c0684b2db48
src/Data/Binary.hs | 4 ++++
src/Data/Binary/Class.hs | 6 +++++-
src/Data/Binary/Get.hs | 2 ++
src/Data/Binary/Get/Internal.hs | 14 +++++++++++++-
4 files changed, 24 insertions(+), 2 deletions(-)
diff --git a/src/Data/Binary.hs b/src/Data/Binary.hs
index d5a1858..bb25ee5 100644
--- a/src/Data/Binary.hs
+++ b/src/Data/Binary.hs
@@ -180,6 +180,8 @@ decode = runGet get
-- 'Right' on success. In both cases the unconsumed input and the number of
-- consumed bytes is returned. In case of failure, a human-readable error
-- message will be returned as well.
+--
+-- /Since: 0.7.0.0/
decodeOrFail :: Binary a => L.ByteString
-> Either (L.ByteString, ByteOffset, String)
(L.ByteString, ByteOffset, a)
@@ -204,6 +206,8 @@ encodeFile f v = L.writeFile f (encode v)
-- | Decode a value from a file. In case of errors, 'error' will
-- be called with the error message.
+--
+-- /Since: 0.7.0.0/
decodeFile :: Binary a => FilePath -> IO a
decodeFile f = do
result <- decodeFileOrFail f
diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs
index 6247daf..ffb9734 100644
--- a/src/Data/Binary/Class.hs
+++ b/src/Data/Binary/Class.hs
@@ -140,6 +140,8 @@ class Binary t where
#ifdef HAS_VOID
-- Void never gets written nor reconstructed since it's impossible to have a
-- value of that type
+
+-- | /Since: 0.8.0.0/
instance Binary Void where
put = absurd
get = mzero
@@ -274,6 +276,7 @@ roll = foldl' unstep 0 . reverse
-- Fixed-size type for a subset of Natural
type NaturalWord = Word64
+-- | /Since: 0.7.3.0/
instance Binary Natural where
{-# INLINE put #-}
put n | n <= hi = do
@@ -614,6 +617,7 @@ instance (Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) wher
-- Fingerprints
#ifdef HAS_GHC_FINGERPRINT
+-- | /Since: 0.7.6.0/
instance Binary Fingerprint where
put (Fingerprint x1 x2) = do
put x1
@@ -627,7 +631,7 @@ instance Binary Fingerprint where
------------------------------------------------------------------------
-- Version
--- | /Since: binary-0.8/
+-- | /Since: 0.8.0.0/
instance Binary Version where
get = Version <$> get <*> get
put (Version br tags) = put br >> put tags
diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs
index 091a14c..de1a326 100644
--- a/src/Data/Binary/Get.hs
+++ b/src/Data/Binary/Get.hs
@@ -299,6 +299,8 @@ dropHeadChunk lbs =
-- success. In both cases any unconsumed input and the number of bytes
-- consumed is returned. In the case of failure, a human-readable
-- error message is included as well.
+--
+-- /Since: 0.6.4.0/
runGetOrFail :: Get a -> L.ByteString
-> Either (L.ByteString, ByteOffset, String) (L.ByteString, ByteOffset, a)
runGetOrFail g lbs0 = feedAll (runGetIncremental g) lbs0
diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs
index 804fde1..3669242 100644
--- a/src/Data/Binary/Get/Internal.hs
+++ b/src/Data/Binary/Get/Internal.hs
@@ -123,6 +123,7 @@ instance Applicative Get where
(<*>) = apG
{-# INLINE (<*>) #-}
+-- | /Since: 0.7.1.0/
instance MonadPlus Get where
mzero = empty
mplus = (<|>)
@@ -192,6 +193,8 @@ bytesRead = C $ \inp k -> BytesRead (fromIntegral $ B.length inp) (k inp)
-- If the given decoder fails, 'isolate' will also fail.
-- Offset from 'bytesRead' will be relative to the start of 'isolate', not the
-- absolute of the input.
+--
+-- /Since: 0.7.2.0/
isolate :: Int -- ^ The number of bytes that must be consumed
-> Get a -- ^ The decoder to isolate
-> Get a
@@ -254,6 +257,7 @@ getBytes :: Int -> Get B.ByteString
getBytes = getByteString
{-# INLINE getBytes #-}
+-- | /Since: 0.7.0.0/
instance Alternative Get where
empty = C $ \inp _ks -> Fail inp "Data.Binary.Get(Alternative).empty"
(<|>) f g = do
@@ -298,6 +302,8 @@ pushFront bs = C $ \ inp ks -> ks (B.append bs inp) ()
-- | Run the given decoder, but without consuming its input. If the given
-- decoder fails, then so will this function.
+--
+-- /Since: 0.7.0.0/
lookAhead :: Get a -> Get a
lookAhead g = do
(decoder, bs) <- runAndKeepTrack g
@@ -309,6 +315,8 @@ lookAhead g = do
-- | Run the given decoder, and only consume its input if it returns 'Just'.
-- If 'Nothing' is returned, the input will be unconsumed.
-- If the given decoder fails, then so will this function.
+--
+-- /Since: 0.7.0.0/
lookAheadM :: Get (Maybe a) -> Get (Maybe a)
lookAheadM g = do
let g' = maybe (Left ()) Right <$> g
@@ -317,6 +325,8 @@ lookAheadM g = do
-- | Run the given decoder, and only consume its input if it returns 'Right'.
-- If 'Left' is returned, the input will be unconsumed.
-- If the given decoder fails, then so will this function.
+--
+-- /Since: 0.7.1.0/
lookAheadE :: Get (Either a b) -> Get (Either a b)
lookAheadE g = do
(decoder, bs) <- runAndKeepTrack g
@@ -326,8 +336,10 @@ lookAheadE g = do
Fail inp s -> C $ \_ _ -> Fail inp s
_ -> error "Binary: impossible"
--- Label a decoder. If the decoder fails, the label will be appended on
+-- | Label a decoder. If the decoder fails, the label will be appended on
-- a new line to the error message string.
+--
+-- /Since: 0.7.2.0/
label :: String -> Get a -> Get a
label msg decoder = C $ \inp ks ->
let r0 = runCont decoder inp (\inp' a -> Done inp' a)
More information about the ghc-commits
mailing list