{-# LANGUAGE CPP #-} module Import (getLocale' ,fromStrict ,toStrict ,whenJust' ,hGetEncAndNlMode' ) where import GHC.IO.Handle.Types (Handle__(..)) import GHC.IO.Handle.Internals (withHandle_) #if MIN_VERSION_base(4,5,0) import GHC.IO.Encoding (getLocaleEncoding) #else import GHC.IO.Encoding (localeEncoding) #endif import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as L import System.IO {-# INLINE getLocale' #-} getLocale' :: IO TextEncoding getLocale' = #if MIN_VERSION_base(4,5,0) getLocaleEncoding #else return localeEncoding #endif {-# INLINE fromStrict #-} fromStrict :: B.ByteString -> L.ByteString #if MIN_VERSION_bytestring(0,10,0) fromStrict = L.fromStrict #else fromStrict x = L.fromChunks [x] #endif {-# INLINE toStrict #-} toStrict :: L.ByteString -> B.ByteString #if MIN_VERSION_bytestring(0,10,0) toStrict = L.toStrict #else toStrict x = B.concat (L.toChunks x) #endif {-# INLINE whenJust' #-} whenJust' :: Maybe a -> (a -> IO ()) -> IO () whenJust' m act = case m of Just a -> act a Nothing -> return () {-# INLINE hGetEncAndNlMode' #-} hGetEncAndNlMode' :: Handle -> IO (TextEncoding, NewlineMode) hGetEncAndNlMode' handle = withHandle_ "hGetNewlineMode'" handle $ \Handle__{haCodec=mc, haInputNL=i, haOutputNL=o} -> do c <- case mc of Nothing -> getLocale' Just c -> return c return (c, NewlineMode{inputNL=i, outputNL=o})