trying to compile regex-tdfa, I ran into another issue. (earlier I had a 
cabal problem but that's resolved.)

there's a line that won't compile, neither for ghc 6.6.1 nor 6.7 

import 
GHC.Prim(MutableByteArray#,RealWorld,Int#,sizeofMutableByteArray#,unsafeCoerce#)

so the fresh darcs regex tdfa package won't build.

This line (line 16 below) causes this error for 

  ghc -e '' RunMutState.hs

for both ghc 6.1 and 6.7 

Much obliged for any help,

Thomas.

*********************************

[EMAIL PROTECTED]:~/installs/regex_darcs/regex-tdfa>runghc Setup.hs build
Preprocessing library regex-tdfa-0.93...
Building regex-tdfa-0.93...

Text/Regex/TDFA/RunMutState.hs:16:32: parse error on input `#'
[EMAIL PROTECTED]:~/installs/regex_darcs/regex-tdfa>head -n20 
Text/Regex/TDFA/RunMutState.hs | cat -n 
     1  {-# LANGUAGE CPP #-}
     2  module 
Text.Regex.TDFA.RunMutState(TagEngine(..),newTagEngine,newTagEngine2
     3                                    ,newScratch,tagsToGroupsST
     4 ,toInstructions,compareWith,resetScratch
     5                                    ,SScratch(..),MScratch,WScratch) 
where
     6 
     7  import Control.Monad(forM_,liftM,liftM2,liftM3,foldM)
     8  --import Control.Monad.ST.Strict as S (ST)
     9  --import qualified Control.Monad.ST.Lazy as L (ST)
    10  import Control.Monad.State(MonadState(..),execState)
    11 
    12  import Data.Array.Base(unsafeRead,unsafeWrite,STUArray(..))
    13  #ifdef __GLASGOW_HASKELL__
    14  import GHC.Arr(STArray(..))
    15  import GHC.ST(ST(..))
*** 16  import 
GHC.Prim(MutableByteArray#,RealWorld,Int#,sizeofMutableByteArray#,unsafeCoerce#)
    17  #else
    18  import Control.Monad(when)
    19  import Control.Monad.ST(ST)
    20  import Data.Array.ST(STArray)
[EMAIL PROTECTED]:~/installs/regex_darcs/regex-tdfa>



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to