
#14285: Entered absent arg - triggered by INLINEABLE, regression from 8.0.2 ---------------------------------+-------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by RyanGlScott): By sheer dumb luck, I managed to reduce this down to the following two files: {{{#!hs module Foo where import qualified Data.Foldable as F import qualified Data.IntMap as IM import qualified Data.IntSet as IS import Prelude hiding (null) import System.Environment data Set k = Set IS.IntSet null (Set a) = IS.null a empty = Set IS.empty sfromList :: (Enum a, Foldable c) => c a -> Set a sfromList xs = Set $ IS.fromList $ Prelude.map fromEnum $ F.toList xs newtype Map k v = Map { unMap :: (IM.IntMap v) } deriving (Eq, Ord) {-# inlineable fromList #-} fromList :: Enum k => [(k,v)] -> Map k v fromList kvs = Map $ IM.fromList $ Prelude.map (\(k,v) -> (fromEnum k, v)) kvs {-# inlineable findWithDefault #-} findWithDefault d k (Map m) = IM.findWithDefault d (fromEnum k) m data Rel a b = Rel !(Map a (Set b)) !(Map b (Set a)) {-# INLINEABLE images #-} images x (Rel f b) = findWithDefault empty x f {-# INLINEABLE pre_images #-} pre_images x rel = images x $ mirrorRel rel {-# INLINEABLE mirrorRel #-} mirrorRel :: Rel a b -> Rel b a mirrorRel (Rel f g) = Rel g f }}} {{{#!hs module Main where import Foo import Prelude hiding (null) main :: IO () main = do let args = "hw" print $ null $ pre_images 'a' (Rel (fromList [('a',sfromList args)]) (fromList [('b',sfromList ar gs)])) }}} This works on GHC 8.0.2: {{{ $ /opt/ghc/8.0.2/bin/ghc -O2 -fforce-recomp Main.hs [1 of 2] Compiling Foo ( Foo.hs, Foo.o ) [2 of 2] Compiling Main ( Main.hs, Main.o ) Linking Main ... $ ./Main True }}} But not on GHC 8.2.1: {{{ $ /opt/ghc/8.0.2/bin/ghc -O2 -fforce-recomp Main.hs [1 of 2] Compiling Foo ( Foo.hs, Foo.o ) [2 of 2] Compiling Main ( Main.hs, Main.o ) Linking Main ... $ ./Main True }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14285#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler