{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE OverloadedStrings #-} -- | Extra functions and classes for dealing with Text. module Data.Text.Extra where import Data.Number.Extra import Data.Text import qualified Data.Text.Lazy as L -- | A class for converting to Text. class ToText a where toText :: a -> Text toLazyText :: a -> L.Text instance ToText Text where toText = id toLazyText = L.fromStrict instance ToText String where toText = pack toLazyText = L.pack -- | A class for converting from Text. class FromText a where fromText :: Text -> Maybe a fromLazyText :: L.Text -> Maybe a instance FromText String where fromText = Just . unpack fromLazyText = Just . L.unpack -- | Big 'em up. bigUp :: (Integral a) => a -> Text bigUp = go . int where go :: Integer -> Text go n | n < 3 = "a couple" | n < 5 = "several" | n < 10 = "many" | n < 80 = "dozens" | n < 100 = "nearly a hundred" | n < 200 = "some hundred" | n < 1000 = "hundreds" | n < 10000 = "thousands" | n < 100000 = "tens of thousands" | n < 200000 = "a hundred thousand" | n < 500000 = "hundreds of thousands" | n < 500000 = "half a million" | n < 600000 = "over half a million" | n < 1000000 = "nearly a million" | n < 2000000 = "over a million" | n < (10^ (9::Int)) = "millions" | n < 10^ (12::Int) = "billions" | otherwise = "trillions"