On Tuesday 01 February 2011 10:20:26, Carsten Schultz wrote:
> Hello everyone,
>
> I am trying to compile some code that I have written a long time ago
> (might have been for ghc 6.3), and I have not done much Haskell in the
> meantime.  I have trouble compiling the code, maybe only because I do
> not remember the necessary flags (yes, these should be in the source
> files), maybe because ghc has changed.

GHC has changed pretty much. I don't know whether there's a way to make 
your code compile with flags, without changing the code itself.

> I do for example have functions like this:
>
>
> getnArray :: Int -> [Word8] -> Maybe (UArray Int Word8, [Word8])
> getnArrayST :: Int -> [Word8] ->
>              (forall s . ST s (Maybe (UArray Int Word8, [Word8])))
>
> getnArrayST n bs :: ST s (Maybe (UArray Int Word8, [Word8])) =

Get rid of such signatures, this is where you get a parse error, I don't 
know if there's a way to make GHC parse it at all. I doubt it.

>     do
>     (a :: STUArray s Int Word8) <- newArray_ (0,n-1)

Move the signature to the RHS,

      a <- newArray_ (0,n-1) :: ST s (STUArray s Int Word8)

>     let loop k bs
>
>                | k == n = do fa <- freeze a
>
>                              return $ Just (fa, bs)
>
>                | k < n = case bs of
>
>                                  (b:bs) -> do
>                                            writeArray a k b
>                                            loop (k+1) bs
>                                  [] -> return Nothing
>     loop 0 bs
>
> getnArray n bs = runST (getnArrayST n bs)
>

With those changes (and ScopedTypeVariables), it compiles.



_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to