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

Christopher Allen cma at bitemyapp.com
Sat Feb 13 21:33:12 UTC 2016


Holes and bottoms are wildly different. Bottoms are considerably more
useful which I think you'd find if you ran down a list of examples and
tried both in each circumstance. This would force even more rewriting than
present circumstances.

>'undefined' is nasty and has to be used with care

Ya, we tell them that. We also tell them that programs intended to be
executed outside of a learning/development environment should be total (we
explain totality and partiality).

On Sat, Feb 13, 2016 at 3:08 PM, Matthew Pickering <
matthewtpickering at gmail.com> wrote:

> Maybe it would be better to introduce _ rather than using undefined
> for holes in programs. This sidesteps this issue, provides useful
> information to guide the implementation and causes an error when code
> is compiled so programs aren't unexpectedly partial.
>
> It is perhaps not idiomatic to use undefined, even in development
> these days. It is much easier (imo) to use holes and
> -fdefer-type-errors.
>
> 'undefined' is nasty and has to be used with care; CallStacks exist as
> a bit of a safety net. I've not read your book but I'm not convinced
> it should be emphasised so much in the first chapters of an elementary
> Haskell textbook.
>
> On Sat, Feb 13, 2016 at 8:52 PM, Christopher Allen <cma at bitemyapp.com>
> wrote:
> > Replying to a few here.
> >
> > Gigante:
> >
> >>Just a question: how do you manage the type of simple arithmetic
> >> expressions like 1 + 1? I mean, the type contains a constraint there.
> >> Prelude> :t 1 + 1
> >> 1 + 1 :: Num a => a
> >
> > Earlier versions of the book intentionally juked this or concreted the
> type
> > of numbers to Integer, but HaskellForMac defenestrated that with the
> > always-on type showing so now we've had an explanation along the lines
> you
> > suggest for a few months now. We know how to adapt - we've tested the
> book
> > extensively. What we need is the implementation not to expose irrelevant
> > magic/noise in ways that could leak into the first chapter with Haskell
> code
> > in it.
> >
> >
> > Seidel:
> >
> >>If your readers are using :t they must already know about simple types
> > like Integer, [], and, ->, so the new things are HasCallStack and =>.
> >
> > You'd bloody think as we're careful when we introduce :t, but we get
> tickets
> > from people using HaskellForMac[1] that get confused because they are
> shown
> > the types of expressions too early. Now we're careful in how we introduce
> > _any_ expressions.
> >
> > Fisking your attempt:
> >
> >> => is just like -> except
> >
> > They don't know what either of those things are or what they mean in the
> > second chapter because this is the _first_ chapter with any Haskell code.
> > They're just beginning to see how Haskell code might be kinda like the
> > lambdas in the lambda calculus chapter.
> >
> >> the compiler fills in the argument by
> >
> > We do explain what a compiler and interpreter are, but they won't know
> what
> > it means for it to fill in an argument. They don't know why it needs to
> fill
> > in an argument. Where did the argument come from?
> >
> >>  HasCallStack tells the compiler
> >
> > How? Why? Why do they need to care? What's a HasCallStack? Keep in mind
> they
> > don't know types, typeclasses, or anything else.
> >
> >> that the expression needs a call-stack
> >
> > Still don't know what a call, stack, or call-stack are.
> >
> >> because it might crash.
> >
> > Why does that change the type? We can construct bottoms like `let x in x`
> > that crash the program without changing the type.
> >
> >> >So HasCallStack => [Integer] is a [Integer]
> >
> > What makes this even more obnoxious is that when we finally do introduce
> > typeclasses and constraints, we talk about constraining a _type variable_
> > and now you've baked this magic in they cannot possibly be explained at
> all
> > in the book.
> >
> >> that might crash and produce a stack-trace
> >
> > First bit they might pick up from context, they don't know what a stack
> > trace is. Bonus round: when you explain things "from first principles",
> you
> > can't duck the fact that it's actually a call graph when explaining a
> > "stack" trace or call stack. Now you have to explain why/how it gets
> > flattened from one representation into the other.
> >
> >
> > Oliver had it when he said,
> >
> >>"What's a call stack?"
> >
> > They don't know what a stack, a call, or the combination thereof is. We
> had
> > planned to address these issues in the (much later) chapters that cover
> > profiling and errors. Because that's when they're relevant. This hasn't
> been
> > relevant the entire span of the book. It _never_ mattered that you didn't
> > get a stack trace from bottoms. In practice, does it suck? Sure! But
> they're
> > not practitioners yet! I am (I use Haskell for my 9-5 and have done for a
> > year and a half) and it still hasn't mattered to me. The only time I've
> > really wanted a stack trace is when this mechanism would not have been
> > available to me to begin with.
> >
> >
> > Gamari / amindfv
> >> I don't have a copy of GHC 8 atm to test this with: is an expression
> like
> >> this now illegal?
> >>
> >> x :: Int
> >> x = undefined
> >>
> >>This is still valid. The change in GHC 8.0 is merely that GHC will infer
> >>a CallStack constraint instead of solving it in-place if asked to infer
> >>a type for a let binding whose RHS demands a callstack.
> >
> > We have readers use the REPL _a lot_. Not only to load code but also
> > free-standing expressions in the REPL when experimenting and learning.
> Type
> > assignment in the REPL is noisy and we have to write around some pretty
> > gnarly width limitations (40-60 cols). This breaks the examples where
> we're
> > combining bottom and type inference to explore how terms and types
> interact.
> >
> > I am less disturbed by `HasCallStack =>` than I was by the inferred type
> of
> > ($).
> >
> >
> > I know designing around pedagogical limitations like this is tedious but
> > imagine doing it for 900-1,200 pages (formatting varies) of tutorial and
> > exercises, then getting unpleasant surprises right as the book is about
> to
> > be done.
> >
> >
> > Sorry about the messy thread all.
> >
> >
> > [1]: http://haskellformac.com/
> >
> >
> > On Sat, Feb 13, 2016 at 1:48 PM, Bryan Richter <b at chreekat.net> wrote:
> >>
> >> On Sat, Feb 13, 2016 at 09:18:07AM -0800, Eric Seidel wrote:
> >> > Here's what the GHCi session should look like.
> >> >
> >> > > $ ghci
> >> > > GHCi, version 8.0.0.20160204: http://www.haskell.org/ghc/  :? for
> help
> >> > > Loaded GHCi configuration from /home/callen/.ghci
> >> > > Prelude> let myList = [1..5 :: Integer]
> >> > > Prelude> let myList' = myList ++ undefined
> >> > > Prelude> :t myList'
> >> > > myList' :: HasCallStack => [Integer]
> >>
> >> What use case is satisfied by providing this information? How does it
> >> benefit the Haskell programmer? How do I use it?
> >>
> >> _______________________________________________
> >> 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
> >
> > _______________________________________________
> > 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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160213/7c203762/attachment.html>


More information about the Haskell-Cafe mailing list