The Hazy Haskell Compiler

I’m proud to showcase Hazy, my Haskell compiler. This is a project I have been working on in private for 3 years. It’s unfortunately not finished but it’s at the point where it’s fairly interesting. The type checker largely works and it’s able to generate Javascript. Though I haven’t tested the generated code yet.

My main goal with this is to explore how I can make Haskell more performant. I plan to implement lifetimes, linear types, levity polymorphism etc, like I did with my toy language Aith.

39 Likes

Very interesting! There are some very good ideas here, looking forward to seeing where you take Hazy!

3 Likes

It’s great to see more diversity in the Haskell-compiler world.

It’s always good to say what the main goal(s) are, so that others can learn from what you are doing. (E.g. for microHs it’s “small footprint, compiles fast”) And you do indeed say what your main goal is:

Do you mean “compiles fast” or “runs fast”? I think probably the latter.

If you mean “runs fast” do you have any ideas for how to make Haskell run fast? GHC tries to do that too, but you may well have new ideas.

10 Likes

Great news, thanks a lot for sharing your work!

2 Likes

Yes, I do want to make Haskell run faster, but my approach will be different from GHC’s. My plan is to effectively treat current Haskell as legacy and bolt-on a bunch of extensions that let you write fast code. That way you can have nice and friendly Haskell by default but optimize to C-level if you really need to.

My current plans to achieve this are to first implement current Haskell using Preceus (reference counting). This has the advantage that it doesn’t need a fancy runtime and would make Haskell follow C++'s “you don’t pay for what you don’t use” principle. Once that’s done, then I can focus on adding things like strict functions, multiargument functions, effectful functions, levity polymorphism, pointers (with lifetimes), and whatever else I would need. Then finally, when LLVM sees C-like code, it can optimize like C-like code.

I should note these plans are for the far future. Right now I need to focus on actually getting the compiler to work and I plan to do that with my test Javascript backend.

7 Likes

That’s very ambitious, I’d love to contribute in the future. :slight_smile:

4 Likes

How are you planning on dealing with reference cycles?

These are quite common in Haskell since e.g. repeat creates a cyclical list and even very basic patterns like defining Applicative via ap create a cycle between the Applicative and Monad dictionaries.

3 Likes

I already answer this a while ago:

Basically, you remove the sharing for local recursive bindings. It’s the same as if you rewrote all your (local) recursive code with the non sharing fix.

fix f = f (fix f)

For the repeat example, evaluting n cells will be O(n) memory.

3 Likes

Very cool! Welcome to the Haskell implementers crowd.

Haskell is a rather unspecific term. What version of Haskell do you implement?

3 Likes

Haskell is a rather unspecific term. What version of Haskell do you implement?

I currently plan on implementing Haskell 2010-ish plus DataKinds, GADTs and a few other things. I chose these because I need them for bootstrapping. I don’t really plan on implementing things like multiparameter type classes, type families or anything else GHC specific at the moment. Once I have Haskell 2010 in a functional state, I plan on going in different direction and implementing my own extensions.

I mentioned this in the readme, but I already have some custom extensions. Let me highlight these two:

Extended Local Declarations

sortBy :: forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy by = map runBy . sort . map By where
  import Data.List (sort)
  newtype By = By { runBy :: a }
  instance Eq By where
    a == b
      | EQ <- compare a b = True
      | otherwise = False
  instance Ord By where
    compare (By a) (By b) = by a b

Of Guard Blocks

addFail maybe1 maybe2
  of
    Just value1 <- maybe1
    Just value2 <- maybe2
    value1 + value2
  of
    0

With Extended Local Declaration, are data types generative, i.e., with data inside a recursion, does each iteration get a new data type? I’m guessing, no.

With Extended Local Declaration, are data types generative, i.e., with data inside a recursion, does each iteration get a new data type? I’m guessing, no.

I’m not sure how to answer this. As of now, data and class declarations don’t generate code and instance declarations are (effectively) desugared into terms. I guess the answer would be yes. In the same way that polymorphic recursion gives you a new type each iteration, but in a way that the runtime doesn’t care.

If this typechecks, it’s not generative.

f 0 = []
f n =
  let data T = A
  in  A : f (n-1)

That does not type check, T escapes.

I don’t have integer patterns (or generalization) at the moment, but here’s a modified version and the actual message:

module Augestss where

f _ = []
f n =
  let data T = A
  in  A : f (n-1)
Augestss.hs:6:7 error: escaping type: `T`

OK, escaping was not the problem I was referring to. I’ll see if I can come up with a different example.

I noticed that you do not support prefix negation (i.e. -x). That’s what I started with for MicroHs, but I gave up on it, because I wanted to use code written by other people. So if you don’t want to write all the code yourself, I recommend against it.

I’d like to run a program. How do I do that?

Uhh, unfortunately, I’m not that far along yet :pensive_face:. Literally none of base is implemented yet. It’s all x = error "todo". I literally just finished the Javascript generator today and decided it’s a reasonable point to publish it. All you can do is generate Javascript and look at it.

There’s also some low hanging fruit that I need to get around to implementing like lambdas and case expressions.

using lambda lifting to deal with mutually recursive bindings is a very neat idea. does it also work with mutable references?

3 Likes

No it does not. IORef will leak by default and will have to be manually freed. STRefs will be freed when the computation ends. This can be enhanced a bit with monadic regions to allow for scoping.

Again in Aith, I have a region effect system which is equivalent to monadic regions and based on boolean unification. I plan to put it or something like it into Hazy at some point.