byte-order-0.1.2.0: Portable big-endian and little-endian conversions

Safe HaskellNone
LanguageHaskell2010

System.ByteOrder

Contents

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, and fromLittleEndian convert between native-endian words and big/little-endian words. The word resulting from to(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 to from(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

Types

data ByteOrder #

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

Instance details

Defined in GHC.ByteOrder

Enum ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Eq ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Ord ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Read ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Show ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

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).

Constructors

Fixed 

Fields

Instances
Enum a => Enum (Fixed b a) Source # 
Instance details

Defined in System.ByteOrder

Methods

succ :: Fixed b a -> Fixed b a #

pred :: Fixed b a -> Fixed b a #

toEnum :: Int -> Fixed b a #

fromEnum :: Fixed b a -> Int #

enumFrom :: Fixed b a -> [Fixed b a] #

enumFromThen :: Fixed b a -> Fixed b a -> [Fixed b a] #

enumFromTo :: Fixed b a -> Fixed b a -> [Fixed b a] #

enumFromThenTo :: Fixed b a -> Fixed b a -> Fixed b a -> [Fixed b a] #

Eq a => Eq (Fixed b a) Source # 
Instance details

Defined in System.ByteOrder

Methods

(==) :: Fixed b a -> Fixed b a -> Bool #

(/=) :: Fixed b a -> Fixed b a -> Bool #

Integral a => Integral (Fixed b a) Source # 
Instance details

Defined in System.ByteOrder

Methods

quot :: Fixed b a -> Fixed b a -> Fixed b a #

rem :: Fixed b a -> Fixed b a -> Fixed b a #

div :: Fixed b a -> Fixed b a -> Fixed b a #

mod :: Fixed b a -> Fixed b a -> Fixed b a #

quotRem :: Fixed b a -> Fixed b a -> (Fixed b a, Fixed b a) #

divMod :: Fixed b a -> Fixed b a -> (Fixed b a, Fixed b a) #

toInteger :: Fixed b a -> Integer #

Num a => Num (Fixed b a) Source # 
Instance details

Defined in System.ByteOrder

Methods

(+) :: Fixed b a -> Fixed b a -> Fixed b a #

(-) :: Fixed b a -> Fixed b a -> Fixed b a #

(*) :: Fixed b a -> Fixed b a -> Fixed b a #

negate :: Fixed b a -> Fixed b a #

abs :: Fixed b a -> Fixed b a #

signum :: Fixed b a -> Fixed b a #

fromInteger :: Integer -> Fixed b a #

Ord a => Ord (Fixed b a) Source # 
Instance details

Defined in System.ByteOrder

Methods

compare :: Fixed b a -> Fixed b a -> Ordering #

(<) :: Fixed b a -> Fixed b a -> Bool #

(<=) :: Fixed b a -> Fixed b a -> Bool #

(>) :: Fixed b a -> Fixed b a -> Bool #

(>=) :: Fixed b a -> Fixed b a -> Bool #

max :: Fixed b a -> Fixed b a -> Fixed b a #

min :: Fixed b a -> Fixed b a -> Fixed b a #

Real a => Real (Fixed b a) Source # 
Instance details

Defined in System.ByteOrder

Methods

toRational :: Fixed b a -> Rational #

(FixedOrdering b, Storable a, Bytes a) => Storable (Fixed b a) Source # 
Instance details

Defined in System.ByteOrder

Methods

sizeOf :: Fixed b a -> Int #

alignment :: Fixed b a -> Int #

peekElemOff :: Ptr (Fixed b a) -> Int -> IO (Fixed b a) #

pokeElemOff :: Ptr (Fixed b a) -> Int -> Fixed b a -> IO () #

peekByteOff :: Ptr b0 -> Int -> IO (Fixed b a) #

pokeByteOff :: Ptr b0 -> Int -> Fixed b a -> IO () #

peek :: Ptr (Fixed b a) -> IO (Fixed b a) #

poke :: Ptr (Fixed b a) -> Fixed b a -> IO () #

(FixedOrdering b, Prim a, Bytes a) => Prim (Fixed b a) Source # 
Instance details

Defined in System.ByteOrder

Methods

sizeOf# :: Fixed b a -> Int# #

alignment# :: Fixed b a -> Int# #

indexByteArray# :: ByteArray# -> Int# -> Fixed b a #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Fixed b a#) #

writeByteArray# :: MutableByteArray# s -> Int# -> Fixed b a -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Fixed b a -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> Fixed b a #

readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Fixed b a#) #

writeOffAddr# :: Addr# -> Int# -> Fixed b a -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> Fixed b a -> State# s -> State# s #

(FixedOrdering b, PrimUnaligned a, Bytes a) => PrimUnaligned (Fixed b a) Source # 
Instance details

Defined in System.ByteOrder

Classes

class Bytes a Source #

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

toBigEndian, toLittleEndian

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

toFixedEndian

Instances
FixedOrdering LittleEndian Source # 
Instance details

Defined in System.ByteOrder.Class

Methods

toFixedEndian :: Bytes a => a -> a Source #

FixedOrdering BigEndian Source # 
Instance details

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:

  1. The client sends the server a little-endian 16-bit number N. This is how many numbers will follow.
  2. The client sends N little-endian 64-bit numbers to the server.
  3. 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.