[Haskell-cafe] New type of expressions containing (error ...) includes noisy implicit parameter

Eric Seidel eric at seidel.io
Sun Feb 14 06:22:47 UTC 2016


I've put together a patch to prevent GHC from inferring CallStacks for
*top-level* expressions. Given that we've hidden the implicit parameter
behind a type synonym (and may remove it entirely in the future), I'm
less concerned about preserving the expected behavior for implicit
parameters.

I believe this should address most of your concerns wrt ghci
interactions.

ghci> let myList = [1, 2, 3 :: Integer]
myList :: [Integer]
ghci> let myList' = myList ++ undefined
myList' :: [Integer]
ghci> :t myList
myList :: [Integer]
ghci> :t myList'
myList' :: [Integer]
ghci> :sprint myList'
myList' = _
ghci> head myList'
1
it :: Integer
ghci> :sprint myList'
myList' = 1 : _

Note that undefined still takes a CallStack, and thus has a more
involved type.

ghci> :t undefined
undefined
  :: forall (v :: GHC.Types.Levity) (a :: TYPE v).
     GHC.Stack.Types.HasCallStack =>
     a

But uses of undefined will no longer infect the top-level context with
CallStacks, you'll have to request them explicitly. (We need the
inference for local binders, so HaskellForMac and ghc-mod could still
show CallStacks in tooltips).

The patch is awaiting review at https://phabricator.haskell.org/D1912,
you're more than welcome to comment.

Eric

On Sat, Feb 13, 2016, at 16:49, Christopher Allen wrote:
> > What I'd suggest instead is to define your own undefined in a
> > Prelude-replacement (or simplification if you will).
> 
> No. Part of the reason for the book is so that people can learn in the
> environment that they'll use and be equipped to apply what they've
> learned
> with minimal surprises. This solution is worse than the others suggested
> so
> far. And _again_, it's not just about our book it's about learning
> resources more generally and what that experience is like for new people.
> 
> Rust doesn't need to have a beginner's Prelude. Idris doesn't either. In
> fact, most languages don't and the only one that has pulled it off
> convincingly is Racket which had less cause to do so than GHC does at
> this
> juncture.
> 
> On Sat, Feb 13, 2016 at 6:02 PM, Eric Seidel <eric at seidel.io> wrote:
> 
> >
> > On Sat, Feb 13, 2016, at 15:32, Christopher Allen wrote:
> > > There's another problem I discovered with HasCallStack. The implicit
> > > parameter constraint breaks sharing behavior for examples that use
> > > bottom.
> >
> > This is a necessary consequence of the implementation of callstack-aware
> > functions as overloaded functions. It's really no different from using a
> > type-class, and is in my opinion the correct behavior.
> >
> > It seems what you really want is a way to prevent GHC from inferring the
> > HasCallStack constraint in the first place. That's doable with an
> > explicit type signature (or even a combinator to wrap the expression),
> > but this isn't a great solution for your book.
> >
> > What I'd suggest instead is to define your own undefined in a
> > Prelude-replacement (or simplification if you will). Something like
> >
> > undefined :: a
> > undefined = withFrozenCallStack emptyCallStack Prelude.undefined
> >
> > should work to remove all traces of CallStacks (including when it blows
> > up). error can be similarly wrapped to avoid having to deal with
> > CallStacks, and $ and the FTP-related functions can be specialized to
> > less-polymorphic versions that are easier to explain to beginners (at
> > least until they're ready to be exposed to the real versions).
> >
> > I'm sorry that this change has caused you trouble.
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> >
> 
> 
> 
> -- 
> Chris Allen
> Currently working on http://haskellbook.com


More information about the Haskell-Cafe mailing list