Does the Strict extension make monadic bindings strict?

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#stric... 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

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#stric... http://downloads.haskell.org/%7Eghc/master/users-guide/glasgow_exts.html#str...
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

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
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#stric...
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

I believe this is just a bug, since the desugaring ought to be strict in
the \x.
On Tue, Dec 8, 2015 at 6:35 PM, Ömer Sinan Ağacan
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
: 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#stric...
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

I agree that this seems to be a bug. I have a lot to do currently, but might be able to look at it sometime during next week. Adam Sandberg Eriksson On Thu, 10 Dec 2015, at 03:34 PM, Johan Tibell wrote:
I believe this is just a bug, since the desugaring ought to be strict in the \x.
On Tue, Dec 8, 2015 at 6:35 PM, Ömer Sinan Ağacan
wrote: 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
: 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#stric...
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@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org
ghc-devs mailing list
ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

In which case, I've created a ticket to record this bug and to track its fix: https://ghc.haskell.org/trac/ghc/ticket/11193 On 10 December 2015 at 15:26, Adam Sandberg Eriksson < adam@sandbergericsson.se> wrote:
I agree that this seems to be a bug. I have a lot to do currently, but might be able to look at it sometime during next week.
Adam Sandberg Eriksson
On Thu, 10 Dec 2015, at 03:34 PM, Johan Tibell wrote:
I believe this is just a bug, since the desugaring ought to be strict in the \x.
On Tue, Dec 8, 2015 at 6:35 PM, Ömer Sinan Ağacan
wrote: 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
: 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#stric...
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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
*_______________________________________________* ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
participants (5)
-
Adam Sandberg Eriksson
-
David Kraeutmann
-
Johan Tibell
-
Rob Stewart
-
Ömer Sinan Ağacan