#5307: Problems with new cyclic dependency error message
---------------------------------+------------------------------------------
Reporter: simonmar | Owner: simonpj
Type: bug | Status: new
Priority: highest | Milestone: 7.2.1
Component: Compiler | Version: 7.0.3
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Comment(by simonmar):
Here's how to generate some test data:
{{{
module Main where
import System.Random
import System.IO
import Control.Monad
import Control.Applicative
import qualified Data.Map as Map
import Text.Printf
import System.Environment
main = do
[x,y] <- fmap (fmap read) getArgs
(g1,g2) <- split <$> getStdGen
let edges = take y [ (x,[y]) | (x,y) <- zip (randomRs (1,x) g1)
(randomRs (1,x) g2) ]
edgemap = Map.fromListWith (++) edges
forM_ [1..x] $ \m -> do
h <- openFile ("M" ++ show m ++ ".hs") WriteMode
hPrintf h "module M%d where\n" m
mapM_ (hPrintf h "import M%d\n") (Map.findWithDefault [] m edgemap ::
[Int])
hClose h
}}}
use it like this (to generate 100 modules with 1000 random imports):
{{{
$ ghc modloop.hs
$ ./modloop 100 1000
$ ghc -M M1
}}}
for me, this sends GHC off into a little world of its own...
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5307#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs