#4891: dataConInfoPtrToName doesn't correctly resolve constructors with a 
trailing
.
---------------------------------+------------------------------------------
    Reporter:  TristanAllwood    |       Owner:              
        Type:  bug               |      Status:  new         
    Priority:  normal            |   Component:  Compiler    
     Version:  6.12.1            |    Keywords:              
    Testcase:                    |   Blockedby:              
          Os:  Unknown/Multiple  |    Blocking:              
Architecture:  Unknown/Multiple  |     Failure:  None/Unknown
---------------------------------+------------------------------------------
 I believe the {{{parse}}} helper in {{{dataConInfoPtrToName}}} in
 {{{ghci/Linker.lhs}}} doesn't correctly parse data constructors that
 feature a trailing {{{.}}} in the name.

 Test case:

 {{{
 module X where

 data X =  Int :-> Int
        |  Int :->. Int
 }}}

 The second constructor ({{{:->.}}}) will exhibit this bug.

 Program to show the bug (in the same directory, needs ghc-paths from
 hackage):

 {{{
 {-# LANGUAGE BangPatterns #-}
 module Main where

 import ByteCodeLink
 import CoreMonad
 import Data.Array
 import DataCon
 import GHC
 import HscTypes
 import Linker
 import RtClosureInspect
 import GHC.Paths
 import TcEnv
 import Type
 import TcRnMonad
 import TcType
 import Control.Applicative
 import Name (getOccString)
 import Unsafe.Coerce
 import Control.Monad
 import Data.Maybe
 import Bag
 import PrelNames (iNTERACTIVE)
 import Outputable
 import X

 main :: IO ()
 main = runGhc (Just libdir) $ do
   dflags' <- getSessionDynFlags
   primPackages <- setSessionDynFlags dflags'
   dflags <- getSessionDynFlags
   defaultCleanupHandler dflags $ do
     target <- guessTarget "X.hs" Nothing
     setTargets [target]
     load LoadAllTargets

     () <- chaseConstructor (unsafeCoerce False)
     () <- chaseConstructor (unsafeCoerce [1,2,3])
     () <- chaseConstructor (unsafeCoerce (3 :-> 2))
     () <- chaseConstructor (unsafeCoerce (4 :->. 4))
     return ()

 chaseConstructor :: (GhcMonad m) => HValue -> m ()
 chaseConstructor !hv = do
   closure <- liftIO $ getClosureData hv
   case tipe closure  of
     Indirection _ -> chaseConstructor (ptrs closure ! 0)
     Constr -> do
       withSession $ \hscEnv -> liftIO $ initTcForLookup hscEnv $ do
         eDcname <- dataConInfoPtrToName (infoPtr closure)
         case eDcname of
           Left _       -> return ()
           Right dcName -> do
             liftIO $ putStrLn $ "Name: "      ++ showPpr dcName
             liftIO $ putStrLn $ "OccString: " ++ "'" ++ getOccString
 dcName ++ "'"
             dc <- tcLookupDataCon dcName
             liftIO $ putStrLn $ "DataCon: "   ++ showPpr dc
     _ -> return ()

 initTcForLookup :: HscEnv -> TcM a -> IO a
 initTcForLookup hsc_env = liftM (\(msg, mValue) -> fromMaybe (error . show
 . bagToList . snd $ msg) mValue) . initTc hsc_env HsSrcFile False
 iNTERACTIVE
 }}}

 Under 6.12.1, this outputs:

 {{{
 >./Main
 Name: GHC.Bool.False
 OccString: 'False'
 DataCon: GHC.Bool.False
 Name: :
 OccString: ':'
 DataCon: :
 Name: X.:->
 OccString: ':->'
 DataCon: X.:->
 Name: X.:->.
 OccString: ''
 Main: [Failed to load interface for `X.:->':
   Use -v to see a list of the files searched for.]
 }}}

 Note in the last case it's trying to load the interface for :-> (not
 :->.), and the OccString hasn't correctly been resolved.

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

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to