[GHC] #14302: ghc panic on simple program
GHC
ghc-devs at haskell.org
Sun Oct 1 18:55:25 UTC 2017
#14302: ghc panic on simple program
-------------------------------------+-------------------------------------
Reporter: aberent | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by aberent):
This appears to be an error in the error handling. Once I fix the
compilation errors reported by ghci, ghc is happy to compile it.
FYI my fixed code is:
{{{
module Tiltmaze (solve) where
import Data.Sequence as Sequence
-- A maze is a grid of empty cells and walls
-- true means wall
type Maze = Seq (Seq Bool)
data Direction = North | South | East | West deriving (Eq, Show)
directions = [North, South, East, West]
step :: Direction -> Int -> Int -> (Int, Int)
step d x y
| d == North = (x, y-1)
| d == South = (x, y+1)
| d == East = (x+1, y)
| d == West = (x-1, y)
solve :: Maze -> Int -> Int -> Int -> Int -> Bool
solve m sx sy tx ty
| sx == tx && sy == ty = True
| otherwise =
let solved m x y d
| x' < 0 = False
| y' < 0 = False
| x' >= Sequence.length m = False
| y' >= Sequence.length (m `index` x') = False
| not ((m `index` x') `index` y') = False
| otherwise = solve m' x' y' tx ty
where (x', y') = step d x y
m' = update x (update y False (m `index` x)) m
in any (solved m sx sy) directions
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14302#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list