Safe Haskell | None |
---|---|
Language | Haskell2010 |
Unboxed vectors with fixed length.
Immutable
data family Vec (n :: Nat) a Source #
Instances
Unbox n a => VectorN Vec n a Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
Unbox n a => Vector (Vec n) a Source # | |
Arity n => IVector (Vec n) All Source # | |
Arity n => IVector (Vec n) Any Source # | |
Arity n => IVector (Vec n) Double Source # | |
Arity n => IVector (Vec n) Float Source # | |
Arity n => IVector (Vec n) Char Source # | |
Arity n => IVector (Vec n) Word64 Source # | |
Arity n => IVector (Vec n) Word32 Source # | |
Arity n => IVector (Vec n) Word16 Source # | |
Arity n => IVector (Vec n) Word8 Source # | |
Arity n => IVector (Vec n) Word Source # | |
Arity n => IVector (Vec n) Int64 Source # | |
Arity n => IVector (Vec n) Int32 Source # | |
Arity n => IVector (Vec n) Int16 Source # | |
Arity n => IVector (Vec n) Int8 Source # | |
Arity n => IVector (Vec n) Int Source # | |
Arity n => IVector (Vec n) Bool Source # | |
Arity n => IVector (Vec n) () Source # | |
Unbox n a => IVector (Vec n) (Product a) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
Unbox n a => IVector (Vec n) (Sum a) Source # | |
Unbox n a => IVector (Vec n) (Dual a) Source # | |
Unbox n a => IVector (Vec n) (Down a) Source # | |
Unbox n a => IVector (Vec n) (Identity a) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
(Arity n, IVector (Vec n) a) => IVector (Vec n) (Complex a) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
(Arity n, IVector (Vec n) a, IVector (Vec n) b) => IVector (Vec n) (a, b) Source # | |
Unbox n a => IVector (Vec n) (Const a b) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
(Arity n, Vector (Vec n) a, Vector (Vec n) b, Vector (Vec n) c, IVector (Vec n) a, IVector (Vec n) b, IVector (Vec n) c) => IVector (Vec n) (a, b, c) Source # | |
(Unbox n a, Eq a) => Eq (Vec n a) Source # | |
(Typeable n, Unbox n a, Data a) => Data (Vec n a) Source # | |
Defined in Data.Vector.Fixed.Unboxed 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, Ord a) => Ord (Vec n a) Source # | |
(Arity n, Show a, Unbox n a) => Show (Vec n a) Source # | |
(Unbox n a, Semigroup a) => Semigroup (Vec n a) Source # | |
(Unbox n a, Monoid a) => Monoid (Vec n a) Source # | |
(Storable a, Unbox n a) => Storable (Vec n a) Source # | |
(Arity n, Unbox n a, NFData a) => NFData (Vec n a) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
newtype Vec n All Source # | |
newtype Vec n Any Source # | |
newtype Vec n Double Source # | |
newtype Vec n Float Source # | |
newtype Vec n Char Source # | |
newtype Vec n Word64 Source # | |
newtype Vec n Word32 Source # | |
newtype Vec n Word16 Source # | |
newtype Vec n Word8 Source # | |
newtype Vec n Word Source # | |
newtype Vec n Int64 Source # | |
newtype Vec n Int32 Source # | |
newtype Vec n Int16 Source # | |
newtype Vec n Int8 Source # | |
newtype Vec n Int Source # | |
newtype Vec n Bool Source # | |
data Vec n () Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
newtype Vec n (Product a) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
newtype Vec n (Sum a) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
newtype Vec n (Dual a) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
newtype Vec n (Down a) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
newtype Vec n (Identity a) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
newtype Vec n (Complex a) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
data Vec n (a, b) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
newtype Vec n (Const a b) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
data Vec n (a, b, c) Source # | |
type Dim (Vec n) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
type Mutable (Vec n) Source # | |
Defined in Data.Vector.Fixed.Unboxed |
Mutable
data family MVec (n :: Nat) s a Source #
Instances
Type classes
class (Arity n, IVector (Vec n) a, MVector (MVec n) a) => Unbox n a Source #