Skip to content

Commit

Permalink
reorganized module hierarchy, tightened internedbytestring export
Browse files Browse the repository at this point in the history
  • Loading branch information
ekmett committed Aug 4, 2011
1 parent 87a39df commit 780c270
Show file tree
Hide file tree
Showing 9 changed files with 159 additions and 18 deletions.
6 changes: 0 additions & 6 deletions Data/ByteString/Interned.hs

This file was deleted.

6 changes: 6 additions & 0 deletions Data/Interned/ByteString.hs
@@ -0,0 +1,6 @@
module Data.Interned.ByteString
( InternedByteString
) where

import Data.Interned.Internal.ByteString

45 changes: 45 additions & 0 deletions Data/Interned/Internal/ByteString.hs
@@ -0,0 +1,45 @@
{-# LANGUAGE TypeFamilies, FlexibleInstances #-}
module Data.Interned.Internal.ByteString
( InternedByteString(..)
) where

import Data.String
import Data.Interned
import Data.ByteString
import Data.ByteString.Char8 as Char8
import Data.Hashable
import Data.Function (on)

data InternedByteString = InternedByteString
{-# UNPACK #-} !Id
{-# UNPACK #-} !ByteString

instance IsString InternedByteString where
fromString = intern . Char8.pack

instance Eq InternedByteString where
(==) = (==) `on` identity

instance Ord InternedByteString where
compare = compare `on` identity

instance Show InternedByteString where
showsPrec d (InternedByteString _ b) = showsPrec d b

instance Interned InternedByteString where
type Uninterned InternedByteString = ByteString
data Description InternedByteString = DBS {-# UNPACK #-} !ByteString deriving (Eq)
describe = DBS
identify = InternedByteString
identity (InternedByteString i _) = i
cache = ibsCache

instance Uninternable InternedByteString where
unintern (InternedByteString _ b) = b

instance Hashable (Description InternedByteString) where
hash (DBS h) = hash h

ibsCache :: Cache InternedByteString
ibsCache = mkCache
{-# NOINLINE ibsCache #-}
47 changes: 47 additions & 0 deletions Data/Interned/Internal/String.hs
@@ -0,0 +1,47 @@
{-# LANGUAGE TypeFamilies, FlexibleInstances #-}
module Data.Interned.Internal.String
( InternedString(..)
) where

import Data.String
import Data.Interned
import Data.Hashable
import Data.Foldable
import Data.Function (on)

data InternedString = IS
{-# UNPACK #-} !Id
String

instance IsString InternedString where
fromString = intern

instance Eq InternedString where
(==) = (==) `on` identity

instance Ord InternedString where
compare = compare `on` identity

instance Show InternedString where
showsPrec d (IS _ b) = showsPrec d b

instance Interned InternedString where
type Uninterned InternedString = String
data Description InternedString = Cons {-# UNPACK #-} !Char String | Nil
deriving (Eq)
describe (c:cs) = Cons c cs
describe [] = Nil
identify = IS
identity (IS i _) = i
cache = stringCache

instance Uninternable InternedString where
unintern (IS _ b) = b

instance Hashable (Description InternedString) where
hash (Cons c s) = foldl' hashWithSalt (hashWithSalt 0 c) s
hash Nil = 0

stringCache :: Cache InternedString
stringCache = mkCache
{-# NOINLINE stringCache #-}
44 changes: 44 additions & 0 deletions Data/Interned/Internal/Text.hs
@@ -0,0 +1,44 @@
{-# LANGUAGE TypeFamilies, FlexibleInstances #-}
module Data.Interned.Internal.Text
( InternedText(..)
) where

import Data.String
import Data.Interned
import Data.Text
import Data.Hashable
import Data.Function (on)

data InternedText = InternedText
{-# UNPACK #-} !Id
{-# UNPACK #-} !Text

instance IsString InternedText where
fromString = intern . pack

instance Eq InternedText where
(==) = (==) `on` identity

instance Ord InternedText where
compare = compare `on` identity

instance Show InternedText where
showsPrec d (InternedText _ b) = showsPrec d b

instance Interned InternedText where
type Uninterned InternedText = Text
data Description InternedText = DT {-# UNPACK #-} !Text deriving (Eq)
describe = DT
identify = InternedText
identity (InternedText i _) = i
cache = itCache

instance Uninternable InternedText where
unintern (InternedText _ b) = b

instance Hashable (Description InternedText) where
hash (DT h) = hash h

itCache :: Cache InternedText
itCache = mkCache
{-# NOINLINE itCache #-}
5 changes: 5 additions & 0 deletions Data/Interned/String.hs
@@ -0,0 +1,5 @@
module Data.Interned.String
( InternedString
) where

import Data.Interned.Internal.String
5 changes: 5 additions & 0 deletions Data/Interned/Text.hs
@@ -0,0 +1,5 @@
module Data.Interned.Text
( InternedText
) where

import Data.Interned.Internal.Text
5 changes: 0 additions & 5 deletions Data/String/Interned.hs

This file was deleted.

14 changes: 7 additions & 7 deletions intern.cabal
@@ -1,6 +1,6 @@
name: intern
category: Data, Data Structures
version: 0.4.1
version: 0.5.0
license: BSD3
cabal-version: >= 1.6
license-file: LICENSE
Expand Down Expand Up @@ -29,12 +29,12 @@ library

exposed-modules:
Data.Interned
Data.Interned.ByteString
Data.Interned.String
Data.Interned.Text
Data.Interned.Internal
Data.ByteString.Interned
Data.ByteString.Interned.Internal
Data.String.Interned
Data.String.Interned.Internal
Data.Text.Interned
Data.Text.Interned.Internal
Data.Interned.Internal.ByteString
Data.Interned.Internal.String
Data.Interned.Internal.Text

ghc-options: -Wall

0 comments on commit 780c270

Please sign in to comment.