module System.Console.Haskeline.Backend.Posix.Encoder (
Encoder,
Decoder,
newEncoders,
ExternalHandle(eH),
externalHandle,
withCodingMode,
openInCodingMode,
putEncodedStr,
#ifdef TERMINFO
getTermText,
#endif
getBlockOfChars,
getDecodedChar,
getDecodedLine,
) where
import System.IO
import System.Console.Haskeline.Monads
import System.Console.Haskeline.Term
#ifdef TERMINFO
import qualified System.Console.Terminfo.Base as Terminfo
#endif
#ifdef USE_GHC_ENCODINGS
import GHC.IO.Encoding (initLocaleEncoding)
import System.Console.Haskeline.Recover
#else
import System.Console.Haskeline.Backend.Posix.IConv
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
#ifdef TERMINFO
import qualified Data.ByteString.Char8 as BC
#endif
import Control.Monad (liftM2)
#endif
#ifdef USE_GHC_ENCODINGS
data Encoder = Encoder
data Decoder = Decoder
#else
type Decoder = PartialDecoder
type Encoder = String -> IO ByteString
#endif
newEncoders :: IO (Encoder,Decoder)
#ifdef USE_GHC_ENCODINGS
newEncoders = return (Encoder,Decoder)
#else
newEncoders = do
codeset <- bracket (setLocale (Just "")) setLocale $ const $ getCodeset
liftM2 (,) (openEncoder codeset)
(openPartialDecoder codeset)
#endif
data ExternalHandle = ExternalHandle
{ externalMode :: ExternalMode
, eH :: Handle
}
data ExternalMode = CodingMode | OtherMode
externalHandle :: Handle -> ExternalHandle
externalHandle = ExternalHandle OtherMode
withCodingMode :: ExternalHandle -> IO a -> IO a
withCodingMode ExternalHandle {externalMode=CodingMode} act = act
#ifdef USE_GHC_ENCODINGS
withCodingMode (ExternalHandle OtherMode h) act = do
bracket (liftIO $ hGetEncoding h)
(liftIO . hSetBinOrEncoding h)
$ const $ do
hSetEncoding h haskelineEncoding
act
hSetBinOrEncoding :: Handle -> Maybe TextEncoding -> IO ()
hSetBinOrEncoding h Nothing = hSetBinaryMode h True
hSetBinOrEncoding h (Just enc) = hSetEncoding h enc
#else
withCodingMode (ExternalHandle OtherMode h) act = hWithBinaryMode h act
#endif
#ifdef USE_GHC_ENCODINGS
haskelineEncoding :: TextEncoding
haskelineEncoding = transliterateFailure initLocaleEncoding
#endif
openInCodingMode :: FilePath -> IOMode -> IO ExternalHandle
#ifdef USE_GHC_ENCODINGS
openInCodingMode path iomode = do
h <- openFile path iomode
hSetEncoding h haskelineEncoding
return $ ExternalHandle CodingMode h
#else
openInCodingMode path iomode
= fmap (ExternalHandle CodingMode) $ openBinaryFile path iomode
#endif
putEncodedStr :: Encoder -> Handle -> String -> IO ()
#ifdef USE_GHC_ENCODINGS
putEncodedStr _ h = hPutStr h
#else
putEncodedStr enc h s = enc s >>= B.hPutStr h
#endif
#ifdef TERMINFO
getTermText :: Encoder -> String -> IO Terminfo.TermOutput
#ifdef USE_GHC_ENCODINGS
getTermText _ = return . Terminfo.termText
#else
getTermText enc s = enc s >>= return . Terminfo.termText . BC.unpack
#endif
#endif
getBlockOfChars :: Handle -> Decoder -> IO String
#ifdef USE_GHC_ENCODINGS
getBlockOfChars h _ = do
c <- hGetChar h
loop [c]
where
loop cs = do
isReady <- hReady h
if not isReady
then return $ reverse cs
else do
c <- hGetChar h
loop (c:cs)
#else
getBlockOfChars h decode = do
let bufferSize = 32
blockUntilInput h
bs <- B.hGetNonBlocking h bufferSize
decodeAndMore decode h bs
#endif
getDecodedChar :: Handle -> Decoder -> MaybeT IO Char
#ifdef USE_GHC_ENCODINGS
getDecodedChar h _ = guardedEOF hGetChar h
#else
getDecodedChar h decode = do
b <- hGetByte h
cs <- liftIO $ decodeAndMore decode h (B.pack [b])
case cs of
[] -> return '?'
(c:_) -> return c
#endif
getDecodedLine :: Handle -> Decoder -> MaybeT IO String
#ifdef USE_GHC_ENCODINGS
getDecodedLine h _ = guardedEOF hGetLine h
#else
getDecodedLine h decode
= hGetLocaleLine h >>= liftIO . decodeAndMore decode h
#endif
#ifndef USE_GHC_ENCODINGS
blockUntilInput :: Handle -> IO ()
#if __GLASGOW_HASKELL__ >= 611
blockUntilInput h = hWaitForInput h (-1) >> return ()
#else
blockUntilInput h = unsafeHandleToFD h >>= threadWaitRead . Fd
#endif
#endif