From bdcab48838281cb157b5d8bc9d4a2e53d86412d1 Mon Sep 17 00:00:00 2001 From: David Roundy Date: Thu, 8 Nov 2007 20:23:18 +0100 Subject: fix types to work with Mats fix to X11. darcs-hash:20071108192318-72aca-e3a1bd0fb08a79e6a7b185bcfae7babf0bcb3a50.gz --- XMonad/Hooks/SetWMName.hs | 8 ++++---- XMonad/Util/XSelection.hs | 8 ++++---- 2 files changed, 8 insertions(+), 8 deletions(-) diff --git a/XMonad/Hooks/SetWMName.hs b/XMonad/Hooks/SetWMName.hs index 30bb4ce..0e2fdcf 100644 --- a/XMonad/Hooks/SetWMName.hs +++ b/XMonad/Hooks/SetWMName.hs @@ -41,7 +41,7 @@ import Data.Bits ((.|.)) import Data.Char (ord) import Data.List (nub) import Data.Maybe (fromJust, listToMaybe, maybeToList) -import Data.Word (Word8) +import Foreign.C.Types (CChar) import Foreign.Marshal.Alloc (alloca) @@ -65,7 +65,7 @@ setWMName name = do -- _NET_SUPPORTING_WM_CHECK atom of root and support windows refers to the support window mapM_ (\w -> changeProperty32 dpy w atom_NET_SUPPORTING_WM_CHECK wINDOW 0 [fromIntegral supportWindow]) [root, supportWindow] -- set WM_NAME in supportWindow (now only accepts latin1 names to eliminate dependency on utf8 encoder) - changeProperty8 dpy supportWindow atom_NET_WM_NAME atom_UTF8_STRING 0 (latin1StringToWord8List name) + changeProperty8 dpy supportWindow atom_NET_WM_NAME atom_UTF8_STRING 0 (latin1StringToCCharList name) -- declare which _NET protocols are supported (append to the list if it exists) supportedList <- fmap (join . maybeToList) $ getWindowProperty32 dpy atom_NET_SUPPORTED_ATOM root changeProperty32 dpy root atom_NET_SUPPORTED_ATOM aTOM 0 (nub $ fromIntegral atom_NET_SUPPORTING_WM_CHECK : fromIntegral atom_NET_WM_NAME : supportedList) @@ -73,8 +73,8 @@ setWMName name = do netSupportingWMCheckAtom :: X Atom netSupportingWMCheckAtom = getAtom "_NET_SUPPORTING_WM_CHECK" - latin1StringToWord8List :: String -> [Word8] - latin1StringToWord8List str = map (fromIntegral . ord) str + latin1StringToCCharList :: String -> [CChar] + latin1StringToCCharList str = map (fromIntegral . ord) str getSupportWindow :: X Window getSupportWindow = withDisplay $ \dpy -> do diff --git a/XMonad/Util/XSelection.hs b/XMonad/Util/XSelection.hs index e701128..57b45b5 100644 --- a/XMonad/Util/XSelection.hs +++ b/XMonad/Util/XSelection.hs @@ -37,7 +37,7 @@ import Control.Exception as E (catch) import Control.Monad(Monad (return, (>>)), Functor(..), liftM, join) import Data.Char (chr, ord) import Data.Maybe (fromMaybe) -import Foreign (Word8) +import Foreign.C.Types (CChar) import Data.Bits (shiftL, (.&.), (.|.)) import XMonad.Util.Run (safeSpawn, unsafeSpawn) import XMonad (X, io) @@ -146,7 +146,7 @@ unsafePromptSelection app = join $ io $ liftM unsafeSpawn $ fmap (\x -> app ++ " (version 0.1), which is BSD-3 licensed, as is this module. It'd be better to just import Codec.Binary.UTF8.String (decode), but then users of this would need to install it; Xmonad has enough dependencies already. -} -decode :: [Word8] -> String +decode :: [CChar] -> String decode [ ] = "" decode (c:cs) | c < 0x80 = chr (fromEnum c) : decode cs @@ -161,10 +161,10 @@ decode (c:cs) replacement_character :: Char replacement_character = '\xfffd' - multi_byte :: Int -> Word8 -> Int -> [Char] + multi_byte :: Int -> CChar -> Int -> [Char] multi_byte i mask overlong = aux i cs (fromEnum (c .&. mask)) where - aux :: Int -> [Word8] -> Int -> [Char] + aux :: Int -> [CChar] -> Int -> [Char] aux 0 rs acc | overlong <= acc && acc <= 0x10ffff && (acc < 0xd800 || 0xdfff < acc) && -- cgit v1.2.3