Skip to content
GitLab
Explore
Sign in
Register
Primary navigation
Search or go to…
Project
B
binary
Manage
Activity
Members
Labels
Plan
Issues
Issue boards
Milestones
Wiki
Requirements
Code
Merge requests
Repository
Branches
Commits
Tags
Repository graph
Compare revisions
Snippets
Locked files
Build
Pipelines
Jobs
Pipeline schedules
Test cases
Artifacts
Deploy
Releases
Package Registry
Container Registry
Model registry
Operate
Environments
Terraform modules
Monitor
Incidents
Analyze
Value stream analytics
Contributor analytics
CI/CD analytics
Repository analytics
Code review analytics
Issue analytics
Insights
Model experiments
Help
Help
Support
GitLab documentation
Compare GitLab plans
Community forum
Contribute to GitLab
Provide feedback
Terms and privacy
Keyboard shortcuts
?
Snippets
Groups
Projects
Show more breadcrumbs
Rinat Striungis
binary
Commits
cfb9e89b
Unverified
Commit
cfb9e89b
authored
6 years ago
by
Lennart Kolmodin
Committed by
GitHub
6 years ago
Browse files
Options
Downloads
Plain Diff
Merge pull request #164 from harpocrates/haddock-markup
Haddock markup fixes
parents
31f68171
722622d8
No related branches found
Branches containing commit
No related tags found
Tags containing commit
No related merge requests found
Changes
4
Hide whitespace changes
Inline
Side-by-side
Showing
4 changed files
src/Data/Binary.hs
+3
-3
3 additions, 3 deletions
src/Data/Binary.hs
src/Data/Binary/Class.hs
+28
-28
28 additions, 28 deletions
src/Data/Binary/Class.hs
src/Data/Binary/Get.hs
+3
-3
3 additions, 3 deletions
src/Data/Binary/Get.hs
src/Data/Binary/Get/Internal.hs
+7
-7
7 additions, 7 deletions
src/Data/Binary/Get/Internal.hs
with
41 additions
and
41 deletions
src/Data/Binary.hs
+
3
−
3
View file @
cfb9e89b
...
...
@@ -132,7 +132,7 @@ import System.IO ( withBinaryFile, IOMode(ReadMode) )
-- > > let e = OpE "*" (IntE 7) (OpE "/" (IntE 4) (IntE 2))
-- > > let v = encode e
--
-- Where
'v'
is a binary encoded data structure. To reconstruct the
-- Where
@v@
is a binary encoded data structure. To reconstruct the
-- original data, we use 'decode'
--
-- > > decode v :: Exp
...
...
@@ -177,7 +177,7 @@ decode = runGet get
-- consumed bytes is returned. In case of failure, a human-readable error
-- message will be returned as well.
--
--
/S
ince
:
0.7.0.0
/
--
@s
ince 0.7.0.0
decodeOrFail
::
Binary
a
=>
L
.
ByteString
->
Either
(
L
.
ByteString
,
ByteOffset
,
String
)
(
L
.
ByteString
,
ByteOffset
,
a
)
...
...
@@ -203,7 +203,7 @@ 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.
--
--
/S
ince
:
0.7.0.0
/
--
@s
ince 0.7.0.0
decodeFile
::
Binary
a
=>
FilePath
->
IO
a
decodeFile
f
=
do
result
<-
decodeFileOrFail
f
...
...
This diff is collapsed.
Click to expand it.
src/Data/Binary/Class.hs
+
28
−
28
View file @
cfb9e89b
...
...
@@ -174,7 +174,7 @@ defaultPutList xs = put (length xs) <> mapM_ put xs
-- Void never gets written nor reconstructed since it's impossible to have a
-- value of that type
-- |
/S
ince
:
0.8.0.0
/
-- |
@s
ince 0.8.0.0
instance
Binary
Void
where
put
=
absurd
get
=
mzero
...
...
@@ -339,7 +339,7 @@ instance Binary Integer where
let
v
=
roll
bytes
return
$!
if
sign
==
(
1
::
Word8
)
then
v
else
-
v
-- |
/S
ince
:
0.8.0.0
/
-- |
@s
ince 0.8.0.0
#
ifdef
HAS_FIXED_CONSTRUCTOR
instance
Binary
(
Fixed
.
Fixed
a
)
where
put
(
Fixed
.
MkFixed
a
)
=
put
a
...
...
@@ -369,7 +369,7 @@ roll = foldl' unstep 0 . reverse
-- Fixed-size type for a subset of Natural
type
NaturalWord
=
Word64
-- |
/S
ince
:
0.7.3.0
/
-- |
@s
ince 0.7.3.0
instance
Binary
Natural
where
{-# INLINE put #-}
put
n
|
n
<=
hi
=
...
...
@@ -582,7 +582,7 @@ instance Binary a => Binary [a] where
get
=
do
n
<-
get
::
Get
Int
getMany
n
-- | 'getMany n
'
get
'n'
elements in order, without blowing the stack.
-- |
@
'getMany
'
n
@
get
@n@
elements in order, without blowing the stack.
getMany
::
Binary
a
=>
Int
->
Get
[
a
]
getMany
n
=
go
[]
n
where
...
...
@@ -727,7 +727,7 @@ instance (Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) wher
------------------------------------------------------------------------
-- Fingerprints
-- |
/S
ince
:
0.7.6.0
/
-- |
@s
ince 0.7.6.0
instance
Binary
Fingerprint
where
put
(
Fingerprint
x1
x2
)
=
put
x1
<>
put
x2
get
=
do
...
...
@@ -738,7 +738,7 @@ instance Binary Fingerprint where
------------------------------------------------------------------------
-- Version
-- |
/S
ince
:
0.8.0.0
/
-- |
@s
ince 0.8.0.0
instance
Binary
Version
where
put
(
Version
br
tags
)
=
put
br
<>
put
tags
get
=
Version
<$>
get
<*>
get
...
...
@@ -746,43 +746,43 @@ instance Binary Version where
------------------------------------------------------------------------
-- Data.Monoid datatypes
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
a
=>
Binary
(
Monoid
.
Dual
a
)
where
get
=
fmap
Monoid
.
Dual
get
put
=
put
.
Monoid
.
getDual
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
Monoid
.
All
where
get
=
fmap
Monoid
.
All
get
put
=
put
.
Monoid
.
getAll
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
Monoid
.
Any
where
get
=
fmap
Monoid
.
Any
get
put
=
put
.
Monoid
.
getAny
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
a
=>
Binary
(
Monoid
.
Sum
a
)
where
get
=
fmap
Monoid
.
Sum
get
put
=
put
.
Monoid
.
getSum
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
a
=>
Binary
(
Monoid
.
Product
a
)
where
get
=
fmap
Monoid
.
Product
get
put
=
put
.
Monoid
.
getProduct
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
a
=>
Binary
(
Monoid
.
First
a
)
where
get
=
fmap
Monoid
.
First
get
put
=
put
.
Monoid
.
getFirst
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
a
=>
Binary
(
Monoid
.
Last
a
)
where
get
=
fmap
Monoid
.
Last
get
put
=
put
.
Monoid
.
getLast
#
if
MIN_VERSION_base
(
4
,
8
,
0
)
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
(
f
a
)
=>
Binary
(
Monoid
.
Alt
f
a
)
where
get
=
fmap
Monoid
.
Alt
get
put
=
put
.
Monoid
.
getAlt
...
...
@@ -792,37 +792,37 @@ instance Binary (f a) => Binary (Monoid.Alt f a) where
------------------------------------------------------------------------
-- Data.Semigroup datatypes
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
a
=>
Binary
(
Semigroup
.
Min
a
)
where
get
=
fmap
Semigroup
.
Min
get
put
=
put
.
Semigroup
.
getMin
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
a
=>
Binary
(
Semigroup
.
Max
a
)
where
get
=
fmap
Semigroup
.
Max
get
put
=
put
.
Semigroup
.
getMax
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
a
=>
Binary
(
Semigroup
.
First
a
)
where
get
=
fmap
Semigroup
.
First
get
put
=
put
.
Semigroup
.
getFirst
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
a
=>
Binary
(
Semigroup
.
Last
a
)
where
get
=
fmap
Semigroup
.
Last
get
put
=
put
.
Semigroup
.
getLast
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
a
=>
Binary
(
Semigroup
.
Option
a
)
where
get
=
fmap
Semigroup
.
Option
get
put
=
put
.
Semigroup
.
getOption
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
m
=>
Binary
(
Semigroup
.
WrappedMonoid
m
)
where
get
=
fmap
Semigroup
.
WrapMonoid
get
put
=
put
.
Semigroup
.
unwrapMonoid
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
(
Binary
a
,
Binary
b
)
=>
Binary
(
Semigroup
.
Arg
a
b
)
where
get
=
liftM2
Semigroup
.
Arg
get
get
put
(
Semigroup
.
Arg
a
b
)
=
put
a
<>
put
b
...
...
@@ -830,7 +830,7 @@ instance (Binary a, Binary b) => Binary (Semigroup.Arg a b) where
------------------------------------------------------------------------
-- Non-empty lists
-- |
/S
ince
:
0.8.4.0
/
-- |
@s
ince 0.8.4.0
instance
Binary
a
=>
Binary
(
NE
.
NonEmpty
a
)
where
get
=
do
list
<-
get
...
...
@@ -864,17 +864,17 @@ instance Binary a => Binary (NE.NonEmpty a) where
-- * 'SomeTypeRep' (also known as 'Data.Typeable.TypeRep')
--
-- | @since 0.8.5.0
. See #typeable-instances#
-- | @since 0.8.5.0
instance
Binary
VecCount
where
put
=
putWord8
.
fromIntegral
.
fromEnum
get
=
toEnum
.
fromIntegral
<$>
getWord8
-- | @since 0.8.5.0
. See #typeable-instances#
-- | @since 0.8.5.0
instance
Binary
VecElem
where
put
=
putWord8
.
fromIntegral
.
fromEnum
get
=
toEnum
.
fromIntegral
<$>
getWord8
-- | @since 0.8.5.0
. See #typeable-instances#
-- | @since 0.8.5.0
instance
Binary
RuntimeRep
where
put
(
VecRep
a
b
)
=
putWord8
0
>>
put
a
>>
put
b
put
(
TupleRep
reps
)
=
putWord8
1
>>
put
reps
...
...
@@ -918,7 +918,7 @@ instance Binary RuntimeRep where
#
endif
_
->
fail
"GHCi.TH.Binary.putRuntimeRep: invalid tag"
-- | @since 0.8.5.0
. See #typeable-instances#
-- | @since 0.8.5.0
instance
Binary
TyCon
where
put
tc
=
do
put
(
tyConPackage
tc
)
...
...
@@ -928,7 +928,7 @@ instance Binary TyCon where
put
(
tyConKindRep
tc
)
get
=
mkTyCon
<$>
get
<*>
get
<*>
get
<*>
get
<*>
get
-- | @since 0.8.5.0
. See #typeable-instances#
-- | @since 0.8.5.0
instance
Binary
KindRep
where
put
(
KindRepTyConApp
tc
k
)
=
putWord8
0
>>
put
tc
>>
put
k
put
(
KindRepVar
bndr
)
=
putWord8
1
>>
put
bndr
...
...
@@ -948,7 +948,7 @@ instance Binary KindRep where
5
->
KindRepTypeLit
<$>
get
<*>
get
_
->
fail
"GHCi.TH.Binary.putKindRep: invalid tag"
-- | @since 0.8.5.0
. See #typeable-instances#
-- | @since 0.8.5.0
instance
Binary
TypeLitSort
where
put
TypeLitSymbol
=
putWord8
0
put
TypeLitNat
=
putWord8
1
...
...
This diff is collapsed.
Click to expand it.
src/Data/Binary/Get.hs
+
3
−
3
View file @
cfb9e89b
...
...
@@ -126,7 +126,7 @@
-- from a socket which has higher likelihood to fail. To address these needs,
-- use the incremental input method like in @incrementalExample@.
-- For an example of how to read incrementally from a Handle,
-- see the implementation of 'decodeFileOrFail'
in "Data.Binary"
.
-- see the implementation of '
Data.Binary.
decodeFileOrFail'.
-----------------------------------------------------------------------------
...
...
@@ -328,7 +328,7 @@ dropHeadChunk lbs =
-- consumed is returned. In the case of failure, a human-readable
-- error message is included as well.
--
--
/S
ince
:
0.6.4.0
/
--
@s
ince 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
...
...
@@ -366,7 +366,7 @@ pushChunk r inp =
-- | Feed a 'Decoder' with more input. If the 'Decoder' is 'Done' or 'Fail' it
-- will add the input to 'ByteString' of unconsumed input.
-- will add the input to '
L.
ByteString' of unconsumed input.
--
-- @
-- 'runGetIncremental' myParser \`pushChunks\` myLazyByteString
...
...
This diff is collapsed.
Click to expand it.
src/Data/Binary/Get/Internal.hs
+
7
−
7
View file @
cfb9e89b
...
...
@@ -130,7 +130,7 @@ instance Applicative Get where
(
<*>
)
=
apG
{-# INLINE (<*>) #-}
-- |
/S
ince
:
0.7.1.0
/
-- |
@s
ince 0.7.1.0
instance
MonadPlus
Get
where
mzero
=
empty
mplus
=
(
<|>
)
...
...
@@ -201,7 +201,7 @@ bytesRead = C $ \inp k -> BytesRead (fromIntegral $ B.length inp) (k inp)
-- Offset from 'bytesRead' will be relative to the start of 'isolate', not the
-- absolute of the input.
--
--
/S
ince
:
0.7.2.0
/
--
@s
ince 0.7.2.0
isolate
::
Int
-- ^ The number of bytes that must be consumed
->
Get
a
-- ^ The decoder to isolate
->
Get
a
...
...
@@ -264,7 +264,7 @@ getBytes :: Int -> Get B.ByteString
getBytes
=
getByteString
{-# INLINE getBytes #-}
-- |
/S
ince
:
0.7.0.0
/
-- |
@s
ince 0.7.0.0
instance
Alternative
Get
where
empty
=
C
$
\
inp
_ks
->
Fail
inp
"Data.Binary.Get(Alternative).empty"
{-# INLINE empty #-}
...
...
@@ -312,7 +312,7 @@ 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.
--
--
/S
ince
:
0.7.0.0
/
--
@s
ince 0.7.0.0
lookAhead
::
Get
a
->
Get
a
lookAhead
g
=
do
(
decoder
,
bs
)
<-
runAndKeepTrack
g
...
...
@@ -325,7 +325,7 @@ lookAhead g = do
-- If 'Nothing' is returned, the input will be unconsumed.
-- If the given decoder fails, then so will this function.
--
--
/S
ince
:
0.7.0.0
/
--
@s
ince 0.7.0.0
lookAheadM
::
Get
(
Maybe
a
)
->
Get
(
Maybe
a
)
lookAheadM
g
=
do
let
g'
=
maybe
(
Left
()
)
Right
<$>
g
...
...
@@ -335,7 +335,7 @@ lookAheadM g = do
-- If 'Left' is returned, the input will be unconsumed.
-- If the given decoder fails, then so will this function.
--
--
/S
ince
:
0.7.1.0
/
--
@s
ince 0.7.1.0
lookAheadE
::
Get
(
Either
a
b
)
->
Get
(
Either
a
b
)
lookAheadE
g
=
do
(
decoder
,
bs
)
<-
runAndKeepTrack
g
...
...
@@ -348,7 +348,7 @@ lookAheadE g = do
-- | Label a decoder. If the decoder fails, the label will be appended on
-- a new line to the error message string.
--
--
/S
ince
:
0.7.2.0
/
--
@s
ince 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
)
...
...
This diff is collapsed.
Click to expand it.
Preview
0%
Loading
Try again
or
attach a new file
.
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Save comment
Cancel
Please
register
or
sign in
to comment