{-# LANGUAGE CPP #-} module Data.Enumerator.Util where import Data.Enumerator import Data.Char (toUpper, intToDigit, ord) import Data.Word (Word8) import qualified Data.Text as T import qualified Data.Text.Lazy as TL import Control.Monad.IO.Class (MonadIO, liftIO) import qualified Control.Exception as Exc import Numeric (showIntAtBase) tryStep :: MonadIO m => IO t -> (t -> Iteratee a m b) -> Iteratee a m b tryStep get io = do tried <- liftIO (Exc.try get) case tried of Right t -> io t Left err -> throwError (err :: Exc.SomeException) pad0 :: Int -> String -> String pad0 size str = padded where len = Prelude.length str padded = if len >= size then str else Prelude.replicate (size - len) '0' ++ str reprChar :: Char -> String reprChar c = "U+" ++ (pad0 4 (showIntAtBase 16 (toUpper . intToDigit) (ord c) "")) reprWord :: Word8 -> String reprWord w = "0x" ++ (pad0 2 (showIntAtBase 16 (toUpper . intToDigit) w "")) tSpanBy :: (Char -> Bool) -> T.Text -> (T.Text, T.Text) tlSpanBy :: (Char -> Bool) -> TL.Text -> (TL.Text, TL.Text) #if MIN_VERSION_text(0,11,0) tSpanBy = T.span tlSpanBy = TL.span #else tSpanBy = T.spanBy tlSpanBy = TL.spanBy #endif