{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Language.EO.Locale where
import Control.Exception (Exception (..), Handler (..), SomeException, catches)
import Main.Utf8 (withUtf8)
import System.Exit (ExitCode (..), exitWith)
import System.IO.CodePage (withCP65001)
withCorrectLocale :: IO a -> IO a
withCorrectLocale :: forall a. IO a -> IO a
withCorrectLocale IO a
act = do
let withCorrectLocale' :: IO a -> IO a
withCorrectLocale' = IO a -> IO a
forall a. IO a -> IO a
withCP65001 (IO a -> IO a) -> (IO a -> IO a) -> IO a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> IO a
forall (m :: * -> *) r. (MonadIO m, MonadMask m) => m r -> m r
withUtf8
IO a -> IO a
forall a. IO a -> IO a
withCorrectLocale' IO a
act
IO a -> [Handler a] -> IO a
forall a. IO a -> [Handler a] -> IO a
`catches` [ (ExitCode -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
Handler ((ExitCode -> IO a) -> Handler a)
-> (ExitCode -> IO a) -> Handler a
forall a b. (a -> b) -> a -> b
$ \(ExitCode
x :: ExitCode) -> ExitCode -> IO a
forall a. ExitCode -> IO a
exitWith ExitCode
x
, (SomeException -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
Handler ((SomeException -> IO a) -> Handler a)
-> (SomeException -> IO a) -> Handler a
forall a b. (a -> b) -> a -> b
$ \(SomeException
x :: SomeException) ->
IO a -> IO a
forall a. IO a -> IO a
withCorrectLocale' do
String -> IO ()
putStrLn (SomeException -> String
forall e. Exception e => e -> String
displayException SomeException
x)
ExitCode -> IO a
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1)
]