{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}

{-# OPTIONS_GHC -fno-warn-orphans #-}
module Data.Strict.HashMap.Internal where

import Data.HashMap.Lazy                  as L
import Data.Strict.HashMap.Autogen.Strict as S

import Data.Binary
import Data.Hashable
import Data.Foldable.WithIndex
import Data.Functor.WithIndex
import Data.Traversable.WithIndex
import Data.Strict.Classes

instance (Eq k, Hashable k) => Strict (L.HashMap k v) (S.HashMap k v) where
  toStrict :: HashMap k v -> HashMap k v
toStrict = forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
S.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. HashMap k v -> [(k, v)]
L.toList
  toLazy :: HashMap k v -> HashMap k v
toLazy = forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
L.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. HashMap k v -> [(k, v)]
S.toList
  {-# INLINE toStrict #-}
  {-# INLINE toLazy #-}

-- code copied from indexed-traversable-instances

instance FunctorWithIndex k (S.HashMap k) where
  imap :: forall a b. (k -> a -> b) -> HashMap k a -> HashMap k b
imap = forall k a b. (k -> a -> b) -> HashMap k a -> HashMap k b
S.mapWithKey
  {-# INLINE imap #-}

instance FoldableWithIndex k (S.HashMap k) where
  ifoldr :: forall a b. (k -> a -> b -> b) -> b -> HashMap k a -> b
ifoldr  = forall k a b. (k -> a -> b -> b) -> b -> HashMap k a -> b
S.foldrWithKey
  {-# INLINE ifoldr #-}
  ifoldl' :: forall b a. (k -> b -> a -> b) -> b -> HashMap k a -> b
ifoldl' = forall a k v. (a -> k -> v -> a) -> a -> HashMap k v -> 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 k (S.HashMap k) where
  itraverse :: forall (f :: * -> *) a b.
Applicative f =>
(k -> a -> f b) -> HashMap k a -> f (HashMap k b)
itraverse = forall (f :: * -> *) k v1 v2.
Applicative f =>
(k -> v1 -> f v2) -> HashMap k v1 -> f (HashMap k v2)
S.traverseWithKey
  {-# INLINE itraverse #-}

-- code copied from binary-instances

instance (Hashable k, Eq k, Binary k, Binary v) => Binary (S.HashMap k v) where
    get :: Get (HashMap k v)
get = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
S.fromList forall t. Binary t => Get t
get
    put :: HashMap k v -> Put
put = forall t. Binary t => t -> Put
put forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. HashMap k v -> [(k, v)]
S.toList