I promise I’ll have better opinions soon. I’m well past the beginner phase of Dune now but things I take for granted with other tools are glaringly absent at the overview level. Maybe I’ll find out how those things work once I start writing my own custom rules for various code generators, but Dune’s opinion that basic string manipulation is for advanced users seems off-putting to me. Accordingly, I think (but I’m not sure) that I’ll have to reorganize all my expect tests to work with Dune’s opinion about how to organize those, then rewrite my OMake library to accommodate it during my transition. That’s my expectation at least. Will see eventually.
I mean, Common Lisp has been around since time immemorial (and always will be for that matter), but it’s hardly what I’d call thriving. Languages with even a minimal level of code written in them hardly ever truly die out, do they? That doesn’t make they’re alive and growing though. A sort of permanent stagnation more like.
(Emphasis mine)
I think those are cutting words that I wouldn’t like to use about either Common Lisp or OCaml or any of the other programming language communities with comparably long histories and a small but enthusiastic populations.
Yeast in a fermenter will thrive, for a while they will exhibit the opposite of stagnation, but it’s not a sustainable growth. It’s a way to exploit the community of yeast cells to get beer from them before scooping some of them out and putting them into a new fermenter.
I’d prefer to live in a community that knows that it controls enough land to plant the rice that will feed its people over the long term. That’s not stagnation to me. That’s thriving.
@jhw yes, dune trades away flexibility for stability and concision. It’s been around for many years now and we still support very old projects while dramatically improving things under the hood.
We’ve also taken a few lessons from OMake. In particular, OMake’s server mode was incredibly innovative and our watch mode intends to replicate, and hopefully improve on the experience. One thing I dislike about OMake is the language. On one hand, it’s flexible enough for some simple projects, but on the other, anything semi complex goes way out of hand and becomes impossible to maintain. As a programming language, OCaml is much superior to OMake’s and much better suited for writing build rules.
Dune’s language is intentionally primitive and doesn’t pretend to be a serious programming language. Eventually, we’ll make dune extensible directly in OCaml.
@timmy_jose I’m on IRC and discord and I agree that IRC can be a bit dead ever since discord knee capped it. Personally I don’t notice more “useless responses” on IRC than discord. I find that the two communities heavily overlap and the quality of responses is about the same.
I don’t disagree with that. I think honesty and constantly comparing our experience to other languages’ is critical.
At the same time, more people means more hands on deck to make improvements faster. There’s no magical time when we can say: “Tada - now we have the features we need and we can invite more people over!”. An opportunity for growth must be taken when it’s available, and Reason was one such opportunity that unfortunately didn’t keep going due to silly reasons.
Interesting. Still not sure I agree, but I’m open to persuasion on that last point.
You asked for feedback about what annoys me about Dune, and I can infer from that you might also be interested in what I like about OMake compared to it, so let me offer a story that might provide some background color.
Many centuries ago, when the Earth was young and BSD make(1)
was the only build tool any of us had, it fell to me to bring some order and discipline to build logic for a very large software system that had grown into a system of several dozen Makefile
instances using a library that comprised, oh I’m guessing, around 10k lines of make(1)
logic.
I reached for the only tool at the time I knew had been successfully (for some value of “success”) used for such a thing: the imake
tool from X Window System. Ye gods, what a mistake that turned out to be. I would show you my scars, but they are in some intimate locations. I learned to hate the Makefile
language— all variations on it, from BSD to GNU to whatever else— with the blazing fire of a thousand angry suns.
I tried a variety of other options, e.g. Jam
and GNU Automake
. I hated them all. Eventually, I got really crazy and wrote a system in Perl 5 that I called Conjury
. The idea was fairly simple: you write your build logic in an all singing all dancing fully capable industrial grade programming language using a library that results in generating your Makefile
instances for you. Developers still get to use their make
command line tool, but they write their build logic in Perl. (Insert image of Galadriel explaining to the hobbits why they probably don’t want to give the One Ring to her.)
From that, I learned the same thing that the ninja
people eventually learned: the make
tool and its language is just insufficient. You really need the tool itself to have a comprehensive view of the whole project, not just a capsule view of each subproject.
So, I rewrote Conjury to eliminate the make
tool entirely and replace it with a similar tool (called “cast
”) that was written in Perl itself. This turned out to be not a half bad approach to the problem, and I was allowed to post it to CPAN, but day jobs change, and I took another one where they didn’t need me to maintain the build logic. The Perl version of Conjury became something I hacked on in my hobby time, and the CPAN version fell into disrepair.
One thing that I learned to appreciate well, from basically reimplementing all of make(1)
(and then some) in Perl, is that the language that appears in Makefile
programs is deceptively tenacious. People keep using it. It’s a very useful language. Things I thought were warts were actually beauty marks. Because it’s a special purpose language and not a general systems programming language, it’s possible to write logic that expresses build rules and actions concisely and fairly clearly. That’s harder in Perl, and I don’t think I got it right. (I was probably bumping up against the same problems with Perl that made a whole raft of people decamp and make Raku happen. Have I mentioned lately that Raku is an awesome language. I should write more Raku.)
I discovered OCaml in 2002, around the same time I was tiring of Perl. Not long after, I discovered OMake. When I first read the [short, and excellent] reference manual for the OMake language, I was beside myself. Here was a make
variant that seemed to correct all of the things about make
that made me hate it, while leaving in place all the special purpose features that I had learned to appreciate were what made make
into a tenacious weed that seemed like it might never be displaced by anything better.
I didn’t think the original OMake standard library was very rich or extensible, and I thought I could do better. So I reimplemented most of the ideas in the Perl implementation of Conjury into an OMake library of the same name. (Then I rewrote it, after I had learned more OMake, and I discovered just how rich a language it is. I mean, ye gods, somebody wrote an entire C language parser in under 4k lines of OMake— it was last updated 12 years ago, because it still works. Because of course you would do that. Why wouldn’t you do that?)
So, I’ll agree that OMake is not the tool the community should be using right now. It’s not well maintained, the standard library is not very rich, and my Conjury library needs far more time and energy put into it than I can afford to give personally. But the least pressing problem with OMake is the quality of the language. I think the language is awesome, and I’m sad that its library leaves so much to be desired compared to the features now offered by dune
.
So I hear your distaste for the OMake language, and I have to wonder if it comes from the same distaste for make
variants that I developed all those years ago, and it took me so long to overcome before deciding I was wrong about it?
As for what I like now? Well, I’ve grudgingly come to respect bazel
after using it my day job for the last four years. I wish Starlark weren’t a Python variant, but I respect the choice because Python is so widely known.
My advice to the dune
team is to study bazel
intensely. In fact, if I were being puckish, I’d advise the dune
team simply to put all their code into maintenance mode and go find a way to make bazel
rules that can serve as a replacement for it. Which is basically OBazl— you guys should drop everything and go make OBazl happen.
I’m not gonna be at all surprised if the dune
team decides they can do better than bazel
. Maybe by doing to OCaml what Starlark did to Python while stealing all its other awesome ideas like aspects and toolchains and distributed builds, et cetera. I wish them luck.
But really, I think OBazl is what we need.
Not in general. And I hear the ‘move fast’ again.
But more people means more threads like this one.
Thank you for the extensive story, I enjoyed reading it.
You may find this PR an interesting read, as it details some issues they ran into.
Another surprise was a bit of pushback from package maintainers with the switch to bazel, but these complaints may be local to the repo, as it has so many languages involved in it…
This is a fascinating story, and I’m going to finish reading it, but right away one of the first reactions I had was to say to myself, “Well, thankfully, we all get our build tools from opam
and not apt-get
or pkg
or yum
or whatever.”
I think I need to ponder that more deeply while I’m reading this whole thread.
Update: Wow! This story just keeps getting weirder and weirder. The main pushback from the packagers is about requiring build from source to proceed without requiring either a) any network access, or b) vendor bundling of dependencies. Leaving me to wonder just how most OCaml software built with Dune and OPAM today are handled by distribution packagers self-imposing those kinds of requirements. Oh wait, I probably don’t have to wonder. They’re already failing to stay up to date with what’s in OPAM.
There was this recent talk about that tension between language package managers and system package managers which may shed some light.
System package maintainers may seem demanding from our end, but the inevitable byte-sized fragmented libraries delivered through the language’s package manager makes it difficult to audit and provide a safe end-user experience (at least that’s what I got out of it).
By setting some guidelines, one could hope it’d result in safer systems, but it also results in open issues, like what to actually do with libraries that are too small to be defined as a package itself.
I suppose the elephant in all software development rooms would be the abysmal security model and trying to hold together the endless zero-days that compromise our systems.
The trench between security and development widens everyday although I’m not sure why. I guess the conversation isn’t being had?
Also there’s little incentive from a business perspective; hardened security doesn’t increase sales.
Well, not every software shop is like the one at my day job, where we are earnestly preparing to start very very soon driving giant multi-ton robots down residential streets where children, animals and impaired people may encounter them unexpectedly, and it’s important to remember that everyone knows the children were there first and have a right to expect safe and secure behavior from our giant robot interlopers.
I get that safely and securely building and deploying multi-language software packages from source code is a hard problem. But I know of at least one existence proof that it can be done more easily with Bazel than not.
I think I’m sympathetic to the view that system packagers are the ones that need to catch up here.
This is good to hear, indeed! Do you also - perhaps - have plans to replace dune files with ocaml script files too?
@jhw bazel is another interesting system and no doubt it’s the right choice for large companies with many different languages. For us, it’s a bad fit for in two different ways:
- It requires learning yet another DSL that is absolutely a piece of crap compared to OCaml
- Our end goal is to provide the user experience with functionality that isn’t currently covered by bazel. For example, editor integration, seamless package management.
We are picking up some important features from Bazel. We already have very capable sandboxing for rules, and JaneStreet is working on porting its distributed cache from Jenga to Dune. Toolchains is something that I’m learning about right now.
@BikalGurung No, we’d like to keep our purely data oriented sexp frontend. The objections to writing configuration in OCaml remain. Instead, we’ll gradually allow points of extensibility where the user can use OCaml for more complex builds. For example, to define their own stanzas, introduce dune sub commands, allow executed actions to communicate with dune to declare dependencies/targets.
Hear ye, hear ye!
I do think good Bazel support will address some of the issues raised in this thread.
Status update:
- the dune-to-bazel conversion tool is pretty far along
- but the crushing monotony of dealing with all the quirks and pathologies of Dune’s rather loosely-defined build language threatened to unhinge me, so I took a little break and started working on Bazel support for building the compilers themselves. Recursive builds!
- which is almost done, see the dev branch at ocamlcc. now back to rules_ocaml to finish the tooling and get to 1.0
- Bazel 6.0 was just released. Bazel “modules” support is now official - this is Bazel’s solution to the package management problem.
the OCaml language itself has been relatively easy to understand (so far!).
I’d like to throw down a gauntlet.
Here is four lines of working F# code that I can write off the top of my head that represent a regular expression that makes it easy to implement Antimirov derivatives:
type RegEx<'a when 'a: comparison> =
| Lit of 'a
| Alt of Set<RegEx<'a>>
| Seq of RegEx<'a> list
That code means “I have a type RegEx
that is polymorphic and parameterised over a type variable 'a
with the constraint that 'a
implements equality and comparison. A RegEx
is either a literal 'a
or one of a set of alternative RegEx
s or a sequence of RegEx
s”.
Compiled and ran first time. Succinct. Comprehensible. Nice.
Some notes:
- Being polymorphic over the element type means the same code can be used to match sequences of any type, not just strings of chars or arrays of bytes.
- Using sets to represent alternatives and lists to represent sequences means the regular expression that doesn’t match any input is
bot = Alt Set.empty
and the one matching with no input iseps = Seq []
. This is simpler than having more cases:Bot | Eps | Alt of re * re | Seq of re * re
. - The use of a sorted set of regular expressions eliminates duplicates and improves asymptotic performance which is more efficient than using explicit cases.
- You can print any value of any type including this
RegEx
usingprintfn "%A"
.
I’d love to see a simple port of this to OCaml. I just spent an hour trying and my use of mutually-recursive higher-order modules with PPX deriving show and ord resulted in pages of code that still doesn’t work.
I call them “undead languages”, e.g. COBOL.
Here is a simple solution, I hope.
module Make (X : Set.OrderedType) = struct
module rec S : (Set.S with type elt = R.t) = Set.Make (R)
and R : sig
type t = Lit of X.t | Alt of S.t | Seq of t list
val compare : t -> t -> int
end = struct
type t = Lit of X.t | Alt of S.t | Seq of t list [@@deriving ord]
end
end
Well, you got much further much faster than I did! But where’s your pretty printer?
I tried adding show
but, of course, it requires an S.pp
.
I guess the following could work:
module Make2 (X : sig
include Set.OrderedType
val pp : Format.formatter -> t -> unit
end) =
struct
module rec S : sig
include Set.S with type elt = R.t
val pp : Format.formatter -> t -> unit
end = struct
include Set.Make (R)
let pp fmt s =
Format.pp_print_seq ~pp_sep:Format.pp_print_space R.pp fmt (to_seq s)
end
and R : sig
type t = Lit of X.t | Alt of S.t | Seq of t list
val compare : t -> t -> int
val pp : Format.formatter -> t -> unit
end = struct
type t = Lit of X.t | Alt of S.t | Seq of t list [@@deriving ord, show]
end
end
I am pretty sure more elegant solutions exist, but that is already enough gauntlets for me to catch today!
Two thoughts:
- I wonder whether with modular implicits, this could be made … more modular. It looks like the F#
when
construct is some sort of modular implicit/trait ?
But 2. I had a similar problem: I wanted to have pp
and pp_hum
(as well as equality, ordered comparison) over base types, and then lift that up to map and set types over those base types. So I defined various signatures and functors that did that. It was a little tedious; here’s some bits of it:
module type PP_HUM_SIG = sig
type t = 'a ;
value pp_hum : Fmt.t t ;
end ;
module type PP_HUM_POLY1_SIG = sig
type t 'b = 'a ;
value pp_hum : Fmt.t 'b -> Fmt.t (t 'b) ;
end ;
module type ORDERED_TYPE_WITH_PP = sig
type t = 'a [@@deriving (to_yojson, eq, ord, show);] ;
include (Set.OrderedType with type t := t) ;
include (PP_HUM_SIG with type t := t) ;
end ;
module type SET_WITH_PP = sig
type elt = 'a [@@deriving (to_yojson, eq, ord, show);] ;
type t = 'a [@@deriving (to_yojson, eq, ord, show);] ;
include (Set.S with type elt := elt and type t := t) ;
include (PP_HUM_SIG with type t := t) ;
end ;
module type MAP_WITH_PP = sig
type key = 'a [@@deriving (to_yojson, eq, ord, show);] ;
type t !+'a = 'b [@@deriving (to_yojson, eq, ord, show);] ;
include (Map.S with type key := key and type t 'a := t 'a) ;
include (PP_HUM_POLY1_SIG with type t 'a := t 'a) ;
end ;
module MapWithPP(M : ORDERED_TYPE_WITH_PP) : (MAP_WITH_PP with type key = M.t) = struct
module S = Map.Make(M) ;
value pp_key = M.pp ;
value show_key = M.show ;
value equal_key = M.equal ;
value compare_key = M.compare ;
value key_to_yojson = M.to_yojson ;
type _t 'a = list (M.t * 'a) [@@deriving (to_yojson, eq, ord, show);] ;
value pp ppval pps m = pp__t ppval pps (S.bindings m) ;
value show ppval m = show__t ppval (S.bindings m) ;
value to_yojson val_to_yojson m = _t_to_yojson val_to_yojson (S.bindings m) ;
value pp_hum ppval_hum pps m =
Fmt.(pf pps "%a" (list ~{sep=const string ", "} (pair ~{sep=const string " : "} M.pp_hum ppval_hum)) (S.bindings m))
;
include S ;
end ;
module SetWithPP(M : ORDERED_TYPE_WITH_PP) : (SET_WITH_PP with type elt = M.t) = struct
module S = Set.Make(M) ;
value pp_elt = M.pp ;
value show_elt = M.show ;
value compare_elt = M.compare ;
value equal_elt = M.equal ;
value elt_to_yojson = M.to_yojson ;
type _t = list M.t [@@deriving (to_yojson, eq, ord, show);] ;
value pp_hum pps l =
Fmt.(pf pps "%a" (list ~{sep=const string ", "} M.pp_hum) (S.elements l))
;
value pp pps s = pp__t pps (S.elements s) ;
value show s = show__t (S.elements s) ;
value to_yojson s = _t_to_yojson (S.elements s);
value compare s1 s2 = compare__t (S.elements s1) (S.elements s2) ;
include S ;
end ;