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