problem compiling an older Haskell program with GHC 6.6.1

hi, I really appreciate the amazingly fast and helpful feedback to my previous message. that problem (FiniteMap not found) is solved. but a new problem came up... I am trying to compile paradox 1.0, an older (GHC 5) Haskell program, with GHC 6.6.1 (the Solaris 10 / x86 binary distribution). now I get the error Data.hs:760:20: Not in scope: 'bounds' Data.hs is one of the files in the program. here is the nearby code: updateTable :: Hash a => a -> IO b -> Table a b -> IO b updateTable x my (MkTable ref) = do MkHTab n arr <- readIORef ref let (_,size) = bounds arr hashx = hash x i = hashx `mod` size ... in case it's helpful, the entire paradox source code is at http://www.cs.sunysb.edu/~stoller/out/paradox-1.0-casc.tar.gz just delete "-package lang" from the Makefile before running "make". any advice would be greatly appreciated. best regards, scott

On Sat, Jul 07, 2007 at 03:59:48PM -0400, Scott Stoller wrote:
hi,
I really appreciate the amazingly fast and helpful feedback to my previous message. that problem (FiniteMap not found) is solved. but a new problem came up...
I am trying to compile paradox 1.0, an older (GHC 5) Haskell program, with GHC 6.6.1 (the Solaris 10 / x86 binary distribution).
now I get the error
Data.hs:760:20: Not in scope: 'bounds'
Data.hs is one of the files in the program. here is the nearby code:
updateTable :: Hash a => a -> IO b -> Table a b -> IO b updateTable x my (MkTable ref) = do MkHTab n arr <- readIORef ref let (_,size) = bounds arr hashx = hash x i = hashx `mod` size ...
in case it's helpful, the entire paradox source code is at http://www.cs.sunysb.edu/~stoller/out/paradox-1.0-casc.tar.gz just delete "-package lang" from the Makefile before running "make".
Bounds was removed in 6.4.x to allow for dynamically sized arrays; it should work as: updateTable :: Hash a => a -> IO b -> Table a b -> IO b updateTable x my (MkTable ref) = do MkHTab n arr <- readIORef ref (_,size) <- getBounds arr let hashx = hash x i = hashx `mod` size Stefan

hi, thanks to Stefan, I am past the second problem in compiling this program (needed to change 'bounds' to 'getBounds'). now I get a more intimidating error message... I am trying to compile paradox 1.0, an older (GHC 5) Haskell program, with GHC 6.6.1. I get the intimidating error message shown below. I would appreciate any advice about how to fix this. I am guessing that the problem might be a change in the type of some library function. best regards, scott p.s. the file causing the error is in the paradox source code at http://www.cs.sunysb.edu/~stoller/out/paradox-1.0-casc.tar.gz Building paradox (release) Compiling: AnalysisTypes.hs Glasgow Haskell Compiler, Version 6.6.1, for Haskell 98, compiled by GHC version 6.6.1 Using package config file: /usr/local/lib/ghc-6.6.1/package.conf wired-in package base mapped to base-2.1.1 wired-in package rts mapped to rts-1.0 wired-in package haskell98 mapped to haskell98-1.0 wired-in package template-haskell mapped to template-haskell-2.1 Hsc static flags: -fauto-sccs-on-all-toplevs -static Created temporary directory: /tmp/ghc835_0 *** Checking old interface for main:AnalysisTypes: *** Parser: *** Renamer/typechecker: AnalysisTypes.hs:135:2: Inferred type is less polymorphic than expected Quantified type variable `s' is mentioned in the environment: m :: forall b. STRef s Int -> STRef s ((:=>) Symbol [TypeId s]) -> STRef s ((:=>) Symbol ([TypeId s], TypeId s)) -> STRef s ((:=>) Symbol (TypeId s)) -> (String -> ST s b) -> (a -> ST s b) -> ST s b (bound at AnalysisTypes.hs:284:6) In the first argument of `runST', namely `(do idfs <- newSTRef 0 preds <- newSTRef empty funs <- newSTRef empty vars <- newSTRef empty m idfs preds funs vars (\ s -> return (Left s)) (\ _ -> do ps' <- readSTRef preds fs' <- readSTRef funs ps <- sequence ([... | (p, ts') <- ...]) fs <- sequence ([... | (f, (ts', t')) <- ...]) typeIds' <- sequence ([... | t' <- ...]) let typeIds = ... names = ... typesAndTypeIds = ... types = ... typeIdToType = ... typeOfId tid = ... predTable = ... funTable = ... typeOfPred Equal = ... typeOfPred (p ::- _) = ... typeOfFun (f ::- _) = ... trans c = ... where ... return (Right (types, trans))))' In the expression: runST (do idfs <- newSTRef 0 preds <- newSTRef empty funs <- newSTRef empty vars <- newSTRef empty m idfs preds funs vars (\ s -> return (Left s)) (\ _ -> do ps' <- readSTRef preds fs' <- readSTRef funs ps <- sequence ([... | (p, ts') <- ...]) fs <- sequence ([... | (f, (ts', t')) <- ...]) typeIds' <- sequence ([... | t' <- ...]) let typeIds = ... names = ... typesAndTypeIds = ... types = ... typeIdToType = ... typeOfId tid = ... predTable = ... funTable = ... typeOfPred Equal = ... typeOfPred (p ::- _) = ... typeOfFun (f ::- _) = ... trans c = ... where ... return (Right (types, trans)))) In the definition of `runT': runT tm = runST (do idfs <- newSTRef 0 preds <- newSTRef empty funs <- newSTRef empty vars <- newSTRef empty m idfs preds funs vars (\ s -> return (Left s)) (\ _ -> do ps' <- ... fs' <- ... ps <- ... fs <- ... typeIds' <- ... let ... ...)) where MkT m = tm *** Deleting temp files: Deleting: /tmp/ghc835_0/ghc835_0.hc Warning: deleting non-existent /tmp/ghc835_0/ghc835_0.hc *** Deleting temp dirs: Deleting: /tmp/ghc835_0 make: *** [AnalysisTypes.o] Error 1

On Sat, Jul 07, 2007 at 10:53:17PM -0400, Scott Stoller wrote:
hi,
thanks to Stefan, I am past the second problem in compiling this program (needed to change 'bounds' to 'getBounds'). now I get a more intimidating error message...
I am trying to compile paradox 1.0, an older (GHC 5) Haskell program, with GHC 6.6.1. I get the intimidating error message shown below. I would appreciate any advice about how to fix this. I am guessing that the problem might be a change in the type of some library function.
best regards, scott
p.s. the file causing the error is in the paradox source code at http://www.cs.sunysb.edu/~stoller/out/paradox-1.0-casc.tar.gz
Add {-# OPTIONS_GHC -fno-mono-pat-binds #-} You are the fourth person to discover monomorphic pattern bindings :) As an experiment, the GHC team has changed GHC to make pattern bindings (like MkT m = tm) default to only produce values usable at one type. The full generality of Haskell-98's rules complicated the implementation, and the idea was that if sufficiently few people complained, the next version of Haskell could use simpler rules. (at least that's how *I* remember the explanation.) Another workaround is to do it with an explicit unwrap: where m = case tm of MkT m -> m instead of where MkT m = tm Stefan

| Add {-# OPTIONS_GHC -fno-mono-pat-binds #-} | | You are the fourth person to discover monomorphic pattern bindings :) Yes, the details are here http://hackage.haskell.org/trac/haskell-prime/wiki/MonomorphicPatternBinding... If you could snip out the code that gave rise to the error, I'll add it to that wiki page. (There are four other examples there, one from Koen which might perhaps be essentially the same thing.) thanks Stefan for identifying this Simon

Simon Peyton-Jones writes:
| Add {-# OPTIONS_GHC -fno-mono-pat-binds #-} | | You are the fourth person to discover monomorphic pattern bindings :)
Yes, the details are here http://hackage.haskell.org/trac/haskell-prime/wiki/MonomorphicPatternBinding...
If you could snip out the code that gave rise to the error, I'll add it to that wiki page. (There are four other examples there, one from Koen which might perhaps be essentially the same thing.)
it looks like that example from Koen (one of the authors of Paradox) is essentially the same as this one, as you guessed. If you'd like to add this code anyway, let me know. or perhaps it would be more appropriate to ask Koen, since it's his code. best regards, scott
participants (3)
-
Scott Stoller
-
Simon Peyton-Jones
-
Stefan O'Rear