Does the Strict extension make monadic bindings strict?

Ömer Sinan Ağacan omeragacan at gmail.com
Tue Dec 8 17:35:03 UTC 2015


I think this is a problem/bug in the implementation. In the "function
definitions" section of the wiki page it says the argument will have a
bang pattern. But then this code:

    do x <- ...
       return (x + 1)

which is just a syntactic sugar for `... >>= \x -> return (x + 1)`
doesn't have the bang pattern in `x`.

(See also a related email I sent to ghc-devs yesterday:
https://mail.haskell.org/pipermail/ghc-devs/2015-December/010699.html)

2015-12-08 12:27 GMT-05:00 David Kraeutmann <kane at kane.cx>:
> While there's a fundamental difference between (>>=) and let-bindings, it
> might be worth adding to the docs that -XStrict only makes let bindings
> strict.
>
>
> On 12/08/2015 06:22 PM, Rob Stewart wrote:
>
> Are the following two programs equivalent with respect to the strictness
> of `readFile`?
>
> --8<---------------cut here---------------start------------->8---
> {-# LANGUAGE BangPatterns #-}
>
> module Main where
>
> main = do
>   !contents <- readFile "foo.txt"
>   print contents
> --8<---------------cut here---------------end--------------->8---
>
> And:
>
> --8<---------------cut here---------------start------------->8---
> {-# LANGAUGE Strict #-}
>
> module Main where
>
> main = do
>   contents <- readFile "foo.txt"
>   print contents
> --8<---------------cut here---------------end--------------->8---
>
> The documentation on "Strict-by-default pattern bindings" gives
> let/where binding as an example, but there is not a monadic bind example.
> http://downloads.haskell.org/~ghc/master/users-guide/glasgow_exts.html#strict-by-default-pattern-bindings
>
> Inspecting GHC Core for these two programs suggests that
>
> !contents <- readFile "foo.txt"
>
> is not equivalent to (with Strict enabled):
>
> contents <- readFile "foo.txt"
>
> Here's core using BangPatterns:
>
> (readFile (unpackCString# "foo.txt"#))
> (\ (contents_asg :: String) ->
>    case contents_asg of contents1_Xsk { __DEFAULT ->
>    print @ String $dShow_rYy contents1_Xsk
>    })
>
> Here's core using Strict:
>
> (readFile (unpackCString# "foo.txt"#))
> (\ (contents_asg :: String) ->
>    print @ String $dShow_rYv contents_asg)
>
> Does this core align with the design of the Strict extension?
>
> If it does, are users going to understand that using Strict is going to
> make let/where bindings strict, but is not going to make <- or >>=
> bindings strict?
>
> --
> Rob Stewart
>
>
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
>
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>


More information about the ghc-devs mailing list