diff options
author | Lukas Mai <l.mai@web.de> | 2008-04-06 03:12:34 +0200 |
---|---|---|
committer | Lukas Mai <l.mai@web.de> | 2008-04-06 03:12:34 +0200 |
commit | 666e757e8f44a6f61d9bb0db52fa65f98b8b1bfd (patch) | |
tree | b94595b776ee06ceb46574dc50e1c191679d12e2 /XMonad | |
parent | 3bc603f59ff3cd8ee60c4b285053cdf83107c548 (diff) | |
download | xmonad-666e757e8f44a6f61d9bb0db52fa65f98b8b1bfd.tar.gz xmonad-666e757e8f44a6f61d9bb0db52fa65f98b8b1bfd.tar.xz xmonad-666e757e8f44a6f61d9bb0db52fa65f98b8b1bfd.zip |
XMonad.Main: call setlocale on startup
darcs-hash:20080406011234-462cf-09fde81185653a210d292b90b02595de7c365bb1.gz
Diffstat (limited to '')
-rw-r--r-- | XMonad/Main.hsc (renamed from XMonad/Main.hs) | 12 |
1 files changed, 11 insertions, 1 deletions
diff --git a/XMonad/Main.hs b/XMonad/Main.hsc index ab276af..5df6ed8 100644 --- a/XMonad/Main.hs +++ b/XMonad/Main.hsc @@ -1,4 +1,4 @@ -{-# LANGUAGE MultiParamTypeClasses, FlexibleContexts #-} +{-# LANGUAGE MultiParamTypeClasses, FlexibleContexts, ForeignFunctionInterface #-} ---------------------------------------------------------------------------- -- | -- Module : XMonad.Main @@ -23,6 +23,9 @@ import Control.Monad.Reader import Control.Monad.State import Data.Maybe (fromMaybe) +import Foreign.C +import Foreign.Ptr + import System.Environment (getArgs) import System.Posix.Signals @@ -37,11 +40,18 @@ import XMonad.Operations import System.IO +#include <locale.h> + +foreign import ccall unsafe "locale.h setlocale" c_setlocale :: CInt -> Ptr CChar -> IO (Ptr CChar) + -- | -- The main entry point -- xmonad :: (LayoutClass l Window, Read (l Window)) => XConfig l -> IO () xmonad initxmc = do + -- setup locale information from environment + withCString "" $ \p -> do + c_setlocale (#const LC_ALL) p -- ignore SIGPIPE installHandler openEndedPipe Ignore Nothing -- First, wrap the layout in an existential, to keep things pretty: |