module NLP.Text.BTI where
import Control.Applicative
import Control.DeepSeq (NFData(..))
import Data.Aeson as A
import Data.Binary as DB
import Data.Hashable
import Data.Serialize as DS
import Data.Serialize.Text
import Data.Stringable as SA
import Data.String as IS
import Data.Text.Binary
import Data.Text (Text)
import Data.Vector.Unboxed.Deriving
import GHC.Generics
import NLP.Text.BTI.Internal
newtype BTI = BTI { getBTI :: Int }
deriving (Eq,Generic)
derivingUnbox "BTI"
[t| BTI -> Int |]
[| getBTI |]
[| BTI |]
instance Ord BTI where
BTI l `compare` BTI r = btiBimapLookupInt l `compare` btiBimapLookupInt r
bti :: Text -> BTI
bti s = BTI $! btiBimapAdd s
instance IsString BTI where
fromString = bti . IS.fromString
instance Show BTI where
showsPrec p i r = showsPrec p (toString i) r
instance Read BTI where
readsPrec p str = [ (bti $ IS.fromString s, y) | (s,y) <- readsPrec p str ]
instance Hashable BTI
instance Stringable BTI where
toString = toString . btiBimapLookupInt . getBTI
fromString = bti . SA.fromString
length = SA.length . btiBimapLookupInt . getBTI
toText = toText . btiBimapLookupInt . getBTI
fromText = bti . fromText
instance NFData BTI where
rnf = rnf . getBTI
instance Binary BTI where
put = DB.put . toText
get = fromText <$> DB.get
instance Serialize BTI where
put = DS.put . toText
get = fromText <$> DS.get
instance FromJSON BTI where
parseJSON s = fromText <$> parseJSON s
instance ToJSON BTI where
toJSON = toJSON . toText