ONC-RPC-0.2: ONC RPC (aka Sun RPC) and XDR library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.ONCRPC.XDR.Array

Description

Various kinds of arrays (lists, vectors, bytestrings) with statically aserted length constraints encoded in their type.

Synopsis

Documentation

class KnownNat (n :: Nat) #

This class gives the integer associated with a type-level natural. There are instances of the class for every concrete literal: 0, 1, 2, etc.

Since: base-4.7.0.0

Minimal complete definition

natSing

class KnownOrdering (o :: Ordering) Source #

Minimal complete definition

orderingVal

Instances

Instances details
KnownOrdering 'EQ Source # 
Instance details

Defined in Network.ONCRPC.XDR.Array

Methods

orderingVal :: proxy 'EQ -> Ordering

KnownOrdering 'GT Source # 
Instance details

Defined in Network.ONCRPC.XDR.Array

Methods

orderingVal :: proxy 'GT -> Ordering

KnownOrdering 'LT Source # 
Instance details

Defined in Network.ONCRPC.XDR.Array

Methods

orderingVal :: proxy 'LT -> Ordering

newtype OpaqueString Source #

A ByteString that uses hex (base16) for Read/Show.

Constructors

OpaqueString 

Instances

Instances details
IsString OpaqueString Source #

Allows either hex or character input, dynamically.

Instance details

Defined in Network.ONCRPC.XDR.Array

Monoid OpaqueString Source # 
Instance details

Defined in Network.ONCRPC.XDR.Array

Semigroup OpaqueString Source # 
Instance details

Defined in Network.ONCRPC.XDR.Array

Read OpaqueString Source # 
Instance details

Defined in Network.ONCRPC.XDR.Array

Show OpaqueString Source # 
Instance details

Defined in Network.ONCRPC.XDR.Array

Eq OpaqueString Source # 
Instance details

Defined in Network.ONCRPC.XDR.Array

Ord OpaqueString Source # 
Instance details

Defined in Network.ONCRPC.XDR.Array

KnownNat n => XDR (LengthArray 'EQ n OpaqueString) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

KnownNat n => XDR (LengthArray 'LT n OpaqueString) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

data LengthArray (o :: Ordering) (n :: Nat) a Source #

Assertion that the contained array satisfies compareLength a n = o

Instances

Instances details
KnownNat n => XDR (LengthArray 'EQ n OpaqueString) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

KnownNat n => XDR (LengthArray 'EQ n ByteString) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

(KnownNat n, XDR a) => XDR (LengthArray 'EQ n (Vector a)) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

(KnownNat n, XDR a) => XDR (LengthArray 'EQ n [a]) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

KnownNat n => XDR (LengthArray 'LT n OpaqueString) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

KnownNat n => XDR (LengthArray 'LT n ByteString) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

(KnownNat n, XDR a) => XDR (LengthArray 'LT n (Vector a)) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

(KnownNat n, XDR a) => XDR (LengthArray 'LT n [a]) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Serial

(KnownOrdering o, KnownNat n, IsString a, HasLength a) => IsString (LengthArray o n a) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Array

Methods

fromString :: String -> LengthArray o n a #

Show a => Show (LengthArray o n a) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Array

Methods

showsPrec :: Int -> LengthArray o n a -> ShowS #

show :: LengthArray o n a -> String #

showList :: [LengthArray o n a] -> ShowS #

Eq a => Eq (LengthArray o n a) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Array

Methods

(==) :: LengthArray o n a -> LengthArray o n a -> Bool #

(/=) :: LengthArray o n a -> LengthArray o n a -> Bool #

Ord a => Ord (LengthArray o n a) Source # 
Instance details

Defined in Network.ONCRPC.XDR.Array

Methods

compare :: LengthArray o n a -> LengthArray o n a -> Ordering #

(<) :: LengthArray o n a -> LengthArray o n a -> Bool #

(<=) :: LengthArray o n a -> LengthArray o n a -> Bool #

(>) :: LengthArray o n a -> LengthArray o n a -> Bool #

(>=) :: LengthArray o n a -> LengthArray o n a -> Bool #

max :: LengthArray o n a -> LengthArray o n a -> LengthArray o n a #

min :: LengthArray o n a -> LengthArray o n a -> LengthArray o n a #

type FixedLengthArray n a = LengthArray 'EQ n a Source #

Assertion that the contained array is exactly a static length

type BoundedLengthArray n a = LengthArray 'LT (n + 1) a Source #

Assertion that the contained array is at most a static length (inclusive)

boundedLengthArrayBound :: KnownNat n => LengthArray 'LT n a -> Int Source #

Static upper-bound (inclusive) of a BoundedLengthArray

unsafeLengthArray :: a -> LengthArray o n a Source #

Unsafely create a LengthArray without checking the length bound assertion. May cause unpredictable behavior if the bound does not hold.

lengthArray :: forall o n a. (KnownOrdering o, KnownNat n, HasLength a) => a -> Maybe (LengthArray o n a) Source #

Safely create a LengthArray out of an array if it conforms to the static length assertion.

lengthArray' :: forall o n a. (KnownOrdering o, KnownNat n, HasLength a) => a -> LengthArray o n a Source #

Create a LengthArray or runtime error if the assertion fails: fromMaybe undefined . lengthArray

boundLengthArray :: (KnownNat n, Array a) => a -> LengthArray 'LT n a Source #

Create a BoundedLengthArray by trimming the given array if necessary.

boundLengthArrayFromList :: (KnownNat n, Array a) => [Elem a] -> LengthArray 'LT n a Source #

Create a BoundedLengthArray by trimming the given array if necessary.

padLengthArray :: (KnownNat n, Array a) => a -> Elem a -> LengthArray 'EQ n a Source #

Create a FixedLengthArray by trimming or padding (on the right) as necessary.

constLengthArray :: (KnownNat n, Array a) => Elem a -> LengthArray 'EQ n a Source #

Create a FixedLengthArray filled with the same value.

appendLengthArray :: Monoid a => LengthArray o n a -> LengthArray o m a -> LengthArray o (n + m) a Source #

Append to two LengthArrays.

fromLengthList :: Array a => LengthArray o n [Elem a] -> LengthArray o n a Source #