[Haskell-cafe] Bad interaction of inlinePerformIO and mutable vectors

Michael Snoyman michael at snoyman.com
Thu Jul 31 14:51:36 UTC 2014


Thanks for digging into this Felipe! That's certainly an interesting
result, though I similarly have no idea why that's what the simplifier is
doing.


On Thu, Jul 31, 2014 at 5:27 PM, Felipe Lessa <felipe.lessa at gmail.com>
wrote:

> Checking a bit deeper using:
>
>   $ ghc-core --no-cast --no-asm snoyberg.hs -O1 -ddump-simpl \
>              -dverbose-core2core -dcore-lint
>
> This is the last time we see the "inlinePerformIO" function call (before
> it being optimized away):
>
> lvl_s2R1 =
>   \ (vm_a2gL [OS=ProbOneShot]
>        :: Data.Vector.Mutable.MVector
>             RealWorld Char) ->
>     thenIO
>       @ ()
>       @ ()
>       lvl_s2QY
>       (let {
>          a_s2QN
>            :: State# RealWorld
>               -> (# State# RealWorld, () #)
>
>          a_s2QN =
>            \ (eta_Xm [OS=OneShot] :: State# RealWorld) ->
>              ((bindIO
>                  @ (Data.Vector.Vector Char)
>                  @ ()
>                  (Data.Vector.unsafeFreeze
>                     @ IO
>                     @ Char
>                     Control.Monad.Primitive.$fPrimMonadIO
>                     (vm_a2gL `cast` ...))
>                  lvl_s2QV)
>               `cast` ...)
>                eta_Xm } in
>        thenIO
>          @ ()
>          @ ()
>          (a_s2QN `cast` ...)
>          (case $
>                  @ (IO ())
>                  @ ()
>                  (Data.ByteString.Internal.inlinePerformIO @ ())
>                  (Data.Vector.Mutable.write
>                     @ IO
>                     @ Char
>                     Control.Monad.Primitive.$fPrimMonadIO
>                     (vm_a2gL `cast` ...)
>                     lvl_s2QZ
>                     lvl_s2R0)
>           of _ [Occ=Dead] { () ->
>           a_s2QN `cast` ...
>           }))
>
> lvl_s2QV is the action that prints the array contents.  The above
> snippet prints the contents, writes the new value then prints the
> contents again.
>
> But then comes a simplifier phase which lead us to:
>
>     ...
>     of _ [Occ=Dead] { (# ipv_X3cp [OS=OneShot], ipv1_X3cr #) ->
>     let {
>       a_s2QN
>         :: State# RealWorld
>            -> (# State# RealWorld, () #)
>       [LclId,
>        Arity=1,
>
>        Unf=Unf{Src=<vanilla>, TopLvl=False, Arity=1, Value=True,
>                ConLike=True, WorkFree=True, Expandable=True,
>                Guidance=IF_ARGS [0] 91 0}]
>       a_s2QN =
>         \ (eta_Xm [OS=OneShot] :: State# RealWorld) ->
>           case unsafeFreezeArray#
>                  @ (Control.Monad.Primitive.PrimState IO)
>                  @ Char
>                  ipv1_a2NI
>                  (eta_Xm `cast` ...)
>           of _ [Occ=Dead] { (# ipv_a2Oy [OS=OneShot], ipv1_a2Oz #) ->
>           Handle.Text.hPutStr2
>             Handle.FD.stdout
>             (Data.Vector.$fShowVector_$cshow
>                @ Char
>                $fShowChar
>                (Data.Vector.Vector @ Char 0 1 ipv1_a2Oz))
>             True
>             (ipv_a2Oy `cast` ...)
>           } } in
>     case a_s2QN ipv_X3cp
>     of _ [Occ=Dead] { (# ipv_X3cv [OS=OneShot], ipv1_X3dt #) ->
>     a_s2QN ipv_X3cv
>     ...
>
> Note that a_s2QN has changed due to inlining but still performs the same
> action.  However!  ipv_X3cp is *not* the same as the big case with our
> inlinePerformIO, it's merely the resulting RealWorld from printing
> "inlinePerformIO"!  This is the spot.
>
> Now I'm stuck, though.  I have no idea why the simplifier did this.
>
> Cheers!
>
> --
> Felipe.
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140731/3e60e12f/attachment.html>


More information about the Haskell-Cafe mailing list