aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util
diff options
context:
space:
mode:
authorgwern0 <gwern0@gmail.com>2008-09-20 17:16:15 +0200
committergwern0 <gwern0@gmail.com>2008-09-20 17:16:15 +0200
commite17e6eadf6a1dbcff7b78d74ea013b5c5187e55b (patch)
tree20db6761063e8f006dabde82007310106bca27d9 /XMonad/Util
parentb09eacbae6d94f294050a7eb0d29a96d5a163180 (diff)
downloadXMonadContrib-e17e6eadf6a1dbcff7b78d74ea013b5c5187e55b.tar.gz
XMonadContrib-e17e6eadf6a1dbcff7b78d74ea013b5c5187e55b.tar.xz
XMonadContrib-e17e6eadf6a1dbcff7b78d74ea013b5c5187e55b.zip
XSelection.hs: use CPP to compile against utf8-string
darcs-hash:20080920151615-f7719-f3e3f95487ffce029e822e9a00d2aab2f1751cdd.gz
Diffstat (limited to 'XMonad/Util')
-rw-r--r--XMonad/Util/XSelection.hs86
1 files changed, 46 insertions, 40 deletions
diff --git a/XMonad/Util/XSelection.hs b/XMonad/Util/XSelection.hs
index fef9b3f..c9cb410 100644
--- a/XMonad/Util/XSelection.hs
+++ b/XMonad/Util/XSelection.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
{- |
Module : XMonad.Util.XSelection
Copyright : (C) 2007 Andrea Rossato, Matthew Sackman
@@ -24,13 +25,55 @@ module XMonad.Util.XSelection ( -- * Usage
import Control.Concurrent (forkIO)
import Control.Exception as E (catch)
import Control.Monad(Monad (return, (>>)), Functor(..), liftM, join)
-import Data.Bits (shiftL, (.&.), (.|.))
-import Data.Char (chr, ord)
+import Data.Char (ord)
import Data.Maybe (fromMaybe)
-import Data.Word (Word8)
import XMonad
import XMonad.Util.Run (safeSpawn, unsafeSpawn)
+#ifdef UTF8
+import Codec.Binary.UTF8.String (decode)
+#else
+import Data.Bits (shiftL, (.&.), (.|.))
+import Data.Char (chr)
+import Data.Word (Word8)
+{- | Decode a UTF8 string packed into a list of Word8 values, directly to
+ String; does not deal with CChar, hence you will want the counter-intuitive @map fromIntegral@
+ UTF-8 decoding for internal use in getSelection.
+
+ This code is copied from Eric Mertens's "utf-string" library <http://code.haskell.org/utf8-string/>
+ (as of version 0.1),\which is BSD-3 licensed like 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 [] = ""
+decode (c:cs)
+ | c < 0x80 = chr (fromEnum c) : decode cs
+ | c < 0xc0 = replacement_character : decode cs
+ | c < 0xe0 = multi_byte 1 0x1f 0x80
+ | c < 0xf0 = multi_byte 2 0xf 0x800
+ | c < 0xf8 = multi_byte 3 0x7 0x10000
+ | c < 0xfc = multi_byte 4 0x3 0x200000
+ | c < 0xfe = multi_byte 5 0x1 0x4000000
+ | otherwise = replacement_character : decode cs
+ where
+
+ replacement_character :: Char
+ replacement_character = '\xfffd'
+
+ multi_byte :: Int -> Word8 -> Int -> [Char]
+ multi_byte i mask overlong = aux i cs (fromEnum (c .&. mask))
+ where
+ aux 0 rs acc
+ | overlong <= acc && acc <= 0x10ffff &&
+ (acc < 0xd800 || 0xdfff < acc) &&
+ (acc < 0xfffe || 0xffff < acc) = chr acc : decode rs
+ | otherwise = replacement_character : decode rs
+ aux n (r:rs) acc
+ | r .&. 0xc0 == 0x80 = aux (n-1) rs
+ $ shiftL acc 6 .|. fromEnum (r .&. 0x3f)
+ aux _ rs _ = replacement_character : decode rs
+#endif
+
{- $usage
Add @import XMonad.Util.XSelection@ to the top of Config.hs
Then make use of getSelection or promptSelection as needed; if
@@ -129,40 +172,3 @@ promptSelection, safePromptSelection, unsafePromptSelection :: String -> X ()
promptSelection = unsafePromptSelection
safePromptSelection app = join $ io $ liftM (safeSpawn app) (getSelection)
unsafePromptSelection app = join $ io $ liftM unsafeSpawn $ fmap (\x -> app ++ " " ++ x) getSelection
-
-{- | Decode a UTF8 string packed into a list of Word8 values, directly to
- String; does not deal with CChar, hence you will want the counter-intuitive @map fromIntegral@
- UTF-8 decoding for internal use in getSelection.
-
- This code is copied from Eric Mertens's "utf-string" library <http://code.haskell.org/utf8-string/>
- (as of version 0.1),\which is BSD-3 licensed like 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 [ ] = ""
-decode (c:cs)
- | c < 0x80 = chr (fromEnum c) : decode cs
- | c < 0xc0 = replacement_character : decode cs
- | c < 0xe0 = multi_byte 1 0x1f 0x80
- | c < 0xf0 = multi_byte 2 0xf 0x800
- | c < 0xf8 = multi_byte 3 0x7 0x10000
- | c < 0xfc = multi_byte 4 0x3 0x200000
- | c < 0xfe = multi_byte 5 0x1 0x4000000
- | otherwise = replacement_character : decode cs
- where
-
- replacement_character :: Char
- replacement_character = '\xfffd'
-
- multi_byte :: Int -> Word8 -> Int -> [Char]
- multi_byte i mask overlong = aux i cs (fromEnum (c .&. mask))
- where
- aux 0 rs acc
- | overlong <= acc && acc <= 0x10ffff &&
- (acc < 0xd800 || 0xdfff < acc) &&
- (acc < 0xfffe || 0xffff < acc) = chr acc : decode rs
- | otherwise = replacement_character : decode rs
- aux n (r:rs) acc
- | r .&. 0xc0 == 0x80 = aux (n-1) rs
- $ shiftL acc 6 .|. fromEnum (r .&. 0x3f)
- aux _ rs _ = replacement_character : decode rs