Berk Özkütük pushed to branch wip/ozkutuk/sprint-fun at Glasgow Haskell Compiler / GHC

Commits:

3 changed files:

Changes:

  • compiler/GHC/Runtime/Heap/Inspect.hs
    ... ... @@ -367,7 +367,7 @@ cPprTermBase y =
    367 367
       , ifTerm' (isTyCon doubleTyCon  . ty) ppr_double
    
    368 368
       , ifTerm' (isTyCon integerTyCon . ty) ppr_integer
    
    369 369
       , ifTerm' (isTyCon naturalTyCon . ty) ppr_natural
    
    370
    -  , ifFunSuspension         (isFunTy . ty) ppr_fun
    
    370
    +  , ifFunSuspension      (isFunTy . ty) ppr_fun
    
    371 371
       ]
    
    372 372
      where
    
    373 373
        ifTerm :: (Term -> Bool)
    
    ... ... @@ -386,9 +386,11 @@ cPprTermBase y =
    386 386
                        -> (Precedence -> Term -> m (Maybe SDoc))
    
    387 387
                        -> Precedence -> Term -> m (Maybe SDoc)
    
    388 388
        ifFunSuspension pred f prec t@Suspension{ctype = ctype}
    
    389
    -       | ctype `elem` fun_ctype && pred t    = f prec t
    
    389
    +       | ctype `elem` fun_ctype && pred t = f prec t
    
    390 390
          where
    
    391
    -       fun_ctype = [ FUN, FUN_1_0, FUN_0_1, FUN_2_0, FUN_1_1, FUN_0_2, FUN_STATIC ]
    
    391
    +       -- TODO(ozkutuk): PAP _seems to be_ indicate a function closure,
    
    392
    +       -- I have no idea what AP is though
    
    393
    +       fun_ctype = [ FUN, FUN_1_0, FUN_0_1, FUN_2_0, FUN_1_1, FUN_0_2, FUN_STATIC, AP, PAP ]
    
    392 394
        ifFunSuspension _ _ _ _  = return Nothing
    
    393 395
     
    
    394 396
        isFunTy :: Type -> Bool
    

  • testsuite/tests/ghci/scripts/T14828.stdout
    ... ... @@ -15,4 +15,4 @@ mappend = <_ :: forall a. Monoid a => a -> a -> a>
    15 15
     foldl' = <_ :: forall (t :: * -> *) b a.
    
    16 16
                    Foldable t =>
    
    17 17
                    (b -> a -> b) -> b -> t a -> b>
    
    18
    -f = <_ :: forall b. (forall a. a -> a) -> b -> b>
    18
    +f = (_t8::(forall a. a -> a) -> b -> b)

  • testsuite/tests/ghci/scripts/shadow-bindings.stdout
    ... ... @@ -27,7 +27,7 @@ it :: () = ()
    27 27
     Expecting T and foo with function type
    
    28 28
     type T :: *
    
    29 29
     data T = ...
    
    30
    -foo :: T -> Bool = <_ :: T -> Bool>
    
    30
    +foo :: T -> Bool = _
    
    31 31
     it :: () = ()
    
    32 32
     Expecting T and foo :: Bool
    
    33 33
     type T :: *