Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Data.Map.Vector
Synopsis
- data MapVector k v
- = MapVector (Map k v)
- | ConstantMap v
Documentation
Note: <*>
in the Applicative
instance operates under intersection. i.e.:
>>>
(MapVector $ Map.fromList [("x", id)]) <*> (MapVector $ Map.fromList [("y", 3)])
MapVector (fromList [])
Use the Applicative
instance for elementwise operations:
>>>
liftA2 (*) (MapVector $ Map.fromList [("x", 2), ("y", 3)]) (MapVector $ Map.fromList [("x", 5),("y", 7)])
MapVector (fromList [("x",10),("y",21)])
>>>
liftA2 (*) (MapVector $ Map.fromList [("x", 2), ("y", 3)]) (MapVector $ Map.fromList [("y", 7)])
MapVector (fromList [("y",21)])
*^
in the VectorSpace
instance multiplies by the scalar of v. Nesting MapVectors preserves
the scalar type, e.g. Scalar (MapVector k (MapVector k' v))
= Scalar v
.
>>>
2 *^ (ConstantMap $ MapVector $ Map.fromList [("x", 3 :: Int), ("y", 5)])
ConstantMap (MapVector (fromList [("x",6),("y",10)]))
Finally, <.>
in InnerSpace
is the dot-product operator. Again, it operates under intersection.
>>>
(MapVector $ Map.fromList [("x", 2 :: Int), ("y", 3)]) <.> (MapVector $ Map.fromList [("x", 5),("y", 7)])
31
>>>
(pure . MapVector $ Map.fromList [("x", 2 :: Int), ("y", 3)]) <.> (MapVector $ Map.fromList [("a", pure (5::Int))])
25
Addition with ^+^
operates under union.
Constructors
MapVector (Map k v) | |
ConstantMap v | An infinite-dimensional vector with the same value on all dimensions |
Instances
Functor (MapVector k) Source # | |
Ord k => Applicative (MapVector k) Source # | |
Defined in Data.Map.Vector | |
Foldable (MapVector k) Source # | |
Defined in Data.Map.Vector Methods fold :: Monoid m => MapVector k m -> m # foldMap :: Monoid m => (a -> m) -> MapVector k a -> m # foldr :: (a -> b -> b) -> b -> MapVector k a -> b # foldr' :: (a -> b -> b) -> b -> MapVector k a -> b # foldl :: (b -> a -> b) -> b -> MapVector k a -> b # foldl' :: (b -> a -> b) -> b -> MapVector k a -> b # foldr1 :: (a -> a -> a) -> MapVector k a -> a # foldl1 :: (a -> a -> a) -> MapVector k a -> a # toList :: MapVector k a -> [a] # null :: MapVector k a -> Bool # length :: MapVector k a -> Int # elem :: Eq a => a -> MapVector k a -> Bool # maximum :: Ord a => MapVector k a -> a # minimum :: Ord a => MapVector k a -> a # | |
Traversable (MapVector k) Source # | |
Defined in Data.Map.Vector | |
(Eq k, Eq v) => Eq (MapVector k v) Source # | |
(Data k, Data v, Ord k) => Data (MapVector k v) Source # | |
Defined in Data.Map.Vector Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MapVector k v -> c (MapVector k v) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MapVector k v) # toConstr :: MapVector k v -> Constr # dataTypeOf :: MapVector k v -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MapVector k v)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MapVector k v)) # gmapT :: (forall b. Data b => b -> b) -> MapVector k v -> MapVector k v # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MapVector k v -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MapVector k v -> r # gmapQ :: (forall d. Data d => d -> u) -> MapVector k v -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MapVector k v -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MapVector k v -> m (MapVector k v) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MapVector k v -> m (MapVector k v) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MapVector k v -> m (MapVector k v) # | |
(Ord k, Read k, Read v) => Read (MapVector k v) Source # | |
(Show k, Show v) => Show (MapVector k v) Source # | |
Semigroup (MapVector k v) Source # | |
(Ord k, Monoid v) => Monoid (MapVector k v) Source # | |
(Ord k, HasBasis v, AdditiveGroup (Scalar v)) => HasBasis (MapVector k v) Source # | |
(Ord k, VectorSpace v) => VectorSpace (MapVector k v) Source # | |
(Ord k, VectorSpace v, InnerSpace v, AdditiveGroup (Scalar v)) => InnerSpace (MapVector k v) Source # | |
(AdditiveGroup v, Ord k) => AdditiveGroup (MapVector k v) Source # | |
type Basis (MapVector k v) Source # | |
Defined in Data.Map.Vector | |
type Scalar (MapVector k v) Source # | |
Defined in Data.Map.Vector |