Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
System.ByteOrder
Description
This module offers an interface to portably work with byte arrays whose contents are known to be of a fixed endianness. There are two ways to use this module:
- Untyped Conversions: The functions
toBigEndian
,toLittleEndian
,fromBigEndian
, andfromLittleEndian
convert between native-endian words and big/little-endian words. The word resulting fromto(Big|Little)Endian
should be written to a primitive byte array or a pointer afterwards. (There is no other purpose of such a conversion.) Similarly, the argument tofrom(Big|Little)Endian
should be a word that was read from a primitive byte array or a pointer. This interface is useful when serializing or deserializing a data structure with fields of varying sizes. - Typed Conversions: The type
Fixed
provides a convenient type-directed interface to working with arrays of homogenous words. This interface is easier to use and should be preferred when possible.
The example at the bottom of this page demonstrates how to use the type-directed interface.
Synopsis
- data ByteOrder
- newtype Fixed :: ByteOrder -> Type -> Type where
- class Bytes a
- class FixedOrdering (b :: ByteOrder)
- toBigEndian :: Bytes a => a -> a
- toLittleEndian :: Bytes a => a -> a
- fromBigEndian :: Bytes a => a -> a
- fromLittleEndian :: Bytes a => a -> a
- targetByteOrder :: ByteOrder
Types
Byte ordering.
Constructors
BigEndian | most-significant-byte occurs in lowest address. |
LittleEndian | least-significant-byte occurs in lowest address. |
Instances
Bounded ByteOrder | Since: base-4.11.0.0 |
Enum ByteOrder | Since: base-4.11.0.0 |
Defined in GHC.ByteOrder Methods succ :: ByteOrder -> ByteOrder # pred :: ByteOrder -> ByteOrder # fromEnum :: ByteOrder -> Int # enumFrom :: ByteOrder -> [ByteOrder] # enumFromThen :: ByteOrder -> ByteOrder -> [ByteOrder] # enumFromTo :: ByteOrder -> ByteOrder -> [ByteOrder] # enumFromThenTo :: ByteOrder -> ByteOrder -> ByteOrder -> [ByteOrder] # | |
Generic ByteOrder | |
Read ByteOrder | Since: base-4.11.0.0 |
Show ByteOrder | Since: base-4.11.0.0 |
Eq ByteOrder | Since: base-4.11.0.0 |
Ord ByteOrder | Since: base-4.11.0.0 |
type Rep ByteOrder | Since: base-4.15.0.0 |
newtype Fixed :: ByteOrder -> Type -> Type where Source #
A word whose byte order is specified (not platform dependent)
when working with Prim
, Storable
, and PrimUnaligned
(this
last instance is provided alongside the typeclass itself in the
primitive-unaligned
library).
Instances
Classes
Types that are represented as a fixed-sized word. For these types, the bytes can be swapped. The instances of this class use byteswapping primitives and compile-time knowledge of native endianness to provide portable endianness conversion functions.
Minimal complete definition
Instances
Bytes Int16 Source # | |
Defined in System.ByteOrder.Class | |
Bytes Int32 Source # | |
Defined in System.ByteOrder.Class | |
Bytes Int64 Source # | |
Defined in System.ByteOrder.Class | |
Bytes Int8 Source # | |
Defined in System.ByteOrder.Class | |
Bytes Word16 Source # | |
Defined in System.ByteOrder.Class | |
Bytes Word32 Source # | |
Defined in System.ByteOrder.Class | |
Bytes Word64 Source # | |
Defined in System.ByteOrder.Class | |
Bytes Word8 Source # | |
Defined in System.ByteOrder.Class | |
Bytes Word128 Source # | |
Defined in System.ByteOrder.Class | |
Bytes Word256 Source # | |
Defined in System.ByteOrder.Class | |
Bytes Word Source # | |
Defined in System.ByteOrder.Class |
class FixedOrdering (b :: ByteOrder) Source #
A byte order that can be interpreted as a conversion function.
This class is effectively closed. The only instances are for
BigEndian
and LittleEndian
. It is not possible to write more
instances since there are no other inhabitants of ByteOrder
.
Minimal complete definition
Instances
FixedOrdering 'BigEndian Source # | |
Defined in System.ByteOrder.Class Methods toFixedEndian :: Bytes a => a -> a Source # | |
FixedOrdering 'LittleEndian Source # | |
Defined in System.ByteOrder.Class Methods toFixedEndian :: Bytes a => a -> a Source # |
Conversion
toBigEndian :: Bytes a => a -> a Source #
Convert from a native-endian word to a big-endian word.
toLittleEndian :: Bytes a => a -> a Source #
Convert from a native-endian word to a little-endian word.
fromBigEndian :: Bytes a => a -> a Source #
Convert from a big-endian word to a native-endian word.
fromLittleEndian :: Bytes a => a -> a Source #
Convert from a little-endian word to a native-endian word.
System Byte Order
targetByteOrder :: ByteOrder #
The byte ordering of the target machine.
Example
Suppose there is a protocol for aggregating numbers that uses stream sockets for communication. The protocol interprets all numbers as unsigned. It is described as follows:
- The client sends the server a little-endian 16-bit number
N
. This is how many numbers will follow. - The client sends
N
little-endian 64-bit numbers to the server. - The server responds with two little-endian 64-bit numbers:
the sum and the product of the
N
numbers it received.
Assume the existence of a send
and receive
that block until
the total number of requested bytes have been handled. They both
work on their argument arrays starting at index zero, which ensures
that any 2-byte, 4-byte, or 8-byte types will be aligned properly.
(GHC always machine-word aligns the payload of a byte array.)
Additionally, assume the typed
and untyped
functions that convert between
PrimArray
and ByteArray
by changing out the data constructor.
send :: Socket -> ByteArray -> IO () receive :: Socket -> Int -> IO ByteArray typed :: ByteArray -> PrimArray a untyped :: PrimArray a -> ByteArray
For simplicity, all error-handling is omitted. With the type-directed interface, the server is implemented as:
import Data.Primitive.ByteArray import Data.Primitive.PrimArray import System.ByteOrder server :: Socket -> IO a server sckt = forever $ do totalByteArray <- receive sckt 2 let totalPrimArray = typed totalByteArray :: PrimArray (Fixed 'LittleEndian Word16) let Fixed total = indexPrimArray totalPrimArray 0 numberByteArray <- receive sckt (8 * fromIntegral @Word16 @Int total) let (sum,prod) = foldlPrimArray' (\(!sumN,!prodN) (Fixed n) -> (sumN + n, prodN * n)) (0,1) (typed numberByteArray :: PrimArray (Fixed 'LittleEndian Word64)) reply :: MutablePrimArray RealWorld (Fixed 'LittleEndian Word64) <- newPrimArray 2 writePrimArray reply 0 (Fixed sum) writePrimArray reply 1 (Fixed prod) send sckt . untyped =<< unsafeFreezePrimArray reply
Not every explicit type annotation above is needed. Some are provided
for the reader's benefit. As long as the user ensures that the
typed primitive arrays use Fixed
in their element types, the endianness
conversions are guaranteed to be correct.