Deepseq versus "make invalid laziness unrepresentable"

How would you emulate the short-circuiting behaviour of Haskell’s (&&)/Python’s and in a strict language?

I guess what you wanted to ask was “how to emulate short circuiting in user defined functions/operators/…”?

1 Like

Yes indeed.


I’m not sure what this means. Do you mean:

A = some value output of a function
B = some value output of another function
if A and B:
    print ("ok")

If A is false then B should never be evaluated?

If so then the simple solution is :

A = some value output of a function
B = lambda: some output of another function
if A and B():
    print ("ok")

In that example, the stuff in B does not get executed.

1 Like

I see. So we simulate laziness in a strict language by wrapping things in lambda. And what if we want to do

if f(A) and g(A): ...

where we not only want to avoid calculating g(A) if f(A) is False, but we also want to avoid recalculating A if f(A) is True?

You mean this?

from functools import cache

A = cache(lambda: some value output of a function)
B = lambda: some output of another function

if A() and B():
    print ("ok")

Sure, something like that! So at this point, for me personally, emulating laziness in a strict language doesn’t look any easier. You may have different preferences, of course.

One of the big differences is that in a strict language it is the responsibility of the caller to arrange for things to be evaluated appropriately. In a lazy language it is possible to delegate that responsibility to the callee. It can be very nice to write (&&) and just have it work properly.

So here’s a closure-free form of non-strict semantics:

(…it just needs someone to work out how to implement it ;-)

You’ve inspired me to explore this a bit. I’m going to quickly smash out AoC2021 in functional-style Python here just to see what I end up with.

1 Like

Idris is an eagerly-evaluated language, but it has a Lazy “type former/constructor” that tells the compiler to delay the evaluation of its argument. This lets the programmer be explicit in what values ought to be treated as delayed computations.

I’ve yet to read much in the way of practical uses of Idris code, but I imagine this would be a good place to start looking for performance comparisons of e.g. strict vs lazy container types.

1 Like

While a Lazy “type former/constructor” makes it easier to use, the only construct a programming language requires to support laziness is the conditional:

Having seen that Pascal version alone, it shouldn’t then be much of a surprise that one particularly-annoyed computer scientist called for an alternative paradigm:

But liberty has its price: for certain tasks, the laziness of languages like Miranda or Haskell means that they may sometimes be slower in comparison to some old imperative language (one that still doesn’t have any modern support for modules). But that’s no great surprise either:

The epitome of the mismatch between non-strict semantics and imperative hardware must surely be the veritable “cottage industry” that has formed to (somewhat) ameliorate the difficulties in dealing with that most basic construct of laziness - the conditional: pipeline stalls and flushes, branch (mis)prediction, et al!

Garbage in, garbage out - performance comparisons between Haskell and an imperative bug-prone language running on imperative bug-laden hardware are irrelevant.

i actually agree but until we make a new architecture and then implement it the only comparison that makes sense is how fast haskell is compared to X language in bug laden hardware. i actually would like to work to help here i just don’t know where to start?

I’m learning Scala at the moment for work. It seems like a less elegant Haskell on first contact, but it is very quick to learn and has a lot going for it: strict evaluation, but it has some opt-ins for “laziness”, and OO functional programming is quite nice. You can also just mix mutable stuff seamlessly. Immutable variable? Use val … Mutable variable? Use var … The Scala 3 book is exactly what I’d want from a Haskell noob guide: enough of a bootstrap to get going, and nothing more.

Finally, I’ve a terseness fetish and in Scala you can compress single argument anonymous function from (x => x + 2) to just (_ + 2) , we should totally steal that …

What’s wrong with sectioning a la (+2)?

5 Likes

But all a strict language really needs are if...then...else conditionals to emulate laziness.


If by “seamlessly” you mean “able to sneak in an effect anywhere in the program” - there’s a reason why the name chosen for things of pseudo-type IO T -> T often start with the prefix unsafe (hint: parallelism ;-)

You may – and I very frequently do – need the variable to feature in many places in an anonymous function: E.g. _^2 + _*2 + 5 or h(f(_), g(_,3))

Similarly, I think comprehensions in Scala make more sense in complex cases. They are basically an arbitrary for loop supporting multiple generators with a yield statement. Reads like normal code. From here:

def foo(n: Int, v: Int) =
   for i <- 0 until n
       j <- 0 until n if i + j == v
   yield (i, j)

 // prints (1, 9) (2, 8) (3, 7) (4, 6) (5, 5) (6, 4) (7, 3) (8, 2) (9, 1)
foo(10, 10).foreach {
  (i, j) => println(s"($i, $j) ")
}
2 Likes

Note that in Scala, each _ is a new parameter; those expressions would not reuse a single parameter in multiple places.

4 Likes

Ah thanks, I didn’t know that, my mistake. I guess its still valid for different reasons: 1. Placement of the variable (i.e. if its anywhere other than the beginning or end its harder in Haskell), and 2. multiple variables treated as merely ordered rather than named.

1 Like

Lightweight iterators/generators/streams/comprehensions are extremely important. I haven’t used them in Scala but I love them in Python (where I had trouble getting my non-FP colleagues to adopt them). Here’s how I would implement your example in bluefin:

{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TypeOperators #-}

import Control.Monad (when)
import Bluefin.Eff (Eff, runEff, (:>))
import Bluefin.IO (effIO, runEff)
import Bluefin.Stream (Stream, forEach, yield)
import Data.Foldable (for_)
import PyF (fmt)

foo :: (e :> es) => Int -> Int -> Stream (Int, Int) e -> Eff es ()
foo n v y = do
  for_ [0..n] $ \i -> do
    for_ [0..n] $ \j -> do
      when (i + j == v) $
        yield y (i, j)

main = runEff $ \io -> forEach (foo 10 10) $ \(i, j) ->
  effIO io (putStr [fmt|({i}, {j}) |])

For another example see Break with traverse / traverse_? - #23 by tomjaguarpaw

I think it’s nice to observe that none of this is “built in” to Haskell, except do notation and [0..n]. These are all provided by libraries:

  • Streaming (via bluefin)
  • for
  • when
  • fmt string interpolation (via PyF)

Yeah when you think about it a little bit, list comprehensions can be used instead of map, filter, zip, drop, take, takeWhile, dropWhile, and so on. Lots of those functions can just be one-line list comprehensions. I’d personally make any high leverage things like that elegant core language features. In trying to write Python functionally last week (AoC2021) I ended up using list comprehensions constantly since its more parsimonious than map(lambda x: ... , filter(lambda x: ..., ...)) : yuck!

1 Like