| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.Meep
Description
Synopsis
- data Meep k a
- empty :: Meep k a
- singleton :: k -> a -> Meep k a
- size :: Num b => Meep k a -> b
- null :: Meep k a -> Bool
- fromMaybe :: Maybe (k, a) -> Meep k a
- toMaybe :: Meep k a -> Maybe (k, a)
- maybeing :: Iso (Meep k v) (Meep k' v') (Maybe (k, v)) (Maybe (k', v'))
- intersection :: Eq k => Meep k a -> Meep k b -> Meep k a
- intersectionWith :: Eq k => (a -> b -> c) -> Meep k a -> Meep k b -> Meep k c
- intersectionWithKey :: Eq k => (k -> a -> b -> c) -> Meep k a -> Meep k b -> Meep k c
- keys :: Meep k a -> Maybe k
- elems :: Meep k a -> Maybe a
Documentation
A Meep from key k to value a
Instances
| Bitraversable Meep Source # | |
Defined in Data.Meep Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Meep a b -> f (Meep c d) # | |
| Bifoldable Meep Source # | |
| Bifunctor Meep Source # | |
| Biapply Meep Source # | |
| FunctorWithIndex k (Meep k) Source # | |
| FoldableWithIndex k (Meep k) Source # | |
Defined in Data.Meep Methods ifoldMap :: Monoid m => (k -> a -> m) -> Meep k a -> m # ifolded :: (Indexable k p, Contravariant f, Applicative f) => p a (f a) -> Meep k a -> f (Meep k a) # ifoldr :: (k -> a -> b -> b) -> b -> Meep k a -> b # ifoldl :: (k -> b -> a -> b) -> b -> Meep k a -> b # | |
| TraversableWithIndex k (Meep k) Source # | |
Defined in Data.Meep Methods itraverse :: Applicative f => (k -> a -> f b) -> Meep k a -> f (Meep k b) # itraversed :: (Indexable k p, Applicative f) => p a (f b) -> Meep k a -> f (Meep k b) # | |
| Functor (Meep k) Source # | |
| Foldable (Meep k) Source # | |
Defined in Data.Meep Methods fold :: Monoid m => Meep k m -> m # foldMap :: Monoid m => (a -> m) -> Meep k a -> m # foldr :: (a -> b -> b) -> b -> Meep k a -> b # foldr' :: (a -> b -> b) -> b -> Meep k a -> b # foldl :: (b -> a -> b) -> b -> Meep k a -> b # foldl' :: (b -> a -> b) -> b -> Meep k a -> b # foldr1 :: (a -> a -> a) -> Meep k a -> a # foldl1 :: (a -> a -> a) -> Meep k a -> a # elem :: Eq a => a -> Meep k a -> Bool # maximum :: Ord a => Meep k a -> a # minimum :: Ord a => Meep k a -> a # | |
| Traversable (Meep k) Source # | |
| Eq k => Apply (Meep k) Source # | |
| (Eq k, Eq a) => Eq (Meep k a) Source # | |
| (Data k, Data a) => Data (Meep k a) Source # | |
Defined in Data.Meep Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Meep k a -> c (Meep k a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Meep k a) # toConstr :: Meep k a -> Constr # dataTypeOf :: Meep k a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Meep k a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Meep k a)) # gmapT :: (forall b. Data b => b -> b) -> Meep k a -> Meep k a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Meep k a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Meep k a -> r # gmapQ :: (forall d. Data d => d -> u) -> Meep k a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Meep k a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Meep k a -> m (Meep k a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Meep k a -> m (Meep k a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Meep k a -> m (Meep k a) # | |
| (Ord k, Ord a) => Ord (Meep k a) Source # | |
Defined in Data.Meep | |
| (Show k, Show a) => Show (Meep k a) Source # | |
| Generic (Meep k a) Source # | |
| (Eq k, Semigroup a) => Semigroup (Meep k a) Source # |
|
| Eq k => Ixed (Meep k a) Source # | |
| Eq k => At (Meep k a) Source # | |
| AsEmpty (Meep k a) Source # | |
| type Rep (Meep k a) Source # | |
Defined in Data.Meep type Rep (Meep k a) = D1 (MetaData "Meep" "Data.Meep" "meep-0.1.2.2-APY5BbX8ClaA3Myq1d9LWV" False) (C1 (MetaCons "Empty" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Meep" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 k) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))) | |
| type Index (Meep k a) Source # | |
| type IxValue (Meep k a) Source # | |
intersection :: Eq k => Meep k a -> Meep k b -> Meep k a Source #
O(1). Intersection of two Meeps
intersection ≡intersectionWithconst
intersectionWith :: Eq k => (a -> b -> c) -> Meep k a -> Meep k b -> Meep k c Source #
O(1). Intersection of two Meeps with a combining function
>>>intersectionWith (+) (Meep "hello" 4) (Meep "hello" 7)fromMaybe (Just ("hello",11))
>>>intersectionWith (+) (Meep "hello" 4) (Meep "bye" 7)fromMaybe Nothing
>>>intersectionWith (+) Empty (Meep "hello" 7)fromMaybe Nothing
intersectionWith f ≡ intersectionWithKey (const f)
intersectionWithKey :: Eq k => (k -> a -> b -> c) -> Meep k a -> Meep k b -> Meep k c Source #
O(1). Intersection of two Meeps with a combining function