aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util/XSelection.hs
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-11-08 20:23:18 +0100
committerDavid Roundy <droundy@darcs.net>2007-11-08 20:23:18 +0100
commitbdcab48838281cb157b5d8bc9d4a2e53d86412d1 (patch)
tree9e43d501bae4e5090f6e99c4832cc59761daf302 /XMonad/Util/XSelection.hs
parent53e3b7f51523661ee4d76aa2d70ced4d4639898c (diff)
downloadXMonadContrib-bdcab48838281cb157b5d8bc9d4a2e53d86412d1.tar.gz
XMonadContrib-bdcab48838281cb157b5d8bc9d4a2e53d86412d1.tar.xz
XMonadContrib-bdcab48838281cb157b5d8bc9d4a2e53d86412d1.zip
fix types to work with Mats fix to X11.
darcs-hash:20071108192318-72aca-e3a1bd0fb08a79e6a7b185bcfae7babf0bcb3a50.gz
Diffstat (limited to 'XMonad/Util/XSelection.hs')
-rw-r--r--XMonad/Util/XSelection.hs8
1 files changed, 4 insertions, 4 deletions
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 ++ "
<http://code.haskell.org/utf8-string/> (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) &&