Wed Nov 29 05:22:30 CET 2006  Eric Kow <[EMAIL PROTECTED]>
  * Add an eyeball test for Unicode strings.
New patches:

[Add an eyeball test for Unicode strings.
Eric Kow <[EMAIL PROTECTED]>**20061129042230] 
<
> {
addfile ./samples/test/UTF8.lhs
hunk ./samples/test/UTF8.lhs 1
+Copyright (c) 2002, members of the Haskell Internationalisation Working
+Group All rights reserved.
+
+Redistribution and use in source and binary forms, with or without
+modification, are permitted provided that the following conditions are met:
+
+* Redistributions of source code must retain the above copyright notice,
+   this list of conditions and the following disclaimer.
+* Redistributions in binary form must reproduce the above copyright notice,
+   this list of conditions and the following disclaimer in the
+   documentation and/or other materials provided with the distribution.
+* Neither the name of the Haskell Internationalisation Working Group nor
+   the names of its contributors may be used to endorse or promote products
+   derived from this software without specific prior written permission.
+
+THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
+AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
+IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
+ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE
+LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
+CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
+SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
+INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
+CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
+ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+POSSIBILITY OF SUCH DAMAGE.
+
+This module provides lazy stream encoding/decoding facilities for UTF-8,
+the Unicode Transformation Format with 8-bit words.
+
+2002-09-02  Sven Moritz Hallberg <[EMAIL PROTECTED]>
+
+
+> module UTF8
+>   ( encode, decode,
+>     encodeOne, decodeOne,
+>   ) where
+
+> import Char (ord, chr)
+> import Data.Word (Word8, Word16, Word32)
+> import Data.Bits (Bits, shiftL, shiftR, (.&.), (.|.))
+
+
+
+///- UTF-8 in General -///
+
+Adapted from the Unicode standard, version 3.2,
+Table 3.1 "UTF-8 Bit Distribution" (excluded are UTF-16 encodings):
+
+  Scalar                    1st Byte  2nd Byte  3rd Byte  4th Byte
+          000000000xxxxxxx  0xxxxxxx
+          00000yyyyyxxxxxx  110yyyyy  10xxxxxx
+          zzzzyyyyyyxxxxxx  1110zzzz  10yyyyyy  10xxxxxx
+  000uuuzzzzzzyyyyyyxxxxxx  11110uuu  10zzzzzz  10yyyyyy  10xxxxxx
+
+Also from the Unicode standard, version 3.2,
+Table 3.1B "Legal UTF-8 Byte Sequences":
+
+  Code Points         1st Byte  2nd Byte  3rd Byte  4th Byte
+    U+0000..U+007F    00..7F
+    U+0080..U+07FF    C2..DF    80..BF
+    U+0800..U+0FFF    E0        A0..BF    80..BF
+    U+1000..U+CFFF    E1..EC    80..BF    80..BF
+    U+D000..U+D7FF    ED        80..9F    80..BF
+    U+D800..U+DFFF    ill-formed
+    U+E000..U+FFFF    EE..EF    80..BF    80..BF
+   U+10000..U+3FFFF   F0        90..BF    80..BF    80..BF
+   U+40000..U+FFFFF   F1..F3    80..BF    80..BF    80..BF
+  U+100000..U+10FFFF  F4        80..8F    80..BF    80..BF
+
+
+
+///- Encoding Functions -///
+
+Must the encoder ensure that no illegal byte sequences are output or
+can we trust the Haskell system to supply only legal values?
+For now I include error case for the surrogate values U+D800..U+DFFF and
+out-of-range scalars.
+
+The function is pretty much a transscript of table 3.1B with error checks.
+It dispatches the actual encoding to functions specific to the number of
+required bytes.
+
+> encodeOne :: Char -> [Word8]
+> encodeOne c
+>-- The report guarantees in (6.1.2) that this won't happen:
+>--   | n < 0       = error "encodeUTF8: ord returned a negative value"
+>     | n < 0x0080  = encodeOne_onebyte n8
+>     | n < 0x0800  = encodeOne_twobyte n16
+>     | n < 0xD800  = encodeOne_threebyte n16
+>     | n < 0xE000  = error "encodeUTF8: ord returned a surrogate value"
+>     | n < 0x10000       = encodeOne_threebyte n16
+>-- Haskell 98 only talks about 16 bit characters, but ghc handles 20.1.
+>     | n < 0x10FFFF      = encodeOne_fourbyte n32
+>     | otherwise  = error "encodeUTF8: ord returned a value above 0x10FFFF"
+>     where
+>     n = ord c            :: Int
+>     n8 = fromIntegral n  :: Word8
+>     n16 = fromIntegral n :: Word16
+>     n32 = fromIntegral n :: Word32
+
+
+With the above, a stream decoder is trivial:
+
+> encode :: [Char] -> [Word8]
+> encode = concatMap encodeOne
+
+
+Now follow the individual encoders for certain numbers of bytes...
+          _
+         / |  __  ___  __ __
+        / ^| //  /__/ // //
+       /.==| \\ //_  // //
+It's  //  || // \_/_//_//_  and it's here to stay!
+
+> encodeOne_onebyte :: Word8 -> [Word8]
+> encodeOne_onebyte cp = [cp]
+
+
+00000yyyyyxxxxxx -> 110yyyyy 10xxxxxx
+
+> encodeOne_twobyte :: Word16 -> [Word8]
+> encodeOne_twobyte cp = [(0xC0.|.ys), (0x80.|.xs)]
+>     where
+>     xs, ys :: Word8
+>     ys = fromIntegral (shiftR cp 6)
+>     xs = (fromIntegral cp) .&. 0x3F
+
+
+zzzzyyyyyyxxxxxx -> 1110zzzz 10yyyyyy 10xxxxxx
+
+> encodeOne_threebyte :: Word16 -> [Word8]
+> encodeOne_threebyte cp = [(0xE0.|.zs), (0x80.|.ys), (0x80.|.xs)]
+>     where
+>     xs, ys, zs :: Word8
+>     xs = (fromIntegral cp) .&. 0x3F
+>     ys = (fromIntegral (shiftR cp 6)) .&. 0x3F
+>     zs = fromIntegral (shiftR cp 12)
+
+
+000uuuzzzzzzyyyyyyxxxxxx -> 11110uuu 10zzzzzz 10yyyyyy 10xxxxxx
+
+> encodeOne_fourbyte :: Word32 -> [Word8]
+> encodeOne_fourbyte cp = [0xF0.|.us, 0x80.|.zs, 0x80.|.ys, 0x80.|.xs]
+>     where
+>     xs, ys, zs, us :: Word8
+>     xs = (fromIntegral cp) .&. 0x3F
+>     ys = (fromIntegral (shiftR cp 6)) .&. 0x3F
+>     zs = (fromIntegral (shiftR cp 12)) .&. 0x3F
+>     us = fromIntegral (shiftR cp 18)
+
+
+
+///- Decoding -///
+
+The decoding is a bit more involved. The byte sequence could contain all
+sorts of corruptions. The user must be able to either notice or ignore these
+errors.
+
+I will first look at the decoding of a single character. The process
+consumes a certain number of bytes from the input. It returns the
+remaining input and either an error and the index of its occurance in the
+byte sequence or the decoded character.
+
+> data Error
+
+The first byte in a sequence starts with either zero, two, three, or four
+ones and one zero to indicate the length of the sequence. If it doesn't,
+it is invalid. It is dropped and the next byte interpreted as the start
+of a new sequence.
+
+>     = InvalidFirstByte
+
+All bytes in the sequence except the first match the bit pattern 10xxxxxx.
+If one doesn't, it is invalid. The sequence up to that point is dropped
+and the "invalid" byte interpreted as the start of a new sequence. The error
+includes the length of the partial sequence and the number of expected bytes.
+
+>     | InvalidLaterByte Int      -- the byte at relative index n was invalid
+
+If a sequence ends prematurely, it has been truncated. It dropped and
+decoding stops. The error reports the actual and expected lengths of the
+sequence.
+
+>     | Truncated Int Int         -- only n of m expected bytes were present
+
+Some sequences would represent code points which would be encoded as a
+shorter sequence by a conformant encoder. Such non-shortest sequences are
+considered erroneous and dropped. The error reports the actual and
+expected number of bytes used.
+
+>     | NonShortest Int Int       -- n instead of m bytes were used
+
+Unicode code points are in the range of [0..0x10FFFF]. Any values outside
+of those bounds are simply invalid.
+
+>     | ValueOutOfBounds
+
+There is no such thing as "surrogate pairs" any more in UTF-8. The
+corresponding code points now form illegal byte sequences.
+
+>     | Surrogate
+>       deriving (Show, Eq)
+
+
+Second, third, and fourth bytes share the common requirement to start
+with the bit sequence 10. So, here's the function to check that property.
+
+> first_bits_not_10 :: Word8 -> Bool
+> first_bits_not_10 b
+>     | (b.&.0xC0) /= 0x80  = True
+>     | otherwise           = False
+
+
+Erm, OK, the single-character decoding function's return type is a bit
+longish. It is a tripel:
+
+ - The first component contains the decoded character or an error
+   if the byte sequence was erroneous.
+ - The second component contains the number of bytes that were consumed
+   from the input.
+ - The third component contains the remaining bytes of input.
+
+> decodeOne :: [Word8] -> (Either Error Char, Int, [Word8])
+> decodeOne bs@(b1:rest)
+>     | b1 < 0x80   = decodeOne_onebyte bs
+>     | b1 < 0xC0   = (Left InvalidFirstByte, 1, rest)
+>     | b1 < 0xE0   = decodeOne_twobyte bs
+>     | b1 < 0xEE   = decodeOne_threebyte bs
+>     | b1 < 0xF5   = decodeOne_fourbyte bs
+>     | otherwise   = (Left ValueOutOfBounds, 1, rest)
+> decodeOne [] = error "UTF8.decodeOne: No input"
+
+
+0xxxxxxx -> 000000000xxxxxxx
+
+> decodeOne_onebyte :: [Word8] -> (Either Error Char, Int, [Word8])
+> decodeOne_onebyte (b:bs) = (Right (cpToChar b), 1, bs)
+> decodeOne_onebyte[] = error "UTF8.decodeOne_onebyte: No input (can't happen)"
+
+> cpToChar :: Integral a => a -> Char
+> cpToChar = chr . fromIntegral
+
+
+110yyyyy 10xxxxxx -> 00000yyyyyxxxxxx
+
+> decodeOne_twobyte :: [Word8] -> (Either Error Char, Int, [Word8])
+> decodeOne_twobyte (_:[])
+>     = (Left (Truncated 1 2), 1, [])
+> decodeOne_twobyte (b1:b2:bs)
+>     | b1 < 0xC2            = (Left (NonShortest 2 1), 2, bs)
+>     | first_bits_not_10 b2 = (Left (InvalidLaterByte 1), 1, (b2:bs))
+>     | otherwise            = (Right (cpToChar result), 2, bs)
+>     where
+>     xs, ys, result :: Word32
+>     xs = fromIntegral (b2.&.0x3F)
+>     ys = fromIntegral (b1.&.0x1F)
+>     result = shiftL ys 6 .|. xs
+> decodeOne_twobyte[] = error "UTF8.decodeOne_twobyte: No input (can't happen)"
+
+
+1110zzzz 10yyyyyy 10xxxxxx -> zzzzyyyyyyxxxxxx
+
+> decodeOne_threebyte :: [Word8] -> (Either Error Char, Int, [Word8])
+> decodeOne_threebyte (_:[])   = threebyte_truncated 1
+> decodeOne_threebyte (_:_:[]) = threebyte_truncated 2
+> decodeOne_threebyte bs@(b1:b2:b3:rest)
+>     | first_bits_not_10 b2
+>         = (Left (InvalidLaterByte 1), 1, drop 1 bs)
+>     | first_bits_not_10 b3
+>         = (Left (InvalidLaterByte 2), 2, drop 2 bs)
+>     | result < 0x0080
+>         = (Left (NonShortest 3 1), 3, rest)
+>     | result < 0x0800
+>         = (Left (NonShortest 3 2), 3, rest)
+>     | result >= 0xD800 && result < 0xE000
+>         = (Left Surrogate, 3, rest)
+>     | otherwise
+>         = (Right (cpToChar result), 3, rest)
+>     where
+>     xs, ys, zs, result :: Word32
+>     xs = fromIntegral (b3.&.0x3F)
+>     ys = fromIntegral (b2.&.0x3F)
+>     zs = fromIntegral (b1.&.0x0F)
+>     result = shiftL zs 12 .|. shiftL ys 6 .|. xs
+> decodeOne_threebyte[]
+>  = error "UTF8.decodeOne_threebyte: No input (can't happen)"
+
+> threebyte_truncated :: Int -> (Either Error Char, Int, [Word8])
+> threebyte_truncated n = (Left (Truncated n 3), n, [])
+
+
+11110uuu 10zzzzzz 10yyyyyy 10xxxxxx -> 000uuuzzzzzzyyyyyyxxxxxx
+
+> decodeOne_fourbyte :: [Word8] -> (Either Error Char, Int, [Word8])
+> decodeOne_fourbyte (_:[])     = fourbyte_truncated 1
+> decodeOne_fourbyte (_:_:[])   = fourbyte_truncated 2
+> decodeOne_fourbyte (_:_:_:[]) = fourbyte_truncated 3
+> decodeOne_fourbyte bs@(b1:b2:b3:b4:rest)
+>     | first_bits_not_10 b2
+>         = (Left (InvalidLaterByte 1), 1, drop 1 bs)
+>     | first_bits_not_10 b3
+>         = (Left (InvalidLaterByte 2), 2, drop 2 bs)
+>     | first_bits_not_10 b4
+>         = (Left (InvalidLaterByte 3), 3, drop 3 bs)
+>     | result < 0x0080
+>         = (Left (NonShortest 4 1), 4, rest)
+>     | result < 0x0800
+>         = (Left (NonShortest 4 2), 4, rest)
+>     | result < 0x10000
+>         = (Left (NonShortest 4 3), 4, rest)
+>     | result > 0x10FFFF
+>         = (Left ValueOutOfBounds, 4, rest)
+>     | otherwise
+>         = (Right (cpToChar result), 4, rest)
+>     where
+>     xs, ys, zs, us, result :: Word32
+>     xs = fromIntegral (b4 .&. 0x3F)
+>     ys = fromIntegral (b3 .&. 0x3F)
+>     zs = fromIntegral (b2 .&. 0x3F)
+>     us = fromIntegral (b1 .&. 0x07)
+>     result = xs .|. shiftL ys 6 .|. shiftL zs 12 .|. shiftL us 18
+> decodeOne_fourbyte[]
+>  = error "UTF8.decodeOne_fourbyte: No input (can't happen)"
+
+> fourbyte_truncated :: Int -> (Either Error Char, Int, [Word8])
+> fourbyte_truncated n = (Left (Truncated n 4), n, [])
+
+
+The decoder examines all input, recording decoded characters as well as
+error-index pairs along the way.
+
+> decode :: [Word8] -> ([Char], [(Error,Int)])
+> decode bytes = iter 0 [] [] bytes
+>     where
+>     iter :: Int -> [Char] -> [(Error,Int)] -> [Word8]
+>          -> ([Char], [(Error,Int)])
+>     iter _ cs es [] = (reverse cs, reverse es)
+>     iter idx cs es bs
+>         = case decodeOne bs of
+>           (Left e, n, rest)  -> iter (idx+n) cs     ((e,idx):es) rest
+>           (Right c, n, rest) -> iter (idx+n) (c:cs) es           rest
+
addfile ./samples/test/UTF8Sampler.hs
hunk ./samples/test/UTF8Sampler.hs 1
+-- an eyeball test for unicode handling
+-- loads a file of UTF-8 encoded strings (hardcoded below) and displays widgets
+-- for each one of the strings
+-- Eric Kow 2006
+
+module Main where
+
+import UTF8
+
+import Graphics.UI.WX
+import Graphics.UI.WXCore
+import System.IO
+import Control.Monad (liftM)
+import Data.Word (Word8)
+import Foreign.Marshal.Array
+
+main :: IO ()
+main = start sampler
+
+sampler :: IO ()
+sampler =
+ do f  <- frame [text := "UTF-8 viewer"]
+    pnl <- panel f []
+    nb  <- notebook pnl []
+    --
+    sLines <- liftM lines readTestFile
+    let bunchOf label thing =
+         do p  <- panel nb []
+            ws <- mapM (\t -> thing p [ text := t, tooltip := t ]) sLines
+            return $ tab label $ container p $ margin 10 $ column 1 $ map widget ws
+        bunchOfSel label thing =
+         do p <- panel nb []
+            w <- thing p [on select ::= logSelect sLines]
+            return $ tab label $ container p $ margin 10 $ widget w
+    -- manually created tabs
+    p1 <- panel nb []
+    let for1 thing =
+          do w <- thing p1 [ on select ::= logSelect sLines, items := sLines ]
+             set w [ selection := 0 ]
+             return w
+    p1choice <- for1 choice
+    p1combo  <- for1 comboBox
+    p1slist  <- for1 singleListBox
+    p1mlist  <- multiListBox p1 [ items := sLines ]
+    let t1 = tab "Selectors" $ container p1 $ margin 10 $ column 1 $
+             [ label "choice", widget p1choice
+             , label "combo" , widget p1combo
+             , label "s-list", widget p1slist
+             , label "m-list", widget p1mlist ]
+    p2 <- panel nb []
+    let t2 = tab "Labels" $ container p2 $ column 1 $ map label sLines
+    --
+    textlog <- textCtrl pnl [enabled := False, wrap := WrapNone]
+    textCtrlMakeLogActiveTarget textlog
+    logMessage "logging enabled"
+    --
+    ts <- sequence [ bunchOf "Static" staticText
+                   , bunchOf "TextEntry" textEntry
+                   , bunchOf "Checks" checkBox
+                   , bunchOf "Buttons" button
+                   , bunchOfSel "Radio"  (\p -> radioBox p Vertical sLines)
+                   ]
+    --
+    set f [layout := container pnl $ hfill $ column 0
+            [ hfill $ tabs nb $ t1:t2:ts
+            , hfill $ widget textlog ]
+          ]
+ where
+    logSelect labels w
+      = do i <- get w selection
+           s <- get w (item i)
+           logMessage ("selected index: " ++ show i ++ ": " ++ s)
+
+--  from the mailing list
+hGetBytes :: Handle -> Int -> IO [Word8]
+hGetBytes h c = allocaArray c $ \p ->
+                  do c' <- hGetBuf h p c
+                     peekArray c' p
+
+readTestFile :: IO String
+readTestFile =
+ do h  <- openBinaryFile testFile ReadMode
+    ws <- hGetBytes h testFileSize
+    return . fst . decode $ ws
+
+testFile :: FilePath
+testFile = "utf-tests"
+testFileSize :: Int -- FIXME: is there a portable way to do fileSize?
+testFileSize = 1846
addfile ./samples/test/utf-tests
hunk ./samples/test/utf-tests 1
+ میں کانچ کھا سکتا ہوں اور مجھے تکلیف نہیں ہوتی (Urdu)
+ زه شيشه خوړلې شم، هغه ما نه خوږوي (Pashto)
+.ᠪᠢ  ᠰᠢᠯᠢ  ᠢᠳᠡᠶᠦ  ᠴᠢᠳᠠᠨᠠ ᠂ ᠨᠠᠳᠤᠷ  ᠬᠣᠤᠷᠠᠳᠠᠢ  ᠪᠢᠰᠢ (Mongolian (Classic))
+ཤལ་ས་ཟ་ནས་ང་ན་ག་མ་རད། (Tibetan)
+我能吞下玻璃而不伤身体   (Chinese simplified)
+我能吞下玻璃而不傷身體。 (Chinese traditional)
+Góa ē-tàng chia̍h po-lê, mā bē tio̍h-siong. (Taiwanese)
+私はガラスを食べられます。それは私を傷つけません。(Japanese)
+나는 유리를 먹을 수 있어요. 그래도 아프지 않아요(Korean)
+Μπορώ να φάω σπασμένα γυαλιά χωρίς να πάθω τίποτα. (Greek)
+Ég  get etið gler án þess að meiða mig. (Íslenska / Icelandic)
+Mogę jeść szkło, i mi nie szkodzi. (Polish)
+Pot să mănânc sticlă și ea nu mă rănește. (Romanian)
+Я можу їсти шкло, й воно мені не пошкодить. (Ukrainian)
+Կրնամ ապակի ուտել և ինծի անհանգիստ չըներ։ (Armenian)
+მინას ვჭამ და არა მტკივა. (Georgian)
+म कच ख सकत ह, मझ उस स कई पड नह हत. (Hindi)
+אני יכול לאכול זכוכית וזה לא מזיק לי. (Hebrew)
+איך קען עסן גלאז און עס טוט מיר נישט װײ. (Yiddish)
+أنا قادر على أكل الزجاج و هذا ل يؤلمني. (Arabic)
+ラスを食べられます。それは私を傷つけません。 (Japanese)
+ฉนกนกระจกได แตมนไมทำใหฉนเจบ (Thai)
+¥·£·€·$·¢·₡·₢·₣·₤·₥·₦·₧·₨·₩·₪·₫·₭·₮·₯ (currency symbols)
}

Context:

[Tweak wx build target to depend on wxcore-clean.
Eric Kow <[EMAIL PROTECTED]>**20061115002142
 
 This avoids weird build errors with GHC 6.6 like
 wx/src/Graphics/UI/WX/Types.hs:94:0:
     Bad interface file: out/wx/imports/Graphics/UI/WXCore/Types.hi
         Something is amiss; requested module
 
] 
[Update Windows/VC++ build for 0.10.1 (from [EMAIL PROTECTED]).
Eric Kow <[EMAIL PROTECTED]>**20061029082957
 
] 
[Add support for toolbar divider and other toolbar options (from [EMAIL PROTECTED])
[EMAIL PROTECTED] 
[Add support for toolbar divider (for [EMAIL PROTECTED])
[EMAIL PROTECTED] 
[Add support for list item mask (from [EMAIL PROTECTED])
[EMAIL PROTECTED] 
[Add support for Calendar events (from [EMAIL PROTECTED])
[EMAIL PROTECTED] 
[Add support for wxWidgets version >= 2.5 (Sound API, db API)
[EMAIL PROTECTED] 
[Shelarcy patch: fix typos in wxHaskell samples/contrib
[EMAIL PROTECTED] 
[Separate make/make install for wxcore and wx.
Eric Kow <[EMAIL PROTECTED]>**20061027201218
 
 Now the user has to type
  make
  (sudo) make install
  make wx
  (sudo) make wx-install
 
 This is a tweak of Shelarcy's patch for making wxhaskell compile on GHC 6.6.
 The intention is to avoid the surprising behaviour of wxcore being installed
 when the user types 'make'.
 
] 
[Add shelarcy patch for compile with GHC-6.6
[EMAIL PROTECTED] 
[(OS X) Skip intermediate step of compiling master.o.
Eric Kow <[EMAIL PROTECTED]>**20060813212620
 
 Removing this step (which compiles master.o, and combines it with other
 stuff to get the real library we want) avoids weird error messages like
 
 ld: out/wxc/master.o undefined symbol 36218 (__ZdaPv) can't be a weak
 definition
 
 It's quite possible that this breaks something else, though...
 
] 
[Update VC++ project file to reflect new wxWidgets version support (untested)
[EMAIL PROTECTED] 
[Update VC++ project file to reflect updated DLL version supporting wxWidgets 2.6.3
[EMAIL PROTECTED] 
[Update revision numbers and wxversion guesses for Windows / VC++ ([EMAIL PROTECTED])
[EMAIL PROTECTED] 
[Shelarcy patch (VC project for wxWindows 2.6.3)
[EMAIL PROTECTED] 
[Shelarcy patch (WxcTypes.hs)
[EMAIL PROTECTED] 
[Shelarcy patch (eljdialup.cpp)
[EMAIL PROTECTED] 
[Shelarcy patch (db.cpp)
[EMAIL PROTECTED] 
[(wxc, Unicode) Files for compiling unicode version under Visual Studio.
shelarcy <[EMAIL PROTECTED]>**20060813212315
 
 This is Eric Kow recording on Shelarcy's behalf.  This corresponds to version
 08 of my Unicode patch.
 
] 
[Add a small makefile for compiling the samples.
Eric Kow <[EMAIL PROTECTED]>**20060813211705
 
 (This comes from version 08 of my Unicode patch).
 
] 
[(wxcore, Unicode) Add/use ability to interact with C wchar_t.
Eric Kow <[EMAIL PROTECTED]>**20060813211211
 
 This corresponds to the wxcore part of my Unicode patch, version 08
 modulo trailing whitespace.
 
 I believe this would require for wxWidgets and wxhaskell to be compiled with
 Unicode enabled.
 
] 
[(wxdirect, Unicode) Use the Haskell types for C wchar_t and friends.
Eric Kow <[EMAIL PROTECTED]>**20060813210420
 
 I believe this would require that wxWidgets be compiled with Unicode
 enabled.
 
] 
[(wxc, Unicode) Use wxChar instead of char.
Eric Kow <[EMAIL PROTECTED]>**20060813205557
 
 wxChar is a C preprocessor macro that selects for char under
 --disable-unicode, and for wchar_t under --enable-unicode.
 
 This corresponds to version 08 of my Unicode patch, but only the parts
 which affect wxc.
 
] 
[[wxhaskell-from-cvs @ 2005-05-08 08:12:51 by dleijen]
dleijen**20050508081251
 updated change log
] 
[[wxhaskell-from-cvs @ 2005-05-08 07:24:23 by dleijen]
dleijen**20050508072423
 Compile wx via -fvia-C to fix crash with ghci on windows
] 
[TAG wxhakell-0-9-4
Unknown tagger**20060712042545] 
Patch bundle hash:
e86ee42d1935c20164f4832fdc22f26c20b4c420
-------------------------------------------------------------------------
Take Surveys. Earn Cash. Influence the Future of IT
Join SourceForge.net's Techsay panel and you'll get the chance to share your
opinions on IT & business topics through brief surveys - and earn cash
http://www.techsay.com/default.php?page=join.php&p=sourceforge&CID=DEVDEV
_______________________________________________
wxhaskell-users mailing list
[email protected]
https://lists.sourceforge.net/lists/listinfo/wxhaskell-users

Reply via email to