{-# LANGUAGE TypeFamilies, FlexibleInstances #-}
module Data.Interned.Internal.String
  ( InternedString(..)
  ) where

import Data.String
import Data.Interned
import Data.Hashable
import Data.Foldable

data InternedString = IS
  { InternedString -> Id
internedStringId :: {-# UNPACK #-} !Id
  , InternedString -> String
uninternString :: String
  }

instance IsString InternedString where
  fromString :: String -> InternedString
fromString = forall t. Interned t => Uninterned t -> t
intern

instance Eq InternedString where
  IS Id
i String
_ == :: InternedString -> InternedString -> Bool
== IS Id
j String
_ = Id
i forall a. Eq a => a -> a -> Bool
== Id
j

instance Ord InternedString where
  compare :: InternedString -> InternedString -> Ordering
compare (IS Id
i String
_) (IS Id
j String
_) = forall a. Ord a => a -> a -> Ordering
compare Id
i Id
j

instance Show InternedString where
  showsPrec :: Id -> InternedString -> ShowS
showsPrec Id
d (IS Id
_ String
b) = forall a. Show a => Id -> a -> ShowS
showsPrec Id
d String
b

instance Hashable InternedString where
  hashWithSalt :: Id -> InternedString -> Id
hashWithSalt Id
s (IS Id
i String
_) = forall a. Hashable a => Id -> a -> Id
hashWithSalt Id
s Id
i

instance Interned InternedString where
  type Uninterned InternedString = String
  data Description InternedString = Cons {-# UNPACK #-} !Char String | Nil
    deriving (Description InternedString -> Description InternedString -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Description InternedString -> Description InternedString -> Bool
$c/= :: Description InternedString -> Description InternedString -> Bool
== :: Description InternedString -> Description InternedString -> Bool
$c== :: Description InternedString -> Description InternedString -> Bool
Eq)
  describe :: Uninterned InternedString -> Description InternedString
describe (Char
c:String
cs) = Char -> String -> Description InternedString
Cons Char
c String
cs
  describe []     = Description InternedString
Nil
  identify :: Id -> Uninterned InternedString -> InternedString
identify = Id -> String -> InternedString
IS
  cache :: Cache InternedString
cache = Cache InternedString
stringCache

instance Uninternable InternedString where
  unintern :: InternedString -> Uninterned InternedString
unintern = InternedString -> String
uninternString

instance Hashable (Description InternedString) where
  hashWithSalt :: Id -> Description InternedString -> Id
hashWithSalt Id
s (Cons Char
c String
cs) = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' forall a. Hashable a => Id -> a -> Id
hashWithSalt (forall a. Hashable a => Id -> a -> Id
hashWithSalt Id
s Char
c) String
cs
  hashWithSalt Id
s Description InternedString
R:DescriptionInternedString
Nil         = Id
s forall a. Hashable a => Id -> a -> Id
`hashWithSalt` (Id
0 :: Int)

stringCache :: Cache InternedString
stringCache :: Cache InternedString
stringCache = forall t. Interned t => Cache t
mkCache
{-# NOINLINE stringCache #-}