repa-convert-4.2.4.0: Packing and unpacking flat tables.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Repa.Convert.Formats

Description

Pre-defined data formats.

Synopsis

Default

class FormatAscii a where Source #

Class of types that can be formatted in some default human readable ASCII way.

Associated Types

type FormatAscii' a Source #

The format for values of this type.

Methods

formatAscii :: a -> FormatAscii' a Source #

Get the standard ASCII format for a value.

The element value itself is not demanded.

Instances

Instances details
FormatAscii Date32 Source #

Dates are formatted as YYYY-MM-DD.

Instance details

Defined in Data.Repa.Convert.Format.Ascii

Associated Types

type FormatAscii' Date32 Source #

FormatAscii String Source #

Strings are formatted with double quotes and back-slash escaping of special characters.

Instance details

Defined in Data.Repa.Convert.Format.Ascii

Associated Types

type FormatAscii' String Source #

FormatAscii () Source #

Empty tuples produce no output.

Instance details

Defined in Data.Repa.Convert.Format.Ascii

Associated Types

type FormatAscii' () Source #

Methods

formatAscii :: () -> FormatAscii' () Source #

FormatAscii Double Source #

Doubles are formatted as base-10 decimal.

Instance details

Defined in Data.Repa.Convert.Format.Ascii

Associated Types

type FormatAscii' Double Source #

FormatAscii Int Source #

Ints are formated in base-10.

Instance details

Defined in Data.Repa.Convert.Format.Ascii

Associated Types

type FormatAscii' Int Source #

Units

data UnitAsc Source #

A particular ASCII string.

Constructors

UnitAsc String 

Instances

Instances details
Show UnitAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Unit

Eq UnitAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Unit

Methods

(==) :: UnitAsc -> UnitAsc -> Bool #

(/=) :: UnitAsc -> UnitAsc -> Bool #

Format UnitAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Unit

Associated Types

type Value UnitAsc Source #

Packable UnitAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Unit

Methods

pack :: UnitAsc -> Value UnitAsc -> Packer Source #

packer :: UnitAsc -> Value UnitAsc -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable UnitAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Unit

Methods

unpack :: UnitAsc -> Unpacker (Value UnitAsc) Source #

unpacker :: UnitAsc -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value UnitAsc -> IO ()) -> IO () Source #

type Value UnitAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Unit

type Value UnitAsc = ()

Maybes

data MaybeChars f Source #

Maybe a raw list of characters, or something else.

Constructors

MaybeChars String f 

Instances

Instances details
Show f => Show (MaybeChars f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Eq f => Eq (MaybeChars f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Methods

(==) :: MaybeChars f -> MaybeChars f -> Bool #

(/=) :: MaybeChars f -> MaybeChars f -> Bool #

Format f => Format (MaybeChars f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Associated Types

type Value (MaybeChars f) Source #

Packable f => Packable (MaybeChars f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Methods

pack :: MaybeChars f -> Value (MaybeChars f) -> Packer Source #

packer :: MaybeChars f -> Value (MaybeChars f) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable f => Unpackable (MaybeChars f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Methods

unpack :: MaybeChars f -> Unpacker (Value (MaybeChars f)) Source #

unpacker :: MaybeChars f -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (MaybeChars f) -> IO ()) -> IO () Source #

type Value (MaybeChars f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

type Value (MaybeChars f) = Maybe (Value f)

data MaybeBytes f Source #

Maybe a raw sequence of bytes, or something else.

Constructors

MaybeBytes ByteString f 

Instances

Instances details
Show f => Show (MaybeBytes f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Eq f => Eq (MaybeBytes f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Methods

(==) :: MaybeBytes f -> MaybeBytes f -> Bool #

(/=) :: MaybeBytes f -> MaybeBytes f -> Bool #

Format f => Format (MaybeBytes f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Associated Types

type Value (MaybeBytes f) Source #

Packable f => Packable (MaybeBytes f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Methods

pack :: MaybeBytes f -> Value (MaybeBytes f) -> Packer Source #

packer :: MaybeBytes f -> Value (MaybeBytes f) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable f => Unpackable (MaybeBytes f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

Methods

unpack :: MaybeBytes f -> Unpacker (Value (MaybeBytes f)) Source #

unpacker :: MaybeBytes f -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (MaybeBytes f) -> IO ()) -> IO () Source #

type Value (MaybeBytes f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Maybe

type Value (MaybeBytes f) = Maybe (Value f)

String Formats

for Haskell Strings

data FixChars Source #

Fixed length sequence of characters, represented as a (hated) Haskell String.

  • The runtime performance of the Haskell String is atrocious. You really shouldn't be using them for large data sets.
  • When packing, the length of the provided string must match the width of the format, else packing will fail.
  • When unpacking, the length of the result will be the width of the format.

Constructors

FixChars Int 

Instances

Instances details
Show FixChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Eq FixChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Format FixChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Associated Types

type Value FixChars Source #

Packable FixChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Methods

pack :: FixChars -> Value FixChars -> Packer Source #

packer :: FixChars -> Value FixChars -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable FixChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Methods

unpack :: FixChars -> Unpacker (Value FixChars) Source #

unpacker :: FixChars -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value FixChars -> IO ()) -> IO () Source #

type Value FixChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

data VarChars Source #

Like FixChars, but with a variable length.

Constructors

VarChars 

Instances

Instances details
Show VarChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Eq VarChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Format VarChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Associated Types

type Value VarChars Source #

Packable VarChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Methods

pack :: VarChars -> Value VarChars -> Packer Source #

packer :: VarChars -> Value VarChars -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable VarChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

Methods

unpack :: VarChars -> Unpacker (Value VarChars) Source #

unpacker :: VarChars -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value VarChars -> IO ()) -> IO () Source #

type Value VarChars Source # 
Instance details

Defined in Data.Repa.Convert.Format.String

data VarCharString Source #

Variable length string in double quotes, and standard backslash encoding of non-printable characters.

Constructors

VarCharString 

data ExactChars Source #

Match an exact sequence of characters.

Constructors

ExactChars String 

for Data.Text

data VarText Source #

Variable length unicode text, represented as a Data.Text thing.

Constructors

VarText 

Instances

Instances details
Show VarText Source # 
Instance details

Defined in Data.Repa.Convert.Format.Text

Eq VarText Source # 
Instance details

Defined in Data.Repa.Convert.Format.Text

Methods

(==) :: VarText -> VarText -> Bool #

(/=) :: VarText -> VarText -> Bool #

Format VarText Source # 
Instance details

Defined in Data.Repa.Convert.Format.Text

Associated Types

type Value VarText Source #

Packable VarText Source # 
Instance details

Defined in Data.Repa.Convert.Format.Text

Methods

pack :: VarText -> Value VarText -> Packer Source #

packer :: VarText -> Value VarText -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable VarText Source # 
Instance details

Defined in Data.Repa.Convert.Format.Text

Methods

unpack :: VarText -> Unpacker (Value VarText) Source #

unpacker :: VarText -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value VarText -> IO ()) -> IO () Source #

type Value VarText Source # 
Instance details

Defined in Data.Repa.Convert.Format.Text

data VarTextString Source #

Variable length string in double quotes, and standard backslash encoding of non-printable characters.

Constructors

VarTextString 

for Data.ByteString

data VarBytes Source #

Variable length sequence of bytes, represented as a ByteString.

Constructors

VarBytes 

Instances

Instances details
Show VarBytes Source # 
Instance details

Defined in Data.Repa.Convert.Format.Bytes

Eq VarBytes Source # 
Instance details

Defined in Data.Repa.Convert.Format.Bytes

Format VarBytes Source # 
Instance details

Defined in Data.Repa.Convert.Format.Bytes

Associated Types

type Value VarBytes Source #

Packable VarBytes Source # 
Instance details

Defined in Data.Repa.Convert.Format.Bytes

Methods

pack :: VarBytes -> Value VarBytes -> Packer Source #

packer :: VarBytes -> Value VarBytes -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable VarBytes Source # 
Instance details

Defined in Data.Repa.Convert.Format.Bytes

Methods

unpack :: VarBytes -> Unpacker (Value VarBytes) Source #

unpacker :: VarBytes -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value VarBytes -> IO ()) -> IO () Source #

type Value VarBytes Source # 
Instance details

Defined in Data.Repa.Convert.Format.Bytes

ASCII Atoms

ASCII integers

data IntAsc Source #

Human-readable ASCII Integer.

Constructors

IntAsc 

Instances

Instances details
Show IntAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Eq IntAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Methods

(==) :: IntAsc -> IntAsc -> Bool #

(/=) :: IntAsc -> IntAsc -> Bool #

Format IntAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Associated Types

type Value IntAsc Source #

Packable IntAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Methods

pack :: IntAsc -> Value IntAsc -> Packer Source #

packer :: IntAsc -> Value IntAsc -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable IntAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Methods

unpack :: IntAsc -> Unpacker (Value IntAsc) Source #

unpacker :: IntAsc -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value IntAsc -> IO ()) -> IO () Source #

type Value IntAsc Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

data IntAsc0 Source #

Human-readable ASCII integer, using leading zeros to pad the encoding out to a fixed length.

Constructors

IntAsc0 Int 

Instances

Instances details
Show IntAsc0 Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Eq IntAsc0 Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Methods

(==) :: IntAsc0 -> IntAsc0 -> Bool #

(/=) :: IntAsc0 -> IntAsc0 -> Bool #

Format IntAsc0 Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Associated Types

type Value IntAsc0 Source #

Packable IntAsc0 Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Methods

pack :: IntAsc0 -> Value IntAsc0 -> Packer Source #

packer :: IntAsc0 -> Value IntAsc0 -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable IntAsc0 Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Methods

unpack :: IntAsc0 -> Unpacker (Value IntAsc0) Source #

unpacker :: IntAsc0 -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value IntAsc0 -> IO ()) -> IO () Source #

type Value IntAsc0 Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

ASCII doubles

data DoubleAsc Source #

Human-readable ASCII Double.

Constructors

DoubleAsc 

data DoubleFixedPack Source #

Human-readable ASCII Double.

When packing we use a fixed number of zeros after the decimal point, though when unpacking we allow a greater precision.

Constructors

DoubleFixedPack Int 

Instances

Instances details
Show DoubleFixedPack Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Eq DoubleFixedPack Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Format DoubleFixedPack Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Associated Types

type Value DoubleFixedPack Source #

Packable DoubleFixedPack Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

Unpackable DoubleFixedPack Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

type Value DoubleFixedPack Source # 
Instance details

Defined in Data.Repa.Convert.Format.Numeric

ASCII dates

data YYYYsMMsDD Source #

Human readable ASCII date in YYYYsMMsDD format.

Constructors

YYYYsMMsDD Char 

data DDsMMsYYYY Source #

Human readable ASCII date in DDsMMsYYYY format.

Constructors

DDsMMsYYYY Char 

Binary Atoms

8-bit binary

data Word8be Source #

Big-endian 8-bit unsigned word.

Constructors

Word8be 

Instances

Instances details
Show Word8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Eq Word8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

(==) :: Word8be -> Word8be -> Bool #

(/=) :: Word8be -> Word8be -> Bool #

Format Word8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Word8be Source #

Packable Word8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Word8be -> Value Word8be -> Packer Source #

packer :: Word8be -> Value Word8be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable Word8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Word8be -> Unpacker (Value Word8be) Source #

unpacker :: Word8be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Word8be -> IO ()) -> IO () Source #

type Value Word8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

data Int8be Source #

Big-endian 8-bit signed integer.

Constructors

Int8be 

Instances

Instances details
Show Int8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Eq Int8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

(==) :: Int8be -> Int8be -> Bool #

(/=) :: Int8be -> Int8be -> Bool #

Format Int8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Int8be Source #

Packable Int8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Int8be -> Value Int8be -> Packer Source #

packer :: Int8be -> Value Int8be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable Int8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Int8be -> Unpacker (Value Int8be) Source #

unpacker :: Int8be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Int8be -> IO ()) -> IO () Source #

type Value Int8be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

16-bit binary

data Word16be Source #

Big-endian 32-bit unsigned word.

Constructors

Word16be 

Instances

Instances details
Show Word16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Eq Word16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Format Word16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Word16be Source #

Packable Word16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Word16be -> Value Word16be -> Packer Source #

packer :: Word16be -> Value Word16be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable Word16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Word16be -> Unpacker (Value Word16be) Source #

unpacker :: Word16be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Word16be -> IO ()) -> IO () Source #

type Value Word16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

data Int16be Source #

Constructors

Int16be 

Instances

Instances details
Show Int16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Eq Int16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

(==) :: Int16be -> Int16be -> Bool #

(/=) :: Int16be -> Int16be -> Bool #

Format Int16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Int16be Source #

Packable Int16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Int16be -> Value Int16be -> Packer Source #

packer :: Int16be -> Value Int16be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable Int16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Int16be -> Unpacker (Value Int16be) Source #

unpacker :: Int16be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Int16be -> IO ()) -> IO () Source #

type Value Int16be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

32-bit binary

data Word32be Source #

Big-endian 32-bit unsigned word.

Constructors

Word32be 

Instances

Instances details
Show Word32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Eq Word32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Format Word32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Word32be Source #

Packable Word32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Word32be -> Value Word32be -> Packer Source #

packer :: Word32be -> Value Word32be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable Word32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Word32be -> Unpacker (Value Word32be) Source #

unpacker :: Word32be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Word32be -> IO ()) -> IO () Source #

type Value Word32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

data Int32be Source #

Big-endian 32-bit signed integer.

Constructors

Int32be 

Instances

Instances details
Show Int32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Eq Int32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

(==) :: Int32be -> Int32be -> Bool #

(/=) :: Int32be -> Int32be -> Bool #

Format Int32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Int32be Source #

Packable Int32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Int32be -> Value Int32be -> Packer Source #

packer :: Int32be -> Value Int32be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable Int32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Int32be -> Unpacker (Value Int32be) Source #

unpacker :: Int32be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Int32be -> IO ()) -> IO () Source #

type Value Int32be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

data Float32be Source #

Big-endian 32-bit IEEE 754 float.

Constructors

Float32be 

64-bit binary

data Word64be Source #

Big-endian 64-bit unsigned word.

Constructors

Word64be 

Instances

Instances details
Show Word64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Eq Word64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Format Word64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Word64be Source #

Packable Word64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Word64be -> Value Word64be -> Packer Source #

packer :: Word64be -> Value Word64be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable Word64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Word64be -> Unpacker (Value Word64be) Source #

unpacker :: Word64be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Word64be -> IO ()) -> IO () Source #

type Value Word64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

data Int64be Source #

Big-endian 64-bit signed integer.

Constructors

Int64be 

Instances

Instances details
Show Int64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Eq Int64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

(==) :: Int64be -> Int64be -> Bool #

(/=) :: Int64be -> Int64be -> Bool #

Format Int64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Associated Types

type Value Int64be Source #

Packable Int64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

pack :: Int64be -> Value Int64be -> Packer Source #

packer :: Int64be -> Value Int64be -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Unpackable Int64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

Methods

unpack :: Int64be -> Unpacker (Value Int64be) Source #

unpacker :: Int64be -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value Int64be -> IO ()) -> IO () Source #

type Value Int64be Source # 
Instance details

Defined in Data.Repa.Convert.Format.Binary

data Float64be Source #

Big-endian 64-bit IEEE 754 float.

Constructors

Float64be 

Compounds

Appended fields

data App f Source #

Append fields without separators.

Constructors

App f 

Instances

Instances details
(Format f1, Format (App fs), Value (App fs) ~ Value fs) => Format (App (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Associated Types

type Value (App (f1 :*: fs)) Source #

Methods

fieldCount :: App (f1 :*: fs) -> Int Source #

minSize :: App (f1 :*: fs) -> Int Source #

fixedSize :: App (f1 :*: fs) -> Maybe Int Source #

packedSize :: App (f1 :*: fs) -> Value (App (f1 :*: fs)) -> Maybe Int Source #

Format (App ()) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Associated Types

type Value (App ()) Source #

Methods

fieldCount :: App () -> Int Source #

minSize :: App () -> Int Source #

fixedSize :: App () -> Maybe Int Source #

packedSize :: App () -> Value (App ()) -> Maybe Int Source #

(Packable f1, Packable (App fs), Value (App fs) ~ Value fs) => Packable (App (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Methods

pack :: App (f1 :*: fs) -> Value (App (f1 :*: fs)) -> Packer Source #

packer :: App (f1 :*: fs) -> Value (App (f1 :*: fs)) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable (App ()) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Methods

pack :: App () -> Value (App ()) -> Packer Source #

packer :: App () -> Value (App ()) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

(Unpackable f1, Unpackable (App fs), Value (App fs) ~ Value fs) => Unpackable (App (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Methods

unpack :: App (f1 :*: fs) -> Unpacker (Value (App (f1 :*: fs))) Source #

unpacker :: App (f1 :*: fs) -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (App (f1 :*: fs)) -> IO ()) -> IO () Source #

Unpackable (App ()) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Methods

unpack :: App () -> Unpacker (Value (App ())) Source #

unpacker :: App () -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (App ()) -> IO ()) -> IO () Source #

type Value (App (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

type Value (App (f1 :*: fs)) = Value f1 :*: Value fs
type Value (App ()) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

type Value (App ()) = ()

Separated fields

data Sep f where Source #

Separate fields with the given character.

  • The separating character is un-escapable.
  • The format (Sep ',') does NOT parse a CSV file according to the CSV specification: http://tools.ietf.org/html/rfc4180.
  • The type is kept abstract as we cache some pre-computed values we use to unpack this format. Use mkSep to make one.

Constructors

SepNil :: Sep () 
SepCons :: !SepMeta -> !f -> Sep fs -> Sep (f :*: fs) 

Instances

Instances details
(Format f1, Format (Sep fs), Value (Sep fs) ~ Value fs) => Format (Sep (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Associated Types

type Value (Sep (f1 :*: fs)) Source #

Methods

fieldCount :: Sep (f1 :*: fs) -> Int Source #

minSize :: Sep (f1 :*: fs) -> Int Source #

fixedSize :: Sep (f1 :*: fs) -> Maybe Int Source #

packedSize :: Sep (f1 :*: fs) -> Value (Sep (f1 :*: fs)) -> Maybe Int Source #

Format (Sep ()) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Associated Types

type Value (Sep ()) Source #

Methods

fieldCount :: Sep () -> Int Source #

minSize :: Sep () -> Int Source #

fixedSize :: Sep () -> Maybe Int Source #

packedSize :: Sep () -> Value (Sep ()) -> Maybe Int Source #

(Packable f1, Packable (Sep (f2 :*: fs)), Value (Sep (f2 :*: fs)) ~ Value (f2 :*: fs), Value (Sep fs) ~ Value fs) => Packable (Sep (f1 :*: (f2 :*: fs))) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

pack :: Sep (f1 :*: (f2 :*: fs)) -> Value (Sep (f1 :*: (f2 :*: fs))) -> Packer Source #

packer :: Sep (f1 :*: (f2 :*: fs)) -> Value (Sep (f1 :*: (f2 :*: fs))) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

(Packable f1, Value (Sep ()) ~ Value ()) => Packable (Sep (f1 :*: ())) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

pack :: Sep (f1 :*: ()) -> Value (Sep (f1 :*: ())) -> Packer Source #

packer :: Sep (f1 :*: ()) -> Value (Sep (f1 :*: ())) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

Packable (Sep ()) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

pack :: Sep () -> Value (Sep ()) -> Packer Source #

packer :: Sep () -> Value (Sep ()) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

(Unpackable f1, Unpackable (Sep (f2 :*: fs)), Value (Sep (f2 :*: fs)) ~ Value (f2 :*: fs), Value (Sep fs) ~ Value fs) => Unpackable (Sep (f1 :*: (f2 :*: fs))) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

unpack :: Sep (f1 :*: (f2 :*: fs)) -> Unpacker (Value (Sep (f1 :*: (f2 :*: fs)))) Source #

unpacker :: Sep (f1 :*: (f2 :*: fs)) -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (Sep (f1 :*: (f2 :*: fs))) -> IO ()) -> IO () Source #

(Unpackable f1, Value (Sep ()) ~ Value ()) => Unpackable (Sep (f1 :*: ())) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

unpack :: Sep (f1 :*: ()) -> Unpacker (Value (Sep (f1 :*: ()))) Source #

unpacker :: Sep (f1 :*: ()) -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (Sep (f1 :*: ())) -> IO ()) -> IO () Source #

Unpackable (Sep ()) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

unpack :: Sep () -> Unpacker (Value (Sep ())) Source #

unpacker :: Sep () -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (Sep ()) -> IO ()) -> IO () Source #

type Value (Sep (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

type Value (Sep (f1 :*: fs)) = Value f1 :*: Value fs
type Value (Sep ()) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

type Value (Sep ()) = ()

class SepFormat f where Source #

Methods

mkSep :: Char -> f -> Sep f Source #

takeSepChar :: Sep f -> Maybe Char Source #

Instances

Instances details
SepFormat () Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

mkSep :: Char -> () -> Sep () Source #

takeSepChar :: Sep () -> Maybe Char Source #

(Format f1, SepFormat fs) => SepFormat (f1 :*: fs) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

mkSep :: Char -> (f1 :*: fs) -> Sep (f1 :*: fs) Source #

takeSepChar :: Sep (f1 :*: fs) -> Maybe Char Source #

Object with labeled fields

data Object fields Source #

Format of a simple object format with labeled fields.

Instances

Instances details
(Format (ObjectFields fs), Value (ObjectFields fs) ~ Value fs) => Format (Object fs) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Object

Associated Types

type Value (Object fs) Source #

(Format (Object f), Value (ObjectFields f) ~ Value f, Packable (ObjectFields f)) => Packable (Object f) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Object

Methods

pack :: Object f -> Value (Object f) -> Packer Source #

packer :: Object f -> Value (Object f) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

type Value (Object fs) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Object

type Value (Object fs) = Value fs

class ObjectFormat f Source #

Minimal complete definition

mkObjectFields

Instances

Instances details
ObjectFormat () Source # 
Instance details

Defined in Data.Repa.Convert.Format.Object

Associated Types

type ObjectFormat' ()

Methods

mkObjectFields :: () -> ObjectFields (ObjectFormat' ())

(Format f1, ObjectFormat fs) => ObjectFormat (Field f1 :*: fs) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Object

Associated Types

type ObjectFormat' (Field f1 :*: fs)

Methods

mkObjectFields :: (Field f1 :*: fs) -> ObjectFields (ObjectFormat' (Field f1 :*: fs))

data Field f Source #

A single field in an object.

Constructors

Field 

Instances

Instances details
(Format f1, ObjectFormat fs) => ObjectFormat (Field f1 :*: fs) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Object

Associated Types

type ObjectFormat' (Field f1 :*: fs)

Methods

mkObjectFields :: (Field f1 :*: fs) -> ObjectFields (ObjectFormat' (Field f1 :*: fs))

mkObject :: ObjectFormat f => f -> Object (ObjectFormat' f) Source #

Make an object format with the given labeled fields. For example:

> let fmt =   mkObject
          $   Field "index"   IntAsc                      Nothing
          :*: Field "message" (VarCharString '-')         Nothing
          :*: Field "value"   (MaybeChars NULL DoubleAsc) (Just isJust)
          :*: ()

Packing this produces:

> let Just str = packToString fmt (27 :*: "foo" :*: Nothing :*: ())
> putStrLn str
> {"index":27,"message":"foo"}

Note that the encodings that this format can generate are a superset of the JavaScript Object Notation (JSON). With the Repa format, the fields of an object can directly encode dates and other values, wheras in JSON these values must be represented by strings.

Products

data a :*: b infixr 9 #

A strict product type, written infix.

Constructors

!a :*: !b infixr 9 

Instances

Instances details
IsProdList ts => Discard 'Z (t1 :*: ts) 
Instance details

Defined in Data.Repa.Scalar.Product

Associated Types

type Discard' 'Z (t1 :*: ts) #

Methods

discard :: Nat 'Z -> (t1 :*: ts) -> Discard' 'Z (t1 :*: ts) #

IsProdList ts => Select 'Z (t1 :*: ts) 
Instance details

Defined in Data.Repa.Scalar.Product

Associated Types

type Select' 'Z (t1 :*: ts) #

Methods

select :: Nat 'Z -> (t1 :*: ts) -> Select' 'Z (t1 :*: ts) #

(Unbox a, Unbox b) => Vector Vector (a :*: b) 
Instance details

Defined in Data.Repa.Scalar.Product

Methods

basicUnsafeFreeze :: Mutable Vector s (a :*: b) -> ST s (Vector (a :*: b))

basicUnsafeThaw :: Vector (a :*: b) -> ST s (Mutable Vector s (a :*: b))

basicLength :: Vector (a :*: b) -> Int

basicUnsafeSlice :: Int -> Int -> Vector (a :*: b) -> Vector (a :*: b)

basicUnsafeIndexM :: Vector (a :*: b) -> Int -> Box (a :*: b)

basicUnsafeCopy :: Mutable Vector s (a :*: b) -> Vector (a :*: b) -> ST s ()

elemseq :: Vector (a :*: b) -> (a :*: b) -> b0 -> b0

(Unbox a, Unbox b) => MVector MVector (a :*: b) 
Instance details

Defined in Data.Repa.Scalar.Product

Methods

basicLength :: MVector s (a :*: b) -> Int

basicUnsafeSlice :: Int -> Int -> MVector s (a :*: b) -> MVector s (a :*: b)

basicOverlaps :: MVector s (a :*: b) -> MVector s (a :*: b) -> Bool

basicUnsafeNew :: Int -> ST s (MVector s (a :*: b))

basicInitialize :: MVector s (a :*: b) -> ST s ()

basicUnsafeReplicate :: Int -> (a :*: b) -> ST s (MVector s (a :*: b))

basicUnsafeRead :: MVector s (a :*: b) -> Int -> ST s (a :*: b)

basicUnsafeWrite :: MVector s (a :*: b) -> Int -> (a :*: b) -> ST s ()

basicClear :: MVector s (a :*: b) -> ST s ()

basicSet :: MVector s (a :*: b) -> (a :*: b) -> ST s ()

basicUnsafeCopy :: MVector s (a :*: b) -> MVector s (a :*: b) -> ST s ()

basicUnsafeMove :: MVector s (a :*: b) -> MVector s (a :*: b) -> ST s ()

basicUnsafeGrow :: MVector s (a :*: b) -> Int -> ST s (MVector s (a :*: b))

Functor ((:*:) a) 
Instance details

Defined in Data.Repa.Scalar.Product

Methods

fmap :: (a0 -> b) -> (a :*: a0) -> a :*: b #

(<$) :: a0 -> (a :*: b) -> a :*: a0 #

(Format f1, Format (App fs), Value (App fs) ~ Value fs) => Format (App (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Associated Types

type Value (App (f1 :*: fs)) Source #

Methods

fieldCount :: App (f1 :*: fs) -> Int Source #

minSize :: App (f1 :*: fs) -> Int Source #

fixedSize :: App (f1 :*: fs) -> Maybe Int Source #

packedSize :: App (f1 :*: fs) -> Value (App (f1 :*: fs)) -> Maybe Int Source #

(Format f1, Format (Sep fs), Value (Sep fs) ~ Value fs) => Format (Sep (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Associated Types

type Value (Sep (f1 :*: fs)) Source #

Methods

fieldCount :: Sep (f1 :*: fs) -> Int Source #

minSize :: Sep (f1 :*: fs) -> Int Source #

fixedSize :: Sep (f1 :*: fs) -> Maybe Int Source #

packedSize :: Sep (f1 :*: fs) -> Value (Sep (f1 :*: fs)) -> Maybe Int Source #

(Packable f1, Packable (App fs), Value (App fs) ~ Value fs) => Packable (App (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Methods

pack :: App (f1 :*: fs) -> Value (App (f1 :*: fs)) -> Packer Source #

packer :: App (f1 :*: fs) -> Value (App (f1 :*: fs)) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

(Packable f1, Packable (Sep (f2 :*: fs)), Value (Sep (f2 :*: fs)) ~ Value (f2 :*: fs), Value (Sep fs) ~ Value fs) => Packable (Sep (f1 :*: (f2 :*: fs))) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

pack :: Sep (f1 :*: (f2 :*: fs)) -> Value (Sep (f1 :*: (f2 :*: fs))) -> Packer Source #

packer :: Sep (f1 :*: (f2 :*: fs)) -> Value (Sep (f1 :*: (f2 :*: fs))) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

(Packable f1, Value (Sep ()) ~ Value ()) => Packable (Sep (f1 :*: ())) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

pack :: Sep (f1 :*: ()) -> Value (Sep (f1 :*: ())) -> Packer Source #

packer :: Sep (f1 :*: ()) -> Value (Sep (f1 :*: ())) -> Addr# -> IO () -> (Addr# -> IO ()) -> IO () Source #

(Unpackable f1, Unpackable (App fs), Value (App fs) ~ Value fs) => Unpackable (App (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

Methods

unpack :: App (f1 :*: fs) -> Unpacker (Value (App (f1 :*: fs))) Source #

unpacker :: App (f1 :*: fs) -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (App (f1 :*: fs)) -> IO ()) -> IO () Source #

(Unpackable f1, Unpackable (Sep (f2 :*: fs)), Value (Sep (f2 :*: fs)) ~ Value (f2 :*: fs), Value (Sep fs) ~ Value fs) => Unpackable (Sep (f1 :*: (f2 :*: fs))) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

unpack :: Sep (f1 :*: (f2 :*: fs)) -> Unpacker (Value (Sep (f1 :*: (f2 :*: fs)))) Source #

unpacker :: Sep (f1 :*: (f2 :*: fs)) -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (Sep (f1 :*: (f2 :*: fs))) -> IO ()) -> IO () Source #

(Unpackable f1, Value (Sep ()) ~ Value ()) => Unpackable (Sep (f1 :*: ())) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

unpack :: Sep (f1 :*: ()) -> Unpacker (Value (Sep (f1 :*: ()))) Source #

unpacker :: Sep (f1 :*: ()) -> Addr# -> Addr# -> (Word8 -> Bool) -> IO () -> (Addr# -> Value (Sep (f1 :*: ())) -> IO ()) -> IO () Source #

Discard n ts => Discard ('S n) (t1 :*: ts) 
Instance details

Defined in Data.Repa.Scalar.Product

Associated Types

type Discard' ('S n) (t1 :*: ts) #

Methods

discard :: Nat ('S n) -> (t1 :*: ts) -> Discard' ('S n) (t1 :*: ts) #

Select n ts => Select ('S n) (t1 :*: ts) 
Instance details

Defined in Data.Repa.Scalar.Product

Associated Types

type Select' ('S n) (t1 :*: ts) #

Methods

select :: Nat ('S n) -> (t1 :*: ts) -> Select' ('S n) (t1 :*: ts) #

(Show a, Show b) => Show (a :*: b) 
Instance details

Defined in Data.Repa.Scalar.Product

Methods

showsPrec :: Int -> (a :*: b) -> ShowS #

show :: (a :*: b) -> String #

showList :: [a :*: b] -> ShowS #

(Eq a, Eq b) => Eq (a :*: b) 
Instance details

Defined in Data.Repa.Scalar.Product

Methods

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

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

(Format f1, ObjectFormat fs) => ObjectFormat (Field f1 :*: fs) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Object

Associated Types

type ObjectFormat' (Field f1 :*: fs)

Methods

mkObjectFields :: (Field f1 :*: fs) -> ObjectFields (ObjectFormat' (Field f1 :*: fs))

(Format f1, SepFormat fs) => SepFormat (f1 :*: fs) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

Methods

mkSep :: Char -> (f1 :*: fs) -> Sep (f1 :*: fs) Source #

takeSepChar :: Sep (f1 :*: fs) -> Maybe Char Source #

(Format a, Format b) => Format (a :*: b) Source #

Formatting fields.

Instance details

Defined in Data.Repa.Convert.Format.Fields

Associated Types

type Value (a :*: b) Source #

Methods

fieldCount :: (a :*: b) -> Int Source #

minSize :: (a :*: b) -> Int Source #

fixedSize :: (a :*: b) -> Maybe Int Source #

packedSize :: (a :*: b) -> Value (a :*: b) -> Maybe Int Source #

(IsKeyValues p, IsKeyValues ps, Keys p ~ Keys ps) => IsKeyValues (p :*: ps) 
Instance details

Defined in Data.Repa.Scalar.Product

Associated Types

type Keys (p :*: ps) #

type Values (p :*: ps) #

Methods

keys :: (p :*: ps) -> [Keys (p :*: ps)] #

values :: (p :*: ps) -> Values (p :*: ps) #

IsProdList fs => IsProdList (f :*: fs) 
Instance details

Defined in Data.Repa.Scalar.Product

Methods

isProdList :: (f :*: fs) -> Bool #

(Unbox a, Unbox b) => Unbox (a :*: b) 
Instance details

Defined in Data.Repa.Scalar.Product

Mask ms ts => Mask (Drop :*: ms) (t1 :*: ts) 
Instance details

Defined in Data.Repa.Scalar.Product

Associated Types

type Mask' (Drop :*: ms) (t1 :*: ts) #

Methods

mask :: (Drop :*: ms) -> (t1 :*: ts) -> Mask' (Drop :*: ms) (t1 :*: ts) #

Mask ms ts => Mask (Keep :*: ms) (t1 :*: ts) 
Instance details

Defined in Data.Repa.Scalar.Product

Associated Types

type Mask' (Keep :*: ms) (t1 :*: ts) #

Methods

mask :: (Keep :*: ms) -> (t1 :*: ts) -> Mask' (Keep :*: ms) (t1 :*: ts) #

type Discard' 'Z (t1 :*: ts) 
Instance details

Defined in Data.Repa.Scalar.Product

type Discard' 'Z (t1 :*: ts) = ts
type Select' 'Z (t1 :*: ts) 
Instance details

Defined in Data.Repa.Scalar.Product

type Select' 'Z (t1 :*: ts) = t1
data MVector s (a :*: b) 
Instance details

Defined in Data.Repa.Scalar.Product

data MVector s (a :*: b) = MV_Prod !Int !(MVector s a) !(MVector s b)
type Value (App (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.App

type Value (App (f1 :*: fs)) = Value f1 :*: Value fs
type Value (Sep (f1 :*: fs)) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Sep

type Value (Sep (f1 :*: fs)) = Value f1 :*: Value fs
type Discard' ('S n) (t1 :*: ts) 
Instance details

Defined in Data.Repa.Scalar.Product

type Discard' ('S n) (t1 :*: ts) = t1 :*: Discard' n ts
type Select' ('S n) (t1 :*: ts) 
Instance details

Defined in Data.Repa.Scalar.Product

type Select' ('S n) (t1 :*: ts) = Select' n ts
type Value (a :*: b) Source # 
Instance details

Defined in Data.Repa.Convert.Format.Fields

type Value (a :*: b) = Value a :*: Value b
type Keys (p :*: ps) 
Instance details

Defined in Data.Repa.Scalar.Product

type Keys (p :*: ps) = Keys p
type Values (p :*: ps) 
Instance details

Defined in Data.Repa.Scalar.Product

type Values (p :*: ps) = Values p :*: Values ps
data Vector (a :*: b) 
Instance details

Defined in Data.Repa.Scalar.Product

data Vector (a :*: b) = V_Prod !Int !(Vector a) !(Vector b)
type Mask' (Drop :*: ms) (t1 :*: ts) 
Instance details

Defined in Data.Repa.Scalar.Product

type Mask' (Drop :*: ms) (t1 :*: ts) = Mask' ms ts
type Mask' (Keep :*: ms) (t1 :*: ts) 
Instance details

Defined in Data.Repa.Scalar.Product

type Mask' (Keep :*: ms) (t1 :*: ts) = t1 :*: Mask' ms ts