
#11126: Entered absent arg in a Repa program -------------------------------------+------------------------------------- Reporter: tuplanolla | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider the following program. {{{#!hs module Main where import Data.Array.Repa data Stuff = !(Array U DIM1 Double) `With` !Double deriving Show through :: Maybe Double -> Stuff -> Stuff m `through` (a `With` _) = let b = a +^ (negate `smap` sumS (extend (Z :. All :. (1 :: Int)) a)) c = maybe b (const (negate `smap` a)) m in computeUnboxedS c `With` sumAllS b main :: IO () main = print $ Just 1 `through` (fromListUnboxed (Z :. 1) [1] `With` 1) }}} It should produce the following result once run. {{{#!hs AUnboxed (Z :. 1) (fromList [-1.0]) `With` 0.0 }}} However, when built using `repa-3.4.0.1` and compiled with the options `-O3 -Wall -funfolding-keeness-factor1000 -funfolding-use-threshold1000`, it crashes as follows. {{{#!hs Main: Oops! Entered absent arg arr2 Array D DIM1 Double }}} Adding `-fno-strictness` to the compiler options or removing strictness annotations from the code makes the problem disappear, so this looks like a strictness analyzer problem. The libraries used were * `QuickCheck-2.8.1`, * `array-0.5.1.0`, * `base-4.8.1.0`, * `bytestring-0.10.6.0`, * `containers-0.5.6.2`, * `deepseq-1.4.1.1`, * `ghc-prim-0.4.0.0`, * `integer-gmp-1.0.0.0`, * `pretty-1.1.2.0`, * `primitive-0.6`, * `random-1.1`, * `repa-3.4.0.1`, * `template-haskell-2.10.0.0`, * `tf-random-0.5`, * `time-1.5.0.1`, * `transformers-0.4.2.0` and * `vector-0.10.12.3`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11126 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler