[GHC] #15054: ghc internal error appeared in GHCI

GHC ghc-devs at haskell.org
Thu Apr 19 07:24:45 UTC 2018


#15054: ghc internal error appeared in GHCI
-------------------------------------+-------------------------------------
           Reporter:  radrow         |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.1
          Component:  GHCi           |           Version:  8.2.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:  x86_64         |   Type of failure:  None/Unknown
  (amd64)                            |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 After playing with vectors in ghci I got following error:


 {{{
 ghc: internal error: Unable to commit 1048576 bytes of memory
 }}}

 It happened randomly, on empty prompt while no query was being evaluated

 I am using latest version of GHC on Arch Linux

 Here is my whole session:
 {{{
 >λ= import Criterion
 Criterion               Criterion.IO.Printf     Criterion.Main.Options
 Criterion.Report
 Criterion.Analysis      Criterion.Internal      Criterion.Measurement
 Criterion.Types
 Criterion.IO            Criterion.Main          Criterion.Monad
 >λ= import Criterion.Main
 >λ= import Data.Vector
 >λ= import Data.Vector as V
 >λ= main = default
 defaultConfig    defaultMain      defaultMainWith
 >λ= defaultMain [bench "TESTXD" $ whnf ([1..100000]!!) 9999]
 benchmarking TESTXD
 time                 19.81 μs   (19.66 μs .. 19.99 μs)
                      0.999 R²   (0.999 R² .. 1.000 R²)
 mean                 13.47 μs   (12.93 μs .. 14.11 μs)
 std dev              853.8 ns   (542.7 ns .. 1.249 μs)
 variance introduced by outliers: 65% (severely inflated)

 >λ= defaultMain [bench "TESTXD" $ whnf ([1..100000]!!) 9999]
 benchmarking TESTXD
 time                 19.62 μs   (19.39 μs .. 19.99 μs)
                      0.999 R²   (0.998 R² .. 1.000 R²)
 mean                 13.49 μs   (12.85 μs .. 14.51 μs)
 std dev              1.154 μs   (524.9 ns .. 1.704 μs)
 variance introduced by outliers: 77% (severely inflated)

 >λ= v = V.fromList [1..100000]
 Display all 192 possibilities? (y or n)
 V.!                  V.fold1M'            V.indexed            V.prescanl
 V.unsafeDrop
 V.!?                 V.fold1M'_           V.init               V.prescanl'
 V.unsafeFreeze
 V.++                 V.fold1M_            V.iscanl             V.prescanr
 V.unsafeHead
 V.//                 V.foldM              V.iscanl'            V.prescanr'
 V.unsafeHeadM
 V.MVector            V.foldM'             V.iscanr             V.product
 V.unsafeIndex
 V.Vector             V.foldM'_            V.iscanr'            V.replicate
 V.unsafeIndexM
 V.accum              V.foldM_             V.iterateN
 V.replicateM         V.unsafeInit
 V.accumulate         V.foldl              V.iterateNM          V.reverse
 V.unsafeLast
 V.accumulate_        V.foldl'             V.izipWith           V.scanl
 V.unsafeLastM
 V.all                V.foldl1             V.izipWith3          V.scanl'
 V.unsafeSlice
 V.and                V.foldl1'            V.izipWith4          V.scanl1
 V.unsafeTail
 V.any                V.foldr              V.izipWith5          V.scanl1'
 V.unsafeTake
 V.backpermute        V.foldr'             V.izipWith6          V.scanr
 V.unsafeThaw
 V.break              V.foldr1             V.izipWithM          V.scanr'
 V.unsafeUpd
 V.concat             V.foldr1'            V.izipWithM_         V.scanr1
 V.unsafeUpdate
 V.concatMap          V.forM               V.last               V.scanr1'
 V.unsafeUpdate_
 V.cons               V.forM_              V.lastM              V.sequence
 V.unstablePartition
 V.constructN         V.force              V.length             V.sequence_
 V.unzip
 V.constructrN        V.freeze             V.map                V.singleton
 V.unzip3
 V.convert            V.fromList           V.mapM               V.slice
 V.unzip4
 V.copy               V.fromListN          V.mapM_              V.snoc
 V.unzip5
 V.create             V.generate           V.mapMaybe           V.span
 V.unzip6
 V.createT            V.generateM          V.maxIndex           V.splitAt
 V.update
 V.drop               V.head               V.maxIndexBy         V.sum
 V.update_
 V.dropWhile          V.headM              V.maximum            V.tail
 V.zip
 V.elem               V.ifilter            V.maximumBy          V.take
 V.zip3
 V.elemIndex          V.ifoldM             V.minIndex           V.takeWhile
 V.zip4
 V.elemIndices        V.ifoldM'            V.minIndexBy         V.thaw
 V.zip5
 V.empty              V.ifoldM'_           V.minimum            V.toList
 V.zip6
 V.enumFromN          V.ifoldM_            V.minimumBy          V.unfoldr
 V.zipWith
 V.enumFromStepN      V.ifoldl             V.modify             V.unfoldrM
 V.zipWith3
 V.enumFromThenTo     V.ifoldl'            V.notElem            V.unfoldrN
 V.zipWith4
 V.enumFromTo         V.ifoldr             V.null               V.unfoldrNM
 V.zipWith5
 V.filter             V.ifoldr'            V.or                 V.uniq
 V.zipWith6
 V.filterM            V.imap               V.partition
 V.unsafeAccum        V.zipWithM
 V.find               V.imapM              V.postscanl
 V.unsafeAccumulate   V.zipWithM_
 V.findIndex          V.imapM_             V.postscanl'
 V.unsafeAccumulate_
 V.findIndices        V.imapMaybe          V.postscanr
 V.unsafeBackpermute
 V.fold1M             V.indexM             V.postscanr'
 V.unsafeCopy
 >λ= defaultMain [bench "TESTXD" $ whnf ([1..100000]!!) 9999, bench "TESTV"
 $ whnf (\x -> (V.!) v x)]
 <interactive>:8:93: error:
     parse error (possibly incorrect indentation or mismatched brackets)
 ] λ= defaultMain [bench "TESTXD" $ whnf ([1..100000]!!) 9999, bench
 "TESTV" $ whnf (\x -> (V.!) v x)

 <interactive>:9:74: error:
     • Couldn't match expected type ‘Benchmarkable’
                   with actual type ‘Int -> Benchmarkable’
     • Probable cause: ‘whnf’ is applied to too few arguments
       In the second argument of ‘($)’, namely ‘whnf (\ x -> (!) v x)’
       In the expression: bench "TESTV" $ whnf (\ x -> (!) v x)
       In the first argument of ‘defaultMain’, namely
         ‘[bench "TESTXD" $ whnf ([1 .. 100000] !!) 9999,
 >λ= defaultMain [bench "TESTXD" $ whnf ([1..100000]!!) 9999, bench "TESTV"
 $ whnf (\x -> (V.!) v x) 9999] benchmarking TESTXD
 time                 20.61 μs   (20.47 μs .. 20.80 μs)
                      0.999 R²   (0.999 R² .. 1.000 R²)
 mean                 14.41 μs   (13.85 μs .. 14.88 μs)
 std dev              805.2 ns   (588.3 ns .. 1.036 μs)
 variance introduced by outliers: 59% (severely inflated)

 benchmarking TESTV
 time                 1.796 ms   (1.768 ms .. 1.831 ms)
                      0.997 R²   (0.995 R² .. 0.999 R²)
 mean                 1.426 ms   (1.367 ms .. 1.481 ms)
 std dev              153.6 μs   (123.2 μs .. 190.1 μs)
 variance introduced by outliers: 69% (severely inflated)
           (V.!)
 >λ=
 >λ= (V.!) v 999
 1000
 >λ= (V.!) v 9999
 10000
 >λ= l = [1..100000])

 <interactive>:13:16: error: parse error on input ‘)’
 >λ= l = [1..100000]
 >λ= l !! 9999
 10000
 >λ= l !! 99999
 100000
 >λ= l !! 999999
 *** Exception: Prelude.!!: index too large
 >λ= l = [1..10000000]
 >λ= l !! 999999
 1000000
 >λ= l !! 9999999
 10000000
 >λ= l !! 99999999
 *** Exception: Prelude.!!: index too large
 >λ= sum l

 <interactive>:22:1: error:
     Ambiguous occurrence ‘sum’
     It could refer to either ‘Data.Vector.sum’,
                              imported from ‘Data.Vector’
                           or ‘Prelude.sum’,
                              imported from ‘Prelude’ (and originally
 defined in ‘Data.Foldable’)
 >λ= Prelude.sum l
 50000005000000
 >λ= Prelude.sum l
 50000005000000
 >λ= v = V.fr
 V.freeze     V.fromList   V.fromListN
 >λ= v = V.fromList l
 >λ= V.last v
 10000000
 >λ= :sprint v
 v = _
 Display all 1088 possibilities? (y or n)
 >λ= V.sum v
 50000005000000
 >λ= V.sum v
 50000005000000
 >λ= V.last v
 10000000
 >λ= relast l
 read        readIO      readLn      reads       realToFrac  rem
 replicate   return
 readFile    readList    readParen   readsPrec   recip       repeat
 replicateM  reverse
 >λ= Prelude.last l
 10000000
 >λ= Prelude.last l
 10000000
 >λ= V.last v
 10000000
 >λ= :t (//)
 (//) :: Vector a -> [(Int, a)] -> Vector a
 >λ= :t v
 v :: (Enum a, Num a) => Vector a
 >λ= l = [1..10000000] :: [Int]
 >λ= last l

 <interactive>:37:1: error:
     Ambiguous occurrence ‘last’
     It could refer to either ‘Data.Vector.last’,
                              imported from ‘Data.Vector’
                           or ‘Prelude.last’,
                              imported from ‘Prelude’ (and originally
 defined in ‘GHC.List’)
 >λ= import Prelude as P
 >λ= P.last l
 10000000
 >λ= v = from
 fromEnum      fromInteger   fromIntegral  fromList      fromListN
 fromRational
 >λ= v = fromList l
 >λ= :t v
 v :: Vector Int
 >λ= V.last v
 10000000
 >λ= V.last v
 10000000
 >λ= V.last v
 10000000
 >λ= v = fromList l
 >λ= P.last l
 10000000
 >λ= P.last l
 10000000
 >λ= V.last v
 10000000
 >λ= V.last v
 10000000
 >λ= V.last v
 10000000
 >λ= P.last l
 10000000
 >λ= P.last l
 10000000
 >λ= l = [1..100000000] :: [Int]
 >λ= v = fromList l
 >λ= P.last l
 100000000
 >λ= V.last v
 100000000
 >λ= V.last v
 100000000
 >λ= :t v
 v :: Vector Int
 >λ= :t v
 v :: Vector Int
 >λ= :sprint v
 v = Data.Vector.Vector 0 100000000 _
 >λ= ghc: internal error: Unable to commit 1048576 bytes of memory
     (GHC version 8.2.2 for x86_64_unknown_linux)
     Please report this as a GHC bug:
 http://www.haskell.org/ghc/reportabug
 [1]    12349 killed     stack ghci
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15054>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list