Hrm.  On the C side the arrays disappear shortly after my call, so just
casting wouldn't really work.  I settled for the following monstrosity
where (cast :: a -> b) is your standard unsafePerformIO/IORef based
casting function:

peekPackedCString :: CString -> IO PackedString
peekPackedCString cs = do
  i <- findLength cs 0
  (arr :: IOUArray Int Char) <- newArray_ (0,i)
  writeToArr arr i 0 cs
  (arr' :: UArray Int Char) <- unsafeFreeze arr
  return (cast arr')
  where
    findLength ptr n = do
      c <- peek ptr
      if c == 0
        then return n
        else findLength (plusPtr ptr 1) $! n+1
    writeToArr arr len pos ptr
        | pos >= len = return ()
        | otherwise  = do
      c <- peek ptr
      writeArray arr pos (castCCharToChar c)
      writeToArr arr len (len+1) (plusPtr ptr 1)

it's pretty fast and works only because the type of PackedString is
  newtype PackedString = PS (UArray Int Char)

so the casting gives us what we want.

This does seem like something that belongs in the PackedString library
or the Foreign.C.String library, though.

 - Hal

--
 Hal Daume III                                   | [EMAIL PROTECTED]
 "Arrest this man, he talks in maths."           | www.isi.edu/~hdaume


> -----Original Message-----
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of 
> John Meacham
> Sent: Thursday, August 21, 2003 3:10 AM
> To: [EMAIL PROTECTED]
> Subject: Re: fast CString -> IO PackedString fuction
> 
> 
> On Wed, Aug 20, 2003 at 06:48:58PM -0700, Hal Daume wrote:
> > is there a way to go from a CString to a PackedString w/o 
> going through
> > a normal String in the middle?
> > or should i write my own?
> 
> If you can get a wchar_t * out of the app then that can be simply cast
> to a packedstring, this is quite speedy.
> if you use mbsrtowcs(3) and friends to do the conversion from char *
> then you get properly localized text via locale settings for free :)
> I have used this sort of thing for interfacing haskell to libraries
> where honoring locale was important in the past. 
>         John 
> 
> -- 
> --------------------------------------------------------------
> -------------
> John Meacham - California Institute of Technology, Alum. - 
> [EMAIL PROTECTED]
> --------------------------------------------------------------
> -------------
> _______________________________________________
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> 
_______________________________________________
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to