| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Network.ByteOrder
Contents
Description
Peek and poke functions for network byte order.
Synopsis
- type Buffer = Ptr Word8
- type Offset = Int
- type BufferSize = Int
- data BufferOverrun = BufferOverrun
- poke8 :: Word8 -> Buffer -> Offset -> IO ()
- poke16 :: Word16 -> Buffer -> Offset -> IO ()
- poke24 :: Word32 -> Buffer -> Offset -> IO ()
- poke32 :: Word32 -> Buffer -> Offset -> IO ()
- poke64 :: Word64 -> Buffer -> Offset -> IO ()
- peek8 :: Buffer -> Offset -> IO Word8
- peek16 :: Buffer -> Offset -> IO Word16
- peek24 :: Buffer -> Offset -> IO Word32
- peek32 :: Buffer -> Offset -> IO Word32
- peek64 :: Buffer -> Offset -> IO Word64
- peekByteString :: Buffer -> Int -> IO ByteString
- bytestring8 :: Word8 -> ByteString
- bytestring16 :: Word16 -> ByteString
- bytestring32 :: Word32 -> ByteString
- bytestring64 :: Word64 -> ByteString
- word8 :: ByteString -> Word8
- word16 :: ByteString -> Word16
- word32 :: ByteString -> Word32
- word64 :: ByteString -> Word64
- unsafeWithByteString :: ByteString -> (Buffer -> Offset -> IO a) -> IO a
- copy :: Buffer -> ByteString -> IO Buffer
- bufferIO :: Buffer -> Int -> (ByteString -> IO a) -> IO a
- class Readable a where
- data ReadBuffer
- withReadBuffer :: ByteString -> (ReadBuffer -> IO a) -> IO a
- read16 :: Readable a => a -> IO Word16
- read24 :: Readable a => a -> IO Word32
- read32 :: Readable a => a -> IO Word32
- extractByteString :: Readable a => a -> Int -> IO ByteString
- data WriteBuffer = WriteBuffer {}
- newWriteBuffer :: Buffer -> BufferSize -> IO WriteBuffer
- withWriteBuffer :: BufferSize -> (WriteBuffer -> IO ()) -> IO ByteString
- write8 :: WriteBuffer -> Word8 -> IO ()
- write16 :: WriteBuffer -> Word16 -> IO ()
- write24 :: WriteBuffer -> Word32 -> IO ()
- write32 :: WriteBuffer -> Word32 -> IO ()
- copyByteString :: WriteBuffer -> ByteString -> IO ()
- shiftLastN :: WriteBuffer -> Offset -> Int -> IO ()
- toByteString :: WriteBuffer -> IO ByteString
- currentOffset :: WriteBuffer -> IO Buffer
- data Word8
- data Word16
- data Word32
- data Word64
- data ByteString
Types
type BufferSize = Int Source #
Size of a buffer.
data BufferOverrun Source #
Constructors
| BufferOverrun | The buffer size is not enough |
Instances
| Eq BufferOverrun Source # | |
Defined in Network.ByteOrder Methods (==) :: BufferOverrun -> BufferOverrun -> Bool # (/=) :: BufferOverrun -> BufferOverrun -> Bool # | |
| Show BufferOverrun Source # | |
Defined in Network.ByteOrder Methods showsPrec :: Int -> BufferOverrun -> ShowS # show :: BufferOverrun -> String # showList :: [BufferOverrun] -> ShowS # | |
| Exception BufferOverrun Source # | |
Defined in Network.ByteOrder Methods toException :: BufferOverrun -> SomeException # fromException :: SomeException -> Maybe BufferOverrun # displayException :: BufferOverrun -> String # | |
Poking
poke8 :: Word8 -> Buffer -> Offset -> IO () Source #
>>>let buf = pack [1,2,3,4]>>>unsafeWithByteString buf (poke8 0)>>>unpack buf[0,2,3,4]
poke16 :: Word16 -> Buffer -> Offset -> IO () Source #
>>>let buf = pack [1,2,3,4]>>>unsafeWithByteString buf (poke16 (7*256 + 8))>>>unpack buf[7,8,3,4]
poke24 :: Word32 -> Buffer -> Offset -> IO () Source #
>>>let buf = pack [1,2,3,4]>>>unsafeWithByteString buf (poke24 (6*65536 + 7*256 + 8))>>>unpack buf[6,7,8,4]
poke32 :: Word32 -> Buffer -> Offset -> IO () Source #
>>>let buf = pack [1,2,3,4]>>>unsafeWithByteString buf (poke32 (6*65536 + 7*256 + 8))>>>unpack buf[0,6,7,8]
poke64 :: Word64 -> Buffer -> Offset -> IO () Source #
>>>let buf = pack [1,2,3,4,5,6,7,8]>>>unsafeWithByteString buf (poke64 (6*65536 + 7*256 + 8))>>>unpack buf[0,0,0,0,0,6,7,8]
Peeking
peek8 :: Buffer -> Offset -> IO Word8 Source #
>>>let buf = pack [1,2,3,4]>>>unsafeWithByteString buf peek81
peek16 :: Buffer -> Offset -> IO Word16 Source #
>>>let buf = pack [1,2,3,4]>>>unsafeWithByteString buf peek16258
peek24 :: Buffer -> Offset -> IO Word32 Source #
>>>let buf = pack [1,2,3,4]>>>unsafeWithByteString buf peek2466051
peek32 :: Buffer -> Offset -> IO Word32 Source #
>>>let buf = pack [1,2,3,4]>>>unsafeWithByteString buf peek3216909060
peek64 :: Buffer -> Offset -> IO Word64 Source #
>>>let buf = pack [1,2,3,4,5,6,7,8]>>>unsafeWithByteString buf peek6472623859790382856
peekByteString :: Buffer -> Int -> IO ByteString Source #
From Word to ByteString
bytestring8 :: Word8 -> ByteString Source #
>>>let w = 5 :: Word8>>>unpack $ bytestring8 w[5]
bytestring16 :: Word16 -> ByteString Source #
>>>let w = foldl' (\x y -> x * 256 + y) 0 [5,6] :: Word16>>>unpack $ bytestring16 w[5,6]
bytestring32 :: Word32 -> ByteString Source #
>>>let w = foldl' (\x y -> x * 256 + y) 0 [5,6,7,8] :: Word32>>>unpack $ bytestring32 w[5,6,7,8]
bytestring64 :: Word64 -> ByteString Source #
>>>let w = foldl' (\x y -> x * 256 + y) 0 [1,2,3,4,5,6,7,8] :: Word64>>>unpack $ bytestring64 w[1,2,3,4,5,6,7,8]
From ByteString to Word
word8 :: ByteString -> Word8 Source #
>>>let buf = pack [1,2,3,4,5,6,7,8]>>>word8 buf1
word16 :: ByteString -> Word16 Source #
>>>let buf = pack [1,2,3,4,5,6,7,8]>>>word16 buf258
word32 :: ByteString -> Word32 Source #
>>>let buf = pack [1,2,3,4,5,6,7,8]>>>word32 buf16909060
word64 :: ByteString -> Word64 Source #
>>>let buf = pack [1,2,3,4,5,6,7,8]>>>word64 buf72623859790382856
Utilities
unsafeWithByteString :: ByteString -> (Buffer -> Offset -> IO a) -> IO a Source #
Using ByteString as Buffer and call the IO action
of the second argument by passing the start point and the offset
of the ByteString.
Note that if a ByteString is created newly, its offset is 0.
copy :: Buffer -> ByteString -> IO Buffer Source #
Copying the bytestring to the buffer. This function returns the point where the next copy should start.
Class to read a buffer
class Readable a where Source #
Methods
read8 :: a -> IO Word8 Source #
Reading one byte as Word8 and ff one byte.
readInt8 :: a -> IO Int Source #
Reading one byte as Int and ff one byte. If buffer overrun occurs, -1 is returned.
ff :: a -> Offset -> IO () Source #
Fast forward the offset pointer. The boundary is not checked.
remainingSize :: a -> IO Int Source #
Returning the length of the remaining
withCurrentOffSet :: a -> (Buffer -> IO b) -> IO b Source #
Executing an action on the current offset pointer.
Memorizing the current offset pointer.
savingSize :: a -> IO Int Source #
Getting how many bytes from the saved offset pinter.
Instances
| Readable ReadBuffer Source # | |
Defined in Network.ByteOrder Methods read8 :: ReadBuffer -> IO Word8 Source # readInt8 :: ReadBuffer -> IO Int Source # ff :: ReadBuffer -> Offset -> IO () Source # remainingSize :: ReadBuffer -> IO Int Source # withCurrentOffSet :: ReadBuffer -> (Buffer -> IO b) -> IO b Source # save :: ReadBuffer -> IO () Source # savingSize :: ReadBuffer -> IO Int Source # | |
| Readable WriteBuffer Source # | |
Defined in Network.ByteOrder Methods read8 :: WriteBuffer -> IO Word8 Source # readInt8 :: WriteBuffer -> IO Int Source # ff :: WriteBuffer -> Offset -> IO () Source # remainingSize :: WriteBuffer -> IO Int Source # withCurrentOffSet :: WriteBuffer -> (Buffer -> IO b) -> IO b Source # save :: WriteBuffer -> IO () Source # savingSize :: WriteBuffer -> IO Int Source # | |
Reading from buffer
data ReadBuffer Source #
Read only buffer. To ensure that the internal is not modified, this is an abstract data type.
Instances
| Readable ReadBuffer Source # | |
Defined in Network.ByteOrder Methods read8 :: ReadBuffer -> IO Word8 Source # readInt8 :: ReadBuffer -> IO Int Source # ff :: ReadBuffer -> Offset -> IO () Source # remainingSize :: ReadBuffer -> IO Int Source # withCurrentOffSet :: ReadBuffer -> (Buffer -> IO b) -> IO b Source # save :: ReadBuffer -> IO () Source # savingSize :: ReadBuffer -> IO Int Source # | |
withReadBuffer :: ByteString -> (ReadBuffer -> IO a) -> IO a Source #
Converting ByteString to ReadBuffer and run the action
with it.
extractByteString :: Readable a => a -> Int -> IO ByteString Source #
Extracting ByteString from the current offset.
The contents is copied, not shared.
Its length is specified by the 2nd argument.
If the length is positive, the area after the current pointer is extracted and FF the length finally.
If the length is negative, the area before the current pointer is extracted and does not FF.
Writing to buffer
data WriteBuffer Source #
Read and write buffer.
Constructors
| WriteBuffer | |
Instances
| Readable WriteBuffer Source # | |
Defined in Network.ByteOrder Methods read8 :: WriteBuffer -> IO Word8 Source # readInt8 :: WriteBuffer -> IO Int Source # ff :: WriteBuffer -> Offset -> IO () Source # remainingSize :: WriteBuffer -> IO Int Source # withCurrentOffSet :: WriteBuffer -> (Buffer -> IO b) -> IO b Source # save :: WriteBuffer -> IO () Source # savingSize :: WriteBuffer -> IO Int Source # | |
newWriteBuffer :: Buffer -> BufferSize -> IO WriteBuffer Source #
Creating a write buffer with the given buffer.
withWriteBuffer :: BufferSize -> (WriteBuffer -> IO ()) -> IO ByteString Source #
Allocate a temporary buffer and copy the result to ByteString.
write8 :: WriteBuffer -> Word8 -> IO () Source #
Write one byte and ff one byte.
If buffer overrun occurs, BufferOverrun is thrown.
write16 :: WriteBuffer -> Word16 -> IO () Source #
Write two bytes and ff one byte.
If buffer overrun occurs, BufferOverrun is thrown.
write24 :: WriteBuffer -> Word32 -> IO () Source #
Write three bytes and ff one byte.
If buffer overrun occurs, BufferOverrun is thrown.
write32 :: WriteBuffer -> Word32 -> IO () Source #
Write four bytes and ff one byte.
If buffer overrun occurs, BufferOverrun is thrown.
copyByteString :: WriteBuffer -> ByteString -> IO () Source #
Copy the content of ByteString and ff its length.
If buffer overrun occurs, BufferOverrun is thrown.
shiftLastN :: WriteBuffer -> Offset -> Int -> IO () Source #
toByteString :: WriteBuffer -> IO ByteString Source #
Copy the area from start to the current pointer to ByteString.
currentOffset :: WriteBuffer -> IO Buffer Source #
Getting the offset pointer.
Re-exporting
8-bit unsigned integer type
Instances
16-bit unsigned integer type
Instances
32-bit unsigned integer type
Instances
64-bit unsigned integer type
Instances
data ByteString #
A space-efficient representation of a Word8 vector, supporting many
efficient operations.
A ByteString contains 8-bit bytes, or by using the operations from
Data.ByteString.Char8 it can be interpreted as containing 8-bit
characters.