{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE LambdaCase #-}
module Text.Enum.Text
( EnumText(..)
, UsingEnumText(..)
, TextParsable(..)
, EnumTextConfig(..)
, defaultEnumTextConfig
) where
import Data.Array
import qualified Data.ByteString.Char8 as B
import Data.Coerce
import Data.Hashable
import Data.Possibly
import qualified Data.HashMap.Strict as HM
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import Data.Text.Read
import Data.Time
import Fmt
import Text.Read
class ( Buildable e
, Bounded e
, Enum e
, Eq e
, Ord e
, Show e
, TextParsable e
) => EnumText e where
configEnumText :: e -> EnumTextConfig
configEnumText _ = defaultEnumTextConfig
renderEnumText :: e -> T.Text
renderEnumText e = enumTextArray ! I e
buildEnumText :: e -> Builder
buildEnumText = build . renderEnumText
parseEnumText :: T.Text -> Possibly e
parseEnumText txt = maybe (Left msg) Right $ HM.lookup txt hashmap_t
where
msg = "parseEnumText: enumeration not recognised: "++show txt
toFieldEnumText :: e -> B.ByteString
toFieldEnumText e = enumByteStringArray ! I e
fromFieldEnumText_ :: Monad m => B.ByteString -> m e
fromFieldEnumText_ bs = maybe (fail msg) return $ HM.lookup bs hashmap_b
where
msg = "fromFieldEnumText_: enumeration not recognised: "++show bs
hashWithSaltEnumText :: Int -> e -> Int
hashWithSaltEnumText n = hashWithSalt n . toFieldEnumText
newtype UsingEnumText a = UsingEnumText { _UsingEnumText :: a }
instance EnumText a => Buildable (UsingEnumText a) where
build (UsingEnumText x) = buildEnumText x
instance EnumText a => TextParsable (UsingEnumText a) where
parseText x = UsingEnumText <$> parseEnumText x
data EnumTextConfig =
EnumTextConfig
{ _etc_text_prep :: T.Text -> T.Text
, _etc_char_prep :: Char -> Char
}
defaultEnumTextConfig :: EnumTextConfig
defaultEnumTextConfig =
EnumTextConfig
{ _etc_text_prep = defaultTextPrep
, _etc_char_prep = defaultCharPrep
}
defaultTextPrep :: T.Text -> T.Text
defaultTextPrep txt = case T.uncons $ T.dropWhile (/='_') txt of
Just (_,rst) | not $ T.null rst -> rst
_ -> error $ "defaultTextPrep: bad data constructor: "++T.unpack txt
defaultCharPrep :: Char -> Char
defaultCharPrep c = case c of
'_' -> '-'
_ -> c
class TextParsable a where
parseText :: T.Text -> Possibly a
instance TextParsable T.Text where parseText = return
instance TextParsable UTCTime where parseText = parseTextRead "UTCTime"
instance TextParsable Day where parseText = parseTextRead "Day"
instance TextParsable Int where parseText = parseDecimal
instance a ~ Char => TextParsable [a] where parseText = return . T.unpack
instance TextParsable a => TextParsable (Maybe a) where
parseText = \case
"" -> Right Nothing
s -> Just <$> parseText s
newtype I a = I { _I :: a }
deriving (Eq,Ord)
instance EnumText e => Ix (I e) where
range (l,h) = coerce [_I l.._I h]
index (l,_) x = fromEnum (_I x) - fromEnum (_I l)
inRange (l,h) x = _I l <= _I x && _I x <= _I h
enumTextArray :: forall e . EnumText e => Array (I e) T.Text
enumTextArray =
listArray (I minBound,I maxBound)
[ T.map _etc_char_prep $ _etc_text_prep $ T.pack $ show e
| e <- [minBound..maxBound :: e]
]
where
EnumTextConfig{..} = configEnumText (minBound :: e)
enumByteStringArray :: forall e . EnumText e => Array (I e) B.ByteString
enumByteStringArray = listArray (I minBound,I maxBound)
[ TE.encodeUtf8 $ renderEnumText e
| e <- [minBound..maxBound :: e]
]
hashmap_t :: EnumText e => HM.HashMap T.Text e
hashmap_t = HM.fromList
[ (renderEnumText c,c)
| c <- [minBound..maxBound]
]
hashmap_b :: EnumText e => HM.HashMap B.ByteString e
hashmap_b = HM.fromList
[ (TE.encodeUtf8 $ renderEnumText c,c)
| c <- [minBound..maxBound]
]
parseDecimal :: T.Text -> Possibly Int
parseDecimal txt = either (Left . typeError "integer") return $ do
(x,r) <- signed decimal txt
case T.null r of
True -> return x
False -> Left $ "residual input: " ++ T.unpack r
parseTextRead :: Read a
=> String
-> T.Text
-> Possibly a
parseTextRead ty_s txt =
maybe (Left $ typeError ty_s $ show str) Right $ readMaybe str
where
str = T.unpack txt
typeError :: String -> String -> String
typeError ty_s msg = "failed to parse "++ty_s++": "++msg