fixed-vector-2.0.0.0: Generic vectors with statically known size.
Safe HaskellNone
LanguageHaskell2010

Data.Vector.Fixed.Unboxed

Description

Adaptive array type which picks vector representation from type of element of array. For example arrays of Double are backed by ByteArray, arrays of Bool are represented as bit-vector, arrays of tuples are products of arrays. Unbox type class is used to describe representation of an array.

Synopsis

Data type

newtype Vec (n :: Nat) a Source #

Adaptive array of dimension n and containing elements of type a.

Constructors

Vec 

Fields

Instances

Instances details
(Arity n, Unbox n a) => Vector (Vec n) a Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

construct :: Fun (Dim (Vec n)) a (Vec n a) Source #

inspect :: Vec n a -> Fun (Dim (Vec n)) a b -> b Source #

basicIndex :: Vec n a -> Int -> a Source #

(Typeable n, Unbox n a, Data a) => Data (Vec n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vec n a -> c (Vec n a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vec n a) #

toConstr :: Vec n a -> Constr #

dataTypeOf :: Vec n a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vec n a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vec n a)) #

gmapT :: (forall b. Data b => b -> b) -> Vec n a -> Vec n a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vec n a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vec n a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Vec n a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Vec n a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vec n a -> m (Vec n a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vec n a -> m (Vec n a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vec n a -> m (Vec n a) #

(Unbox n a, Storable a) => Storable (Vec n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

sizeOf :: Vec n a -> Int #

alignment :: Vec n a -> Int #

peekElemOff :: Ptr (Vec n a) -> Int -> IO (Vec n a) #

pokeElemOff :: Ptr (Vec n a) -> Int -> Vec n a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Vec n a) #

pokeByteOff :: Ptr b -> Int -> Vec n a -> IO () #

peek :: Ptr (Vec n a) -> IO (Vec n a) #

poke :: Ptr (Vec n a) -> Vec n a -> IO () #

(Unbox n a, Monoid a) => Monoid (Vec n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

mempty :: Vec n a #

mappend :: Vec n a -> Vec n a -> Vec n a #

mconcat :: [Vec n a] -> Vec n a #

(Unbox n a, Semigroup a) => Semigroup (Vec n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

(<>) :: Vec n a -> Vec n a -> Vec n a #

sconcat :: NonEmpty (Vec n a) -> Vec n a #

stimes :: Integral b => b -> Vec n a -> Vec n a #

(Unbox n a, Show a) => Show (Vec n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

showsPrec :: Int -> Vec n a -> ShowS #

show :: Vec n a -> String #

showList :: [Vec n a] -> ShowS #

(Unbox n a, NFData a) => NFData (Vec n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

rnf :: Vec n a -> () #

(Unbox n a, Eq a) => Eq (Vec n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

(==) :: Vec n a -> Vec n a -> Bool #

(/=) :: Vec n a -> Vec n a -> Bool #

(Unbox n a, Ord a) => Ord (Vec n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

compare :: Vec n a -> Vec n a -> Ordering #

(<) :: Vec n a -> Vec n a -> Bool #

(<=) :: Vec n a -> Vec n a -> Bool #

(>) :: Vec n a -> Vec n a -> Bool #

(>=) :: Vec n a -> Vec n a -> Bool #

max :: Vec n a -> Vec n a -> Vec n a #

min :: Vec n a -> Vec n a -> Vec n a #

type Dim (Vec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

type Dim (Vec n) = Peano n

type Vec1 = Vec 1 Source #

type Vec2 = Vec 2 Source #

type Vec3 = Vec 3 Source #

type Vec4 = Vec 4 Source #

type Vec5 = Vec 5 Source #

Type classes & derivation

class (Dim (VecRepr n a) ~ Peano n, Vector (VecRepr n a) (EltRepr a)) => Unbox (n :: Nat) a Source #

Type class which selects internal representation of unboxed vector.

Crucial design constraint is this type class must be GND-derivable. And this rules out anything mentioning Fun, since all it's parameters has nominal role. Thus Vector is not GND-derivable and we have to take somewhat roundabout approach.

Minimal complete definition

toEltRepr, fromEltRepr

Instances

Instances details
(n <= 64, Arity n) => Unbox n All Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> All -> EltRepr All

fromEltRepr :: Proxy# n -> EltRepr All -> All

(n <= 64, Arity n) => Unbox n Any Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Any -> EltRepr Any

fromEltRepr :: Proxy# n -> EltRepr Any -> Any

Arity n => Unbox n Int16 Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Int16 -> EltRepr Int16

fromEltRepr :: Proxy# n -> EltRepr Int16 -> Int16

Arity n => Unbox n Int32 Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Int32 -> EltRepr Int32

fromEltRepr :: Proxy# n -> EltRepr Int32 -> Int32

Arity n => Unbox n Int64 Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Int64 -> EltRepr Int64

fromEltRepr :: Proxy# n -> EltRepr Int64 -> Int64

Arity n => Unbox n Int8 Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Int8 -> EltRepr Int8

fromEltRepr :: Proxy# n -> EltRepr Int8 -> Int8

Arity n => Unbox n Word16 Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Word16 -> EltRepr Word16

fromEltRepr :: Proxy# n -> EltRepr Word16 -> Word16

Arity n => Unbox n Word32 Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Word32 -> EltRepr Word32

fromEltRepr :: Proxy# n -> EltRepr Word32 -> Word32

Arity n => Unbox n Word64 Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Word64 -> EltRepr Word64

fromEltRepr :: Proxy# n -> EltRepr Word64 -> Word64

Arity n => Unbox n Word8 Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Word8 -> EltRepr Word8

fromEltRepr :: Proxy# n -> EltRepr Word8 -> Word8

Arity n => Unbox n () Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> () -> EltRepr ()

fromEltRepr :: Proxy# n -> EltRepr () -> ()

(n <= 64, Arity n) => Unbox n Bool Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Bool -> EltRepr Bool

fromEltRepr :: Proxy# n -> EltRepr Bool -> Bool

Arity n => Unbox n Char Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Char -> EltRepr Char

fromEltRepr :: Proxy# n -> EltRepr Char -> Char

Arity n => Unbox n Double Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Double -> EltRepr Double

fromEltRepr :: Proxy# n -> EltRepr Double -> Double

Arity n => Unbox n Float Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Float -> EltRepr Float

fromEltRepr :: Proxy# n -> EltRepr Float -> Float

Arity n => Unbox n Int Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Int -> EltRepr Int

fromEltRepr :: Proxy# n -> EltRepr Int -> Int

Arity n => Unbox n Word Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Word -> EltRepr Word

fromEltRepr :: Proxy# n -> EltRepr Word -> Word

Unbox n a => Unbox n (Complex a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Complex a -> EltRepr (Complex a)

fromEltRepr :: Proxy# n -> EltRepr (Complex a) -> Complex a

Unbox n a => Unbox n (Identity a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Identity a -> EltRepr (Identity a)

fromEltRepr :: Proxy# n -> EltRepr (Identity a) -> Identity a

Unbox n a => Unbox n (Down a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Down a -> EltRepr (Down a)

fromEltRepr :: Proxy# n -> EltRepr (Down a) -> Down a

Unbox n a => Unbox n (Dual a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Dual a -> EltRepr (Dual a)

fromEltRepr :: Proxy# n -> EltRepr (Dual a) -> Dual a

Unbox n a => Unbox n (Product a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Product a -> EltRepr (Product a)

fromEltRepr :: Proxy# n -> EltRepr (Product a) -> Product a

Unbox n a => Unbox n (Sum a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Sum a -> EltRepr (Sum a)

fromEltRepr :: Proxy# n -> EltRepr (Sum a) -> Sum a

(Arity n, Prim a) => Unbox n (UnboxViaPrim a) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> UnboxViaPrim a -> EltRepr (UnboxViaPrim a)

fromEltRepr :: Proxy# n -> EltRepr (UnboxViaPrim a) -> UnboxViaPrim a

(Unbox n a, Unbox n b) => Unbox n (a, b) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> (a, b) -> EltRepr (a, b)

fromEltRepr :: Proxy# n -> EltRepr (a, b) -> (a, b)

Unbox n a => Unbox n (Const a b) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

toEltRepr :: Proxy# n -> Const a b -> EltRepr (Const a b)

fromEltRepr :: Proxy# n -> EltRepr (Const a b) -> Const a b

data UnboxViaPrim a Source #

Wrapper for deriving Unbox for data types which are instances of Prim type class:

deriving via UnboxViaPrim Word instance (C.Arity n) => Unbox n Word

Concrete representations

data BitVec (n :: Nat) a Source #

Bit vector represented as 64-bit word. This puts upper limit on length of vector. It's not a big problem. 64-element will strain GHC quite a bit.

Instances

Instances details
(n <= 64, Arity n, a ~ Bool) => Vector (BitVec n) a Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

construct :: Fun (Dim (BitVec n)) a (BitVec n a) Source #

inspect :: BitVec n a -> Fun (Dim (BitVec n)) a b -> b Source #

basicIndex :: BitVec n a -> Int -> a Source #

type Dim (BitVec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

type Dim (BitVec n) = Peano n

data T2 (n :: Nat) a b x Source #

Representation for vector of 2-tuple as two vectors.

Constructors

T2 !(Vec n a) !(Vec n b) 

Instances

Instances details
(Arity n, Unbox n a, Unbox n b) => Vector (T2 n a b) (a, b) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

construct :: Fun (Dim (T2 n a b)) (a, b) (T2 n a b (a, b)) Source #

inspect :: T2 n a b (a, b) -> Fun (Dim (T2 n a b)) (a, b) b0 -> b0 Source #

basicIndex :: T2 n a b (a, b) -> Int -> (a, b) Source #

type Dim (T2 n a b) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

type Dim (T2 n a b) = Peano n

data T3 (n :: Nat) a b c x Source #

Representation for vector of 2-tuple as two vectors.

Constructors

T3 !(Vec n a) !(Vec n b) !(Vec n c) 

Instances

Instances details
(Arity n, Unbox n a, Unbox n b, Unbox n c) => Vector (T3 n a b c) (a, b, c) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

construct :: Fun (Dim (T3 n a b c)) (a, b, c) (T3 n a b c (a, b, c)) Source #

inspect :: T3 n a b c (a, b, c) -> Fun (Dim (T3 n a b c)) (a, b, c) b0 -> b0 Source #

basicIndex :: T3 n a b c (a, b, c) -> Int -> (a, b, c) Source #

type Dim (T3 n a b c) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

type Dim (T3 n a b c) = Peano n