[Haskell-cafe] ($) not as transparent as it seems

Don Stewart dons at galois.com
Thu Feb 3 22:58:50 CET 2011


catamorphism:
> On Thu, Feb 3, 2011 at 12:44 PM, Steffen Schuldenzucker
> <sschuldenzucker at uni-bonn.de> wrote:
> >
> > Dear cafe,
> >
> > does anyone have an explanation for this?:
> >
> >>>> error (error "foo")
> > *** Exception: foo
> >
> >>>> error $ error "foo"
> > *** Exception: *** Exception: foo
> >
> 
> Have you read the intermediate Core (using -ddump-simpl) for each variation?
> 

A.
GHC.Base.bindIO
  @ GHC.Prim.Any
  @ [()]
  ((GHC.Err.error @ [GHC.Types.Char] (GHC.Base.unpackCString# "foo"))
   `cast` (CoUnsafe [GHC.Types.Char] (GHC.Types.IO GHC.Prim.Any)
           :: [GHC.Types.Char] ~ GHC.Types.IO GHC.Prim.Any))
  ((\ (it_ade :: GHC.Prim.Any)
      (eta_B1 :: GHC.Prim.State# GHC.Prim.RealWorld) ->
      ((GHC.Base.returnIO
          @ [()]
          (GHC.Types.:
             @ ()
             (it_ade `cast` (CoUnsafe GHC.Prim.Any () :: GHC.Prim.Any ~ ()))
             (GHC.Types.[] @ ())))
       `cast` (GHC.Types.NTCo:IO [()]
               :: GHC.Types.IO [()]
                    ~
                  (GHC.Prim.State# GHC.Prim.RealWorld
                   -> (# GHC.Prim.State# GHC.Prim.RealWorld, [()] #))))
        eta_B1)
   `cast` (GHC.Prim.Any -> sym (GHC.Types.NTCo:IO [()])
           :: (GHC.Prim.Any
               -> GHC.Prim.State# GHC.Prim.RealWorld
               -> (# GHC.Prim.State# GHC.Prim.RealWorld, [()] #))
                ~
              (GHC.Prim.Any -> GHC.Types.IO [()])))

B.
GHC.Base.bindIO
  @ GHC.Prim.Any
  @ [()]
  (GHC.Base.$
     @ [GHC.Types.Char]
     @ (GHC.Types.IO GHC.Prim.Any)
     (GHC.Err.error @ (GHC.Types.IO GHC.Prim.Any))
     (GHC.Err.error @ [GHC.Types.Char] (GHC.Base.unpackCString# "foo")))
  ((\ (it_aib :: GHC.Prim.Any)
      (eta_B1 :: GHC.Prim.State# GHC.Prim.RealWorld) ->
      ((GHC.Base.returnIO
          @ [()]
          (GHC.Types.:
             @ ()
             (it_aib `cast` (CoUnsafe GHC.Prim.Any () :: GHC.Prim.Any ~ ()))
             (GHC.Types.[] @ ())))
       `cast` (GHC.Types.NTCo:IO [()]
               :: GHC.Types.IO [()]
                    ~
                  (GHC.Prim.State# GHC.Prim.RealWorld
                   -> (# GHC.Prim.State# GHC.Prim.RealWorld, [()] #))))
        eta_B1)
   `cast` (GHC.Prim.Any -> sym (GHC.Types.NTCo:IO [()])
           :: (GHC.Prim.Any
               -> GHC.Prim.State# GHC.Prim.RealWorld
               -> (# GHC.Prim.State# GHC.Prim.RealWorld, [()] #))
                ~
              (GHC.Prim.Any -> GHC.Types.IO [()])))




More information about the Haskell-Cafe mailing list