ghci's :l -> internal error: evacuate: strange closure type 8306
GHCi crashes when :loading a file. Unfortunately I can't reproduce the bug, so this one's gonna be lots of information that probably will help very little.
This is the actual error message:
*CommonStatistics Data.List> :l SimpleCellularALife
[1 of 2] Compiling CommonStatistics ( CommonStatistics.hs, interpreted )
<interactive>: internal error: evacuate: strange closure type 8306
(GHC version 7.6.3 for i386_unknown_mingw32)
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
This application has requested the Runtime to terminate it in an unusual way.
Please contact the application's support team for more information.
This one was the error I was working on, i.e. the (legit) error in the previous call: (Including this because it gives you a clue what I was working on, I was mostly fiddling around with parens in placeAgents' gnd function)
*CommonStatistics Data.List> :l SimpleCellularALife
[1 of 2] Compiling CommonStatistics ( CommonStatistics.hs, interpreted )
[2 of 2] Compiling SimpleCellularALife ( SimpleCellularALife.hs, interpreted )
SimpleCellularALife.hs:70:28:
Couldn't match expected type `Array i0 e0'
with actual type `Ground'
In the return type of a call of `ground'
In the first argument of `(!)', namely `ground (tiles w)'
In the expression: (ground (tiles w) ! (fst $ head grp))
SimpleCellularALife.hs:70:36:
Couldn't match expected type `Tile'
with actual type `Array Coordinates Tile'
In the return type of a call of `tiles'
In the first argument of `ground', namely `(tiles w)'
In the first argument of `(!)', namely `ground (tiles w)'
Failed, modules loaded: CommonStatistics.
Included Source Files - CommonStatistics.hs:
module CommonStatistics where
type Memory = [Int]--Internal state of an Agent.
data StatUpdate = StatUpdate{
newVictories :: [Int] -- by agentID
} deriving (Show)
data Agent = Agent{
agentID :: Int,
sourcePath :: FilePath, --path to .hs source file. relative to executable
doFunc :: [String] -> Memory -> (Memory, [String]),
evFunc :: [String] -> Memory -> (Memory, String),
personalMemory :: Memory
}
instance Show Agent where
show (Agent {
agentID = aID,
sourcePath = path,
doFunc = forgetit,
evFunc = forgetittoo,
personalMemory = mem
}) = show (aID, path, mem)
And SimpleCellularALife.hs: (I am not exactly confident that this is the version that caused the error. I sadly can't reproduce it, so there's no confirming that.
module SimpleCellularALife where
import Data.Array
import Data.List
import System.Random
import CommonStatistics
data Ground = Ground {
food :: Int
}
data Entity = Entity{
ai :: Agent,
health :: Int
}
data Tile = Tile{
ground :: Ground,
entities :: [Entity]
}
data World = World {
tiles :: Array Coordinates Tile
}
type Coordinates = (Int, Int)
getRandomPosition :: RandomGen t => World -> t -> (t, Coordinates)
getRandomPosition w rand =
let
((minx, miny), (maxx, maxy)) = bounds $ tiles w
(x, rand2) = randomR (minx, maxx) rand
(y, rand3) = randomR (miny, maxy) rand2
in
(rand3, (x, y))
placeAgents :: RandomGen t => World -> [Agent] -> t -> (t, World)
placeAgents w agents rand =
let
createTileUpdates (ag:ags) wrld rnd =
let
(rnd2, coords) = getRandomPosition wrld rnd
(rnd3, restUpd) = createTileUpdates ags wrld rnd2
in (rnd3, (coords, ag) : restUpd)
createTileUpdates [] wrld rnd = (rnd, [])
(rand2, assocList) = createTileUpdates agents w rand
groupedAssocList = groupBy (\(c1, a1) (c2, a2) -> c1 == c2) $ sortBy (\(c1, a1) (c2, a2) -> compare c1 c2) assocList
gnd grp = ground ((tiles w) ! (fst $ head grp))
condenseGroup grp = (fst $ head grp, Tile{ground = gnd grp, entities = snd $ unzip grp})
--map condenseGroup groupedAssocList --::(Coordinates, Tile)
in
(rand, w)
--placeAgents (placeAgent w firstAg x y) agents rand3
Someone suggested that this might've been GHCI running out of memory. I am as of writing this at 66% out of 4GB used. The GHCI instance was opened for an extended period of time, so it might have racked up quite a bit of RAM usage. I can say though that considering the file sizes, 1.3GB of RAM usage seems unreasonable.
And because I haven't yet written enough, here are all the variations of the line I was working on that could've caused it. Pulled them out of my text editor's buffer.
gnd grp = (ground (tiles w) ! fst $ head grp)
gnd grp = (ground (tiles w) ! (fst $ head grp)
gnd grp = (ground (tiles w) ! (fst $ head grp))
gnd grp = (ground ((tiles w) ! (fst $ head grp))
gnd grp = ground ((tiles w) ! (fst $ head grp))
Trac metadata
Trac field | Value |
---|---|
Version | 7.6.3 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | GHCi |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | hvr, kacktusdev@gmail.com |
Operating system | |
Architecture |