{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Data.Strict.IntMap.Internal where
import Data.IntMap.Lazy as L
import Data.Strict.IntMap.Autogen.Strict as S
import Control.Monad
import Data.Binary
import Data.Foldable.WithIndex
import Data.Functor.WithIndex
import Data.Traversable.WithIndex
import Data.Semigroup (Semigroup (..))
import Data.Strict.Classes
instance Strict (L.IntMap e) (S.IntMap e) where
toStrict :: IntMap e -> IntMap e
toStrict = forall a. [(Int, a)] -> IntMap a
S.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IntMap a -> [(Int, a)]
L.toList
toLazy :: IntMap e -> IntMap e
toLazy = forall a. [(Int, a)] -> IntMap a
L.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IntMap a -> [(Int, a)]
S.toList
{-# INLINE toStrict #-}
{-# INLINE toLazy #-}
instance FunctorWithIndex Int S.IntMap where
imap :: forall a b. (Int -> a -> b) -> IntMap a -> IntMap b
imap = forall a b. (Int -> a -> b) -> IntMap a -> IntMap b
S.mapWithKey
{-# INLINE imap #-}
instance FoldableWithIndex Int S.IntMap where
ifoldMap :: forall m a. Monoid m => (Int -> a -> m) -> IntMap a -> m
ifoldMap = forall m a. Monoid m => (Int -> a -> m) -> IntMap a -> m
S.foldMapWithKey
{-# INLINE ifoldMap #-}
ifoldr :: forall a b. (Int -> a -> b -> b) -> b -> IntMap a -> b
ifoldr = forall a b. (Int -> a -> b -> b) -> b -> IntMap a -> b
S.foldrWithKey
{-# INLINE ifoldr #-}
ifoldl' :: forall b a. (Int -> b -> a -> b) -> b -> IntMap a -> b
ifoldl' = forall a b. (a -> Int -> b -> a) -> a -> IntMap b -> a
S.foldlWithKey' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip
{-# INLINE ifoldl' #-}
instance TraversableWithIndex Int S.IntMap where
itraverse :: forall (f :: * -> *) a b.
Applicative f =>
(Int -> a -> f b) -> IntMap a -> f (IntMap b)
itraverse = forall (f :: * -> *) a b.
Applicative f =>
(Int -> a -> f b) -> IntMap a -> f (IntMap b)
S.traverseWithKey
{-# INLINE itraverse #-}
instance (Binary e) => Binary (S.IntMap e) where
put :: IntMap e -> Put
put IntMap e
m = forall t. Binary t => t -> Put
put (forall a. IntMap a -> Int
S.size IntMap e
m) forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ forall t. Binary t => t -> Put
put (forall a. IntMap a -> [(Int, a)]
S.toAscList IntMap e
m)
get :: Get (IntMap e)
get = forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM forall a. [(Int, a)] -> IntMap a
S.fromDistinctAscList forall t. Binary t => Get t
get