module GHC.HandleEncoding (configureHandleEncoding) where
import Prelude
import GHC.IO.Encoding (textEncodingName)
import System.Environment
import System.IO
configureHandleEncoding :: IO ()
configureHandleEncoding :: IO ()
configureHandleEncoding = do
mb_val <- String -> IO (Maybe String)
lookupEnv String
"GHC_CHARENC"
case mb_val of
Just String
"UTF-8" -> do
Handle -> TextEncoding -> IO ()
hSetEncoding Handle
stdout TextEncoding
utf8
Handle -> TextEncoding -> IO ()
hSetEncoding Handle
stderr TextEncoding
utf8
Maybe String
_ -> do
Handle -> IO ()
hSetTranslit Handle
stdout
Handle -> IO ()
hSetTranslit Handle
stderr
hSetTranslit :: Handle -> IO ()
hSetTranslit :: Handle -> IO ()
hSetTranslit Handle
h = do
menc <- Handle -> IO (Maybe TextEncoding)
hGetEncoding Handle
h
case fmap textEncodingName menc of
Just String
name | Char
'/' Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` String
name -> do
enc' <- String -> IO TextEncoding
mkTextEncoding (String -> IO TextEncoding) -> String -> IO TextEncoding
forall a b. (a -> b) -> a -> b
$ String
name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"//TRANSLIT"
hSetEncoding h enc'
Maybe String
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()