[GHC] #10160: GHCi :sprint has odd/unhelpful behavior for values defined within the REPL

#10160: GHCi :sprint has odd/unhelpful behavior for values defined within the REPL -------------------------------------+------------------------------------- Reporter: bitemyapp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.4 Keywords: :sprint | Operating System: Unknown/Multiple thunk evaluation | Type of failure: Incorrect result Architecture: | at runtime Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Wanted to use :sprint to help learners visualise thunk evaluation behavior in their data. Ran into some behaviors that a few people I checked with didn't have a good explanation for. I couldn't find anything in the user guide to explain this. I don't think it technically violates Haskell Report requirements, but it makes :sprint considerably less useful if you're teaching somebody non-strictness. Examples with code in the REPL: {{{ Prelude> let x = [1, 2, 3] Prelude> :sprint x x = _ Prelude> :t x x :: Num t => [t] -- this makes sense so far. Prelude> let x = [1, 2, 3 :: Integer] Prelude> :sprint x x = [1,2,3] -- errr, what? Prelude> let x = Just (1 :: Integer) Prelude> :sprint x x = Just 1 Prelude> let just = Just Prelude> let x = just (1 :: Integer) Prelude> :sprint x x = _ Prelude> let x = Just (undefined :: Integer) Prelude> :sprint x x = Just _ Prelude> let x = just (undefined :: Integer) Prelude> :sprint x x = _ Prelude> let x = [1, 2, 3 :: Integer] Prelude> let y = x Prelude> :sprint y y = [1,2,3] Prelude> let x = 1 : 2 : (3 :: Integer) : [] Prelude> :sprint x x = [1,2,3] Prelude> let x = [1] ++ [2] ++ [(3 :: Integer)] Prelude> :sprint x x = _ Prelude> let y = (:) Prelude> let x = 1 `y` (2 `y` ((3 :: Integer) `y` [])) Prelude> :sprint x x = _ Prelude> x [1,2,3] Prelude> :sprint x x = [1,2,3] }}} So the behavior here seems to be: Constructors used directly in the construction of data and are not passed functions (including polymorphic vals awaiting concrete instances)/bottoms are immediately evaluated Example, but with loading data from a file: Contents of the file: {{{ x :: Num a => [a] x = [1, 2, 3] }}} GHCi session: {{{ Prelude> :t x x :: Num a => [a] Prelude> :sprint x x = _ Prelude> x [1,2,3] Prelude> :sprint x x = _ }}} Then when x is loaded from a file, but has a different type: {{{ Prelude> :t x x :: [Integer] Prelude> :sprint x x = _ Prelude> head x 1 Prelude> :sprint x x = [1,2,3] }}} Now, this is a bit confusing. Earlier I was able to get :sprint to return [1, _, _] when I evaluated head x, but a couple hours later when I went to write this ticket, I couldn't reproduce that behavior. Is there documentation that explains: 1. Why data is shown as having been evaluated at time of declaration (seemingly) by :sprint when it's defined in the GHCi 2. Why declaring code in GHCi and loading it from a file behaves differently with :sprint (I considered let expression in the implicit GHCi do-block...couldn't find anything to explain this) 3. Why evaluating 'head x' forces the other values as well Are any of these behaviors a bug? If not, are they documented anywhere? Is the "eager" treatment of constructors in GHCi a performance thing? That seems strange given I didn't have -fobject-code turned on. :sprint not demonstrating semantics that match what I expect from a non- strict language hinders its utility as a teaching tool and means the only robust option for learners that I can find is testing evaluation with bottom values. {{{ -- So that you know i picked "7.8.4" as the version consciously [callen@atlantis ~/Work/fpbook]$ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.8.4 [callen@atlantis ~/Work/fpbook]$ ghci --version The Glorious Glasgow Haskell Compilation System, version 7.8.4 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10160 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10160: GHCi :sprint has odd/unhelpful behavior for values defined within the REPL -------------------------------------+------------------------------------- Reporter: bitemyapp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.4 Resolution: | Keywords: :sprint Operating System: Unknown/Multiple | thunk evaluation non-strictness Type of failure: Incorrect result | laziness runtime ghci repl at runtime | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bitemyapp): * keywords: :sprint thunk evaluation => :sprint thunk evaluation non- strictness laziness runtime ghci repl -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10160#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10160: GHCi :sprint has odd/unhelpful behavior for values defined within the REPL -------------------------------------+------------------------------------- Reporter: bitemyapp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.4 Resolution: | Keywords: :sprint Operating System: Unknown/Multiple | thunk evaluation non-strictness Type of failure: Incorrect result | laziness runtime ghci repl at runtime | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by bitemyapp: Old description:
Wanted to use :sprint to help learners visualise thunk evaluation behavior in their data. Ran into some behaviors that a few people I checked with didn't have a good explanation for. I couldn't find anything in the user guide to explain this. I don't think it technically violates Haskell Report requirements, but it makes :sprint considerably less useful if you're teaching somebody non-strictness.
Examples with code in the REPL:
{{{ Prelude> let x = [1, 2, 3] Prelude> :sprint x x = _ Prelude> :t x x :: Num t => [t] -- this makes sense so far.
Prelude> let x = [1, 2, 3 :: Integer] Prelude> :sprint x x = [1,2,3] -- errr, what?
Prelude> let x = Just (1 :: Integer) Prelude> :sprint x x = Just 1
Prelude> let just = Just Prelude> let x = just (1 :: Integer) Prelude> :sprint x x = _
Prelude> let x = Just (undefined :: Integer) Prelude> :sprint x x = Just _
Prelude> let x = just (undefined :: Integer) Prelude> :sprint x x = _
Prelude> let x = [1, 2, 3 :: Integer] Prelude> let y = x Prelude> :sprint y y = [1,2,3]
Prelude> let x = 1 : 2 : (3 :: Integer) : [] Prelude> :sprint x x = [1,2,3] Prelude> let x = [1] ++ [2] ++ [(3 :: Integer)] Prelude> :sprint x x = _
Prelude> let y = (:) Prelude> let x = 1 `y` (2 `y` ((3 :: Integer) `y` [])) Prelude> :sprint x x = _ Prelude> x [1,2,3] Prelude> :sprint x x = [1,2,3] }}}
So the behavior here seems to be:
Constructors used directly in the construction of data and are not passed functions (including polymorphic vals awaiting concrete instances)/bottoms are immediately evaluated
Example, but with loading data from a file:
Contents of the file:
{{{ x :: Num a => [a] x = [1, 2, 3] }}}
GHCi session:
{{{ Prelude> :t x x :: Num a => [a]
Prelude> :sprint x x = _
Prelude> x [1,2,3]
Prelude> :sprint x x = _ }}}
Then when x is loaded from a file, but has a different type:
{{{ Prelude> :t x x :: [Integer] Prelude> :sprint x x = _ Prelude> head x 1 Prelude> :sprint x x = [1,2,3] }}}
Now, this is a bit confusing. Earlier I was able to get :sprint to return [1, _, _] when I evaluated head x, but a couple hours later when I went to write this ticket, I couldn't reproduce that behavior.
Is there documentation that explains:
1. Why data is shown as having been evaluated at time of declaration (seemingly) by :sprint when it's defined in the GHCi
2. Why declaring code in GHCi and loading it from a file behaves differently with :sprint (I considered let expression in the implicit GHCi do-block...couldn't find anything to explain this)
3. Why evaluating 'head x' forces the other values as well
Are any of these behaviors a bug? If not, are they documented anywhere? Is the "eager" treatment of constructors in GHCi a performance thing? That seems strange given I didn't have -fobject-code turned on.
:sprint not demonstrating semantics that match what I expect from a non- strict language hinders its utility as a teaching tool and means the only robust option for learners that I can find is testing evaluation with bottom values.
{{{ -- So that you know i picked "7.8.4" as the version consciously
[callen@atlantis ~/Work/fpbook]$ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.8.4
[callen@atlantis ~/Work/fpbook]$ ghci --version The Glorious Glasgow Haskell Compilation System, version 7.8.4 }}}
New description: Wanted to use :sprint to help learners visualise thunk evaluation behavior in their data. Ran into some behaviors that a few people I checked with didn't have a good explanation for. I couldn't find anything in the user guide to explain this. I don't think it technically violates Haskell Report requirements, but it makes :sprint considerably less useful if you're teaching somebody non-strictness. Examples with code in the REPL: {{{ Prelude> let x = [1, 2, 3 :: Integer] Prelude> :sprint x x = [1,2,3] -- errr, what? Prelude> let x = Just (1 :: Integer) Prelude> :sprint x x = Just 1 Prelude> let just = Just Prelude> let x = just (1 :: Integer) Prelude> :sprint x x = _ Prelude> let x = Just (undefined :: Integer) Prelude> :sprint x x = Just _ Prelude> let x = just (undefined :: Integer) Prelude> :sprint x x = _ Prelude> let x = [1, 2, 3 :: Integer] Prelude> let y = x Prelude> :sprint y y = [1,2,3] Prelude> let x = 1 : 2 : (3 :: Integer) : [] Prelude> :sprint x x = [1,2,3] Prelude> let x = [1] ++ [2] ++ [(3 :: Integer)] Prelude> :sprint x x = _ Prelude> let y = (:) Prelude> let x = 1 `y` (2 `y` ((3 :: Integer) `y` [])) Prelude> :sprint x x = _ Prelude> x [1,2,3] Prelude> :sprint x x = [1,2,3] }}} So the behavior here seems to be: Constructors used directly in the construction of data and are not passed functions (including polymorphic vals awaiting concrete instances)/bottoms are immediately evaluated Example, but with loading data from a file: Contents of the file: {{{ x :: Num a => [a] x = [1, 2, 3] }}} GHCi session: {{{ Prelude> :t x x :: Num a => [a] Prelude> :sprint x x = _ Prelude> x [1,2,3] Prelude> :sprint x x = _ }}} Then when x is loaded from a file, but has a different type: {{{ Prelude> :t x x :: [Integer] Prelude> :sprint x x = _ Prelude> head x 1 Prelude> :sprint x x = [1,2,3] }}} Now, this is a bit confusing. Earlier I was able to get :sprint to return [1, _, _] when I evaluated head x, but a couple hours later when I went to write this ticket, I couldn't reproduce that behavior. Is there documentation that explains: 1. Why data is shown as having been evaluated at time of declaration (seemingly) by :sprint when it's defined in the GHCi 2. Why declaring code in GHCi and loading it from a file behaves differently with :sprint (I considered let expression in the implicit GHCi do-block...couldn't find anything to explain this) 3. Why evaluating 'head x' forces the other values as well Are any of these behaviors a bug? If not, are they documented anywhere? Is the "eager" treatment of constructors in GHCi a performance thing? That seems strange given I didn't have -fobject-code turned on. :sprint not demonstrating semantics that match what I expect from a non- strict language hinders its utility as a teaching tool and means the only robust option for learners that I can find is testing evaluation with bottom values. {{{ -- So that you know i picked "7.8.4" as the version consciously [callen@atlantis ~/Work/fpbook]$ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.8.4 [callen@atlantis ~/Work/fpbook]$ ghci --version The Glorious Glasgow Haskell Compilation System, version 7.8.4 }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10160#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10160: GHCi :sprint has odd/unhelpful behavior for values defined within the REPL -------------------------------------+------------------------------------- Reporter: bitemyapp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.4 Resolution: | Keywords: :sprint Operating System: Unknown/Multiple | thunk evaluation non-strictness Type of failure: Incorrect result | laziness runtime ghci repl at runtime | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by bitemyapp: Old description:
Wanted to use :sprint to help learners visualise thunk evaluation behavior in their data. Ran into some behaviors that a few people I checked with didn't have a good explanation for. I couldn't find anything in the user guide to explain this. I don't think it technically violates Haskell Report requirements, but it makes :sprint considerably less useful if you're teaching somebody non-strictness.
Examples with code in the REPL:
{{{ Prelude> let x = [1, 2, 3 :: Integer] Prelude> :sprint x x = [1,2,3] -- errr, what?
Prelude> let x = Just (1 :: Integer) Prelude> :sprint x x = Just 1
Prelude> let just = Just Prelude> let x = just (1 :: Integer) Prelude> :sprint x x = _
Prelude> let x = Just (undefined :: Integer) Prelude> :sprint x x = Just _
Prelude> let x = just (undefined :: Integer) Prelude> :sprint x x = _
Prelude> let x = [1, 2, 3 :: Integer] Prelude> let y = x Prelude> :sprint y y = [1,2,3]
Prelude> let x = 1 : 2 : (3 :: Integer) : [] Prelude> :sprint x x = [1,2,3] Prelude> let x = [1] ++ [2] ++ [(3 :: Integer)] Prelude> :sprint x x = _
Prelude> let y = (:) Prelude> let x = 1 `y` (2 `y` ((3 :: Integer) `y` [])) Prelude> :sprint x x = _ Prelude> x [1,2,3] Prelude> :sprint x x = [1,2,3] }}}
So the behavior here seems to be:
Constructors used directly in the construction of data and are not passed functions (including polymorphic vals awaiting concrete instances)/bottoms are immediately evaluated
Example, but with loading data from a file:
Contents of the file:
{{{ x :: Num a => [a] x = [1, 2, 3] }}}
GHCi session:
{{{ Prelude> :t x x :: Num a => [a]
Prelude> :sprint x x = _
Prelude> x [1,2,3]
Prelude> :sprint x x = _ }}}
Then when x is loaded from a file, but has a different type:
{{{ Prelude> :t x x :: [Integer] Prelude> :sprint x x = _ Prelude> head x 1 Prelude> :sprint x x = [1,2,3] }}}
Now, this is a bit confusing. Earlier I was able to get :sprint to return [1, _, _] when I evaluated head x, but a couple hours later when I went to write this ticket, I couldn't reproduce that behavior.
Is there documentation that explains:
1. Why data is shown as having been evaluated at time of declaration (seemingly) by :sprint when it's defined in the GHCi
2. Why declaring code in GHCi and loading it from a file behaves differently with :sprint (I considered let expression in the implicit GHCi do-block...couldn't find anything to explain this)
3. Why evaluating 'head x' forces the other values as well
Are any of these behaviors a bug? If not, are they documented anywhere? Is the "eager" treatment of constructors in GHCi a performance thing? That seems strange given I didn't have -fobject-code turned on.
:sprint not demonstrating semantics that match what I expect from a non- strict language hinders its utility as a teaching tool and means the only robust option for learners that I can find is testing evaluation with bottom values.
{{{ -- So that you know i picked "7.8.4" as the version consciously
[callen@atlantis ~/Work/fpbook]$ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.8.4
[callen@atlantis ~/Work/fpbook]$ ghci --version The Glorious Glasgow Haskell Compilation System, version 7.8.4 }}}
New description: Wanted to use :sprint to help learners visualise thunk evaluation behavior in their data. Ran into some behaviors that a few people I checked with didn't have a good explanation for. I couldn't find anything in the user guide to explain this. I don't think it technically violates Haskell Report requirements, but it makes :sprint considerably less useful if you're teaching somebody non-strictness. Examples with code in the REPL: {{{ Prelude> let x = [1, 2, 3 :: Integer] Prelude> :sprint x x = [1,2,3] -- errr, what? Prelude> let x = Just (1 :: Integer) Prelude> :sprint x x = Just 1 Prelude> let just = Just Prelude> let x = just (1 :: Integer) Prelude> :sprint x x = _ Prelude> let x = Just (undefined :: Integer) Prelude> :sprint x x = Just _ Prelude> let x = just (undefined :: Integer) Prelude> :sprint x x = _ Prelude> let x = [1, 2, 3 :: Integer] Prelude> let y = x Prelude> :sprint y y = [1,2,3] Prelude> let x = 1 : 2 : (3 :: Integer) : [] Prelude> :sprint x x = [1,2,3] Prelude> let x = [1] ++ [2] ++ [(3 :: Integer)] Prelude> :sprint x x = _ Prelude> let y = (:) Prelude> let x = 1 `y` (2 `y` ((3 :: Integer) `y` [])) Prelude> :sprint x x = _ Prelude> x [1,2,3] Prelude> :sprint x x = [1,2,3] }}} So the behavior here seems to be: Constructors used directly in the construction of data and are not passed functions (including polymorphic vals awaiting concrete instances)/bottoms are immediately evaluated Example, but with loading data from a file: Contents of the file: {{{ x :: Num a => [a] x = [1, 2, 3] }}} GHCi session: {{{ Prelude> :t x x :: Num a => [a] Prelude> :sprint x x = _ Prelude> x [1,2,3] Prelude> :sprint x x = _ -- ^^ this is expected }}} Then when x is loaded from a file, but has a different type: {{{ Prelude> :t x x :: [Integer] Prelude> :sprint x x = _ Prelude> head x 1 Prelude> :sprint x x = [1,2,3] -- ^^ this is not }}} Now, this is a bit confusing. Earlier I was able to get :sprint to return [1, _, _] when I evaluated head x, but a couple hours later when I went to write this ticket, I couldn't reproduce that behavior. Is there documentation that explains: 1. Why data is shown as having been evaluated at time of declaration (seemingly) by :sprint when it's defined in the GHCi 2. Why declaring code in GHCi and loading it from a file behaves differently with :sprint (I considered let expression in the implicit GHCi do-block...couldn't find anything to explain this) 3. Why evaluating 'head x' forces the other values as well Are any of these behaviors a bug? If not, are they documented anywhere? Is the "eager" treatment of constructors in GHCi a performance thing? That seems strange given I didn't have -fobject-code turned on. :sprint not demonstrating semantics that match what I expect from a non- strict language hinders its utility as a teaching tool and means the only robust option for learners that I can find is testing evaluation with bottom values. {{{ -- So that you know i picked "7.8.4" as the version consciously [callen@atlantis ~/Work/fpbook]$ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.8.4 [callen@atlantis ~/Work/fpbook]$ ghci --version The Glorious Glasgow Haskell Compilation System, version 7.8.4 }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10160#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10160: GHCi :sprint has odd/unhelpful behavior for values defined within the REPL -------------------------------------+------------------------------------- Reporter: bitemyapp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.4 Resolution: | Keywords: :sprint Operating System: Unknown/Multiple | thunk evaluation non-strictness Type of failure: Incorrect result | laziness runtime ghci repl at runtime | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Well to start with, none of this is really "behavior of `:sprint`": it's the behavior of ghci when interpreting expressions, and the details of this behavior are exposed by `:sprint`. Specifically, constructors are always fully applied in Core, so when ghci encounters a constructor application, it can (emit code to) directly produce a heap object representing an evaluated constructor, rather than producing whatever sort of heap object represents the application of an unknown function and leaving it to be reduced to WHNF later. I imagine that similar comments would apply to the case of integer literals at type `Integer`, where ghci should just build the required `Integer` literal directly rather than building a thunk for an application of `fromInteger` (whose argument would be exactly the necessary `Integer` literal anyways). Yes, this is done for performance reasons, but it's a more basic sort of thing than GHC's optimization passes. It would be quite poor for ghci not to work this way. I think this answers your question 1. As for 2 and 3, I don't know about the details of loading code from a file. It could be that in your example `x` is initially bound in ghci to something along the lines of `loadSymbol "Main.x"`, though I am just speculating based on your experiments. You might consider using an enumeration `let x = [1..3 :: Integer]`, which would behave a bit more like you expect, though forcing elements of that list will also cause earlier elements to be evaluated. I'm sure you can cook up a workaround for that if necessary. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10160#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10160: GHCi :sprint has odd/unhelpful behavior for values defined within the REPL -------------------------------------+------------------------------------- Reporter: bitemyapp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.4 Resolution: | Keywords: :sprint Operating System: Unknown/Multiple | thunk evaluation non-strictness Type of failure: Incorrect result | laziness runtime ghci repl at runtime | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bitemyapp): Yeah Carter had pointed me to the enumFromTo example which has behavior more like what I would expect. The optimization being performed makes sense, the inconsistencies do not. This would appear to mean I am limited to _|_ for reliably demonstrating what values as a general class will or won't get evaluated. Is there something more visual that wouldn't surprise beginners too much? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10160#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10160: GHCi :sprint has odd/unhelpful behavior for values defined within the REPL -------------------------------------+------------------------------------- Reporter: bitemyapp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.4 Resolution: | Keywords: :sprint Operating System: Unknown/Multiple | thunk evaluation non-strictness Type of failure: Incorrect result | laziness runtime ghci repl at runtime | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): How about adding a sentence like this to the documentation of `:print`:
Note that literals and data constructor applications may appear as values rather than thunks even if nothing has yet forced their evaluation, since GHCi constructs these values directly in weak head normal form.
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10160#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC