type error when compiling an older Haskell program

Scott Stoller stoller at cs.sunysb.edu
Sat Jul 7 22:53:17 EDT 2007


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


More information about the Glasgow-haskell-users mailing list