{-# OPTIONS_GHC -fno-warn-orphans #-}
{-|
Module:      TextShow.Data.UnorderedContainers
Copyright:   (C) 2014-2017 Ryan Scott
License:     BSD-style (see the file LICENSE)
Maintainer:  Ryan Scott
Stability:   Provisional
Portability: GHC

'TextShow' instances for 'HashMap' and 'HashSet'.

/Since: 2/
-}
module TextShow.Data.UnorderedContainers () where

import qualified Data.HashMap.Lazy as HM (toList)
import           Data.HashMap.Lazy (HashMap)
import qualified Data.HashSet as HS (toList)
import           Data.HashSet (HashSet)

import           TextShow (TextShow(..), TextShow1(..), TextShow2(..), showbPrec1)
import           TextShow.Utils (showbUnaryListWith)

-- | /Since: 2/
instance (TextShow k, TextShow v) => TextShow (HashMap k v) where
    showbPrec :: Int -> HashMap k v -> Builder
showbPrec = Int -> HashMap k v -> Builder
forall (f :: * -> *) a.
(TextShow1 f, TextShow a) =>
Int -> f a -> Builder
showbPrec1
    {-# INLINE showbPrec #-}

-- | /Since: 2/
instance TextShow k => TextShow1 (HashMap k) where
    liftShowbPrec :: (Int -> a -> Builder)
-> ([a] -> Builder) -> Int -> HashMap k a -> Builder
liftShowbPrec = (Int -> k -> Builder)
-> ([k] -> Builder)
-> (Int -> a -> Builder)
-> ([a] -> Builder)
-> Int
-> HashMap k a
-> Builder
forall (f :: * -> * -> *) a b.
TextShow2 f =>
(Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> f a b
-> Builder
liftShowbPrec2 Int -> k -> Builder
forall a. TextShow a => Int -> a -> Builder
showbPrec [k] -> Builder
forall a. TextShow a => [a] -> Builder
showbList
    {-# INLINE liftShowbPrec #-}

-- | /Since: 2/
instance TextShow2 HashMap where
    liftShowbPrec2 :: (Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> HashMap a b
-> Builder
liftShowbPrec2 Int -> a -> Builder
sp1 [a] -> Builder
_ Int -> b -> Builder
sp2 [b] -> Builder
_ Int
p =
        ([(a, b)] -> Builder) -> Int -> [(a, b)] -> Builder
forall a. ([a] -> Builder) -> Int -> [a] -> Builder
showbUnaryListWith ((Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> [(a, b)]
-> Builder
forall (f :: * -> * -> *) a b.
TextShow2 f =>
(Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> [f a b]
-> Builder
liftShowbList2 ((a -> Builder) -> Int -> a -> Builder
forall a b. a -> b -> a
const (Int -> a -> Builder
sp1 Int
0)) [a] -> Builder
forall a. HasCallStack => a
undefined
                                           ((b -> Builder) -> Int -> b -> Builder
forall a b. a -> b -> a
const (Int -> b -> Builder
sp2 Int
0)) [b] -> Builder
forall a. HasCallStack => a
undefined) Int
p ([(a, b)] -> Builder)
-> (HashMap a b -> [(a, b)]) -> HashMap a b -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap a b -> [(a, b)]
forall k v. HashMap k v -> [(k, v)]
HM.toList
    {-# INLINE liftShowbPrec2 #-}

-- | /Since: 2/
instance TextShow a => TextShow (HashSet a) where
    showbPrec :: Int -> HashSet a -> Builder
showbPrec = Int -> HashSet a -> Builder
forall (f :: * -> *) a.
(TextShow1 f, TextShow a) =>
Int -> f a -> Builder
showbPrec1
    {-# INLINE showbPrec #-}

-- | /Since: 2/
instance TextShow1 HashSet where
    liftShowbPrec :: (Int -> a -> Builder)
-> ([a] -> Builder) -> Int -> HashSet a -> Builder
liftShowbPrec Int -> a -> Builder
_ [a] -> Builder
sl Int
p = ([a] -> Builder) -> Int -> [a] -> Builder
forall a. ([a] -> Builder) -> Int -> [a] -> Builder
showbUnaryListWith [a] -> Builder
sl Int
p ([a] -> Builder) -> (HashSet a -> [a]) -> HashSet a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashSet a -> [a]
forall a. HashSet a -> [a]
HS.toList
    {-# INLINE liftShowbPrec #-}