<Drup>
turing completeness is overrated, literally everyone has it
<Drup>
pacman completeness is much cooler
<Drup>
(and slightly related to your area of interest :D)
mcc has quit [Ping timeout: 265 seconds]
MrScout_ has quit [Ping timeout: 258 seconds]
WraithM has quit [Quit: leaving]
struk_at_work has quit [Ping timeout: 246 seconds]
samrat has quit [Ping timeout: 240 seconds]
samrat has joined #ocaml
gdsfh has quit [Quit: Leaving.]
gdsfh has joined #ocaml
psy_ has quit [Quit: Leaving]
mcc has joined #ocaml
pyon has quit [Quit: rcirc on GNU Emacs 24.4.1]
pyon has joined #ocaml
sirGrey has quit [Ping timeout: 264 seconds]
<nicoo>
Drup: What is pacman-completeness ? Is it related to the game or to the package mangler?
sinelaw has joined #ocaml
<dmbaturin_>
mcc: Where is the source though? :)
dmbaturin_ is now known as dmbaturin
WraithM has joined #ocaml
natrium1970 has joined #ocaml
ggole has joined #ocaml
slash^ has joined #ocaml
<natrium1970>
I’m creating a module, and I would like to allow implement custom operators, with infix syntax. I see that the pattern is to use the “plain” operators like + with a symbol afterward. From what I can tell, the only way to make infix operators work is by opening the module.
<natrium1970>
I’m a little concerned that I’m going to accidentally leak some names into scope by opening the module.
mcclurmc has quit [Remote host closed the connection]
octachron has joined #ocaml
<ggole>
You could stick em in a sub module and only open that
<ggole>
module Foo = struct module Ops = struct let (+) a b = ... end end and then later open Foo.Ops, or Foo.Ops(x + y)
<mrvn>
An exception might not be what you want but I don't call that "bad things"
hausdorff has joined #ocaml
<Drup>
mrvn: the type system catching it is much better.
<ggole>
It can infloop, too.
<ggole>
(Which is just another form of diverging, but possibly a more problematic one.)
<mrvn>
Drup: that requires type classes
samrat has joined #ocaml
<ggole>
I saw that coming.
<mrvn>
ggole: true, cyclic structures can screw thingas up. I forgot about that.
<dmbaturin>
Are there any strict by default languages with type classes?
<Drup>
mrvn: and you would have understood that it was the point since the beginning if you were reading it.
<Drup>
dmbaturin: Rust
<mrvn>
Drup: I was reading. I just said that = is not a type equality.
<dmbaturin>
Haskell type classes cause funny errors sometimes, like f x y z = x ++ y + z compiles but causes a runtime error becase it assumes that list is an instance of Num even though + is not implemented for it. I'm not sure if I understand whether this problem is inherent to the type class mechanism it uses or is caused by assumption that referenced functions are implemented somewhere later.
<mrvn>
urgs. That's unaceptable.
mcclurmc_ has joined #ocaml
<whitequark>
O_o
mcclurmc has quit [Ping timeout: 255 seconds]
<nicoo>
dmbaturin: AFAIK, such errors get caught (you will get a type error if you call f in a context where there is no Num [a] instance)
Thooms has quit [Quit: WeeChat 1.0.1]
<nicoo>
It just isn't caught at the definition of f, but at its use points (because for some reason, you could have implemented a Num [something] instance)
<dmbaturin>
Yeah, when compiling an executable it should be a compile-time error, just at a bizzare place still.
<Drup>
ah, right
<Drup>
you said "runtime error"
AlexRussia has quit [Quit: WeeChat 1.1-dev]
<nicoo>
dmbaturin: Well, it is inherent to typeclasses: the compiler cannot guess that you won't define instances of Num [a].
AlexRussia has joined #ocaml
psy_ has joined #ocaml
<dmbaturin>
nicoo: So it's impossible to implement type classes in such a way that said error would be caught at the definition, even in a strict by default language?
<nicoo>
I don't think so.
<ggole>
Can't you scope them?
<mrvn>
In ocaml the type class would have to be defined before being used. So you can report the error imidiatly.
<mrvn>
In haskell type classes seem to be open types
<dmbaturin>
That's what I'm thinking. But I still don't have a good understanding of type classes.
<mrvn>
type classes are like base classes in objects.
<mrvn>
If you use '=' then the arguments must be of type <(=) : 'a -> bool; ..> basically
<mrvn>
'a being the self type
<nicoo>
mrvn: The type class has to be defined, yes. Not all of its instances
mcclurmc_ has quit [Remote host closed the connection]
<mrvn>
I guess it makes sense to keep type classes open. That way the user can implement new members for the type class.
samrat has quit [Quit: Computer has gone to sleep.]
<mrvn>
Ahh, no. It has a problem with using "new" to allocate and free() to destroy.
<mrvn>
ups, ewin
mcclurmc has joined #ocaml
mcc has joined #ocaml
samrat has joined #ocaml
<mcc>
okay, so, i am parsing command line arguments. i am hoping to use "arg". "arg" seems nice.
<Drup>
ahah
<mcc>
however, it is also the case that a thing i really wanted to do was support passing in a single "-" as an argument name, to denote "take standard input".
<mcc>
am… … i understanding right that Arg excludes this possibility with scalpel precision
<mcc>
okay, so are Lwt's callback/flow structures literally Applicatives?
slash^ has quit [Read error: Connection reset by peer]
<whitequark>
I think the applicative functor remark was about cmdliner
<mcc>
ok.
<whitequark>
although that would be literally the least helpful way to describe its API
<mcc>
haha
<whitequark>
even less helpful than just "go fuck yourself"
<mcc>
at any rate, Arg let me do this ("-", Unit(fun () -> print_endline "meh") , "")
<Drup>
whitequark: it's helpful the other way, in fact
<whitequark>
oh?
<nicoo>
whitequark: Nice pic :D
bytbox has quit [Remote host closed the connection]
<Drup>
whitequark: if you have strong FP background and you know that "ok, if I have an applicative functor and a monad I can do *this weird combinator that will solve my problem*, I can apply it to cmdliner, and boom magic
<mcc>
i will strongly consider cmdliner if i hit another place Arg can't do something I want.
<Leonidas>
Drup: that sounds like verybody in Haskellland ever
<mcc>
So something I have been told is that this whole monad/applicative mess that FP people are so bad at describing is something that incidentally maps very, very closely to async scheduling systems like python/javascript like to use.
<Drup>
Leonidas: It's, hum, possible.
<whitequark>
haskellland. that's almost as many l's as dllllvm.so
<whitequark>
mcc: well, Lwt *is* a monad
<Leonidas>
dllllvm.dll
<Drup>
whitequark: no spoiler!
<whitequark>
it's just that I would never start by describing it as a monad, because, well, you know what happens once someone mentions monads
<mcc>
and sometimes accidentally follow the monad rules.
<Drup>
it's funnier when you tell it *after* they used it.
<mcc>
And I find "well, you can easily construct flow structures that naturally involve long pauses or single-threaded concurrency" to be a compelling reason to attempt to investigate something like monads/applicative.
<whitequark>
haha
<Leonidas>
I think the existance of Lwt.(>>=) already gave that much away :->
<Drup>
Leonidas: not necessarily.
<mcc>
I do not find "I specifically decided to use a programming language that lacks mutable structures, and then suddenly I realized I needed mutable structures" to be a compelling reason.
<whitequark>
there's this claim that lack of mutability makes certain kinds of analyses incredibly easier for human and computer alike
<mcc>
I'm aware
<whitequark>
e.g. STM and the like
<whitequark>
I'm not sure I buy it
<mcc>
And I *very* much like the approach of delaying introducing category theory terminology as long as possible. :P
<whitequark>
because it makes some other kinds of analyses incredibly hard
<Drup>
whitequark: I buy it
<Drup>
what I don't buy is that monads are the good formalism to talk about this stuff
<mcc>
I think the fact that "does this follow the monad laws" apparently cannot be typechecked should be a sign of trouble all by itself
<whitequark>
Drup: I don't, after I looked at how many places in haskell use strict evaluation
<Drup>
whitequark: purity is orthogonal to lazyness
<Leonidas>
the more interesting question is whether it obeys asimov's robot laws.
<whitequark>
mcc: it can, but not in haskell
<mcc>
ok
<whitequark>
mcc: say, you can prove it in Coq.
<mcc>
what about in "monadic haskell"
<whitequark>
(in fact, that should be mostly trivial)
<mcc>
that is a product that exists right
<whitequark>
monadic haskell? you mean, haskell? :D
<Drup>
or any other dependently type languages.
<whitequark>
Drup: can't there exist dependently typed languages with a TS not strong enough to prove that?
<mcc>
i thought there was literally a haskell variant that had "monad" or "applicative" or something in the name. maybe i was confused.
<Drup>
whitequark: it's not dependently typed, then.
<Leonidas>
mcc: Template Haskell?
<mcc>
I'd be surprised if template haskell made that possible. I thought that was just haskell with a macro system.
<whitequark>
it is
<whitequark>
also, their macro system is hideous
<Drup>
templates haskell :<
<nicoo>
mcc: TH is ugly macros for Haskell
<whitequark>
ooooh
<whitequark>
let's discuss what's worse: camlp4 or TH
<Drup>
C++.
<mcc>
May I remind you that before I walked into this channel I was writing **C++**
<Drup>
*option D*
<mcc>
A macro system has to be REALLY UGLY to hit ugly by the standards I'm used to :(
<whitequark>
mcc: shhh, we all did that at some point
<whitequark>
it's nothing to be ashamed of
<mcc>
whitequark: so does your ire for camlp4 extend to camlp5
<Drup>
whitequark: I only did because of you !
* ggole
misses defmacro
<whitequark>
mcc: camlp5 is a previous version of camlp4
<whitequark>
mcc: yes, previous.
<whitequark>
don't ask.
<whitequark>
I think camlp4 is just so backwards, it literally evolves in the direction of lower version
<Drup>
/me was very happy not having done any C++ before trying to add functions to the llvm binding.
<mcc>
… oh no.
<mcc>
ggole: wha's defmacro
<whitequark>
camlp5 basically exists because coq can't keep up with the development of camlp4
<ggole>
Lisp's macro facility.
<Drup>
mcc lisp's
<mcc>
ah
<whitequark>
now we have *two* broken libraries to maintain! yay! long live software compatibility!
* whitequark
generously sprays gasoline around and ignites
<Drup>
mcc: to get back to a previous point: writing software using Lwt is, imho, a very nice way to understand monads.
<ggole>
Roughly a million times easier to use than camlp4
<Drup>
without reading about monads
<mcc>
OK.
<ggole>
And no tools, you just type a macro and then use the macro. Sigh.
<mcc>
*deep breath*
<whitequark>
mcc: the nicest thing about lwt is how you keep using exceptions instead of having to remember about errbacks
<whitequark>
raise and try..catch, it just works
<Drup>
ggole: no syntax, no tools, no type system, no speed
<Drup>
:D
<whitequark>
it's probably the first async error handling system I've seen that is not horribly broken
<mcc>
if i ask for someone to point me to a summary of the monad laws which explain them without having to resort to reference to the type system of any particular specific language.
<ggole>
Except slime is really good, and SBCL is actually pretty fast
<mcc>
is that something anyone here would know about.
<ggole>
Not as fast as OCaml (at least, without type annotations), but nowhere near that Python/Ruby crap
<whitequark>
generally, monad laws don't involve a TS?
<mcc>
hm.
<whitequark>
like, you can have a monad in javascript, nothing stops you
<mcc>
whitequark: i was interested! then i couldn't get it to compile and got bored.
<whitequark>
jquery's $ is a monad
<mcc>
ggole: how do you feel about typed racket?
<ggole>
I haven't done serious hacking in it, but I've sort of... approved of it from a distance?
<mcc>
ok
<Drup>
ahah :D
<mcc>
getting to the point where i could describe to someone what a "monad" connotes in js/python/lua or something with closures but not types is the point i would like to get to with monads. and then possibly ideally never use them again :P
<Drup>
it's quite sad that monads is such an overblown term, because the concept is ridiculously simple but became the crystallizing point of "FP is not understandable without a math PHD degree".
<ggole>
Typed racket does some fun stuff like typing variadic functions
<whitequark>
well, you will use them whether you want it or not, as it is a descriptive term for a quite common pattern
<mcc>
In general: I love FP languages. I tend to hate FP communities.
samrat has quit [Quit: Computer has gone to sleep.]
<Drup>
mcc: I hope we are ok :O
<mcc>
Y'all are very nice.
<ggole>
Drup: people being exposed to them generally also have to get familiar with a bunch of foreign sounding terminology, and strange things like higher-kinded types
<ggole>
Eating the whole burrito in one mouthful, so to speak.
<Drup>
:D
<Drup>
I want to eat burritos now
* mcc
is very curious if she can at some point design something like a monad or applicative library which is constructed in such a way to remove any specialist terminology at all.
<Drup>
mcc: well, cmdlinre and lwt are good examples :p
<mcc>
It seems like "we have a thing, and we're globbing 'and then this happens!' onto the end of it" is not a very advanced concept by itself.
<Drup>
indeed :)
<mcc>
like why is that inherently harder than "well, to make something else happen, you put a semicolon and then the next thing".
<whitequark>
practically, monads are just a design pattern right next to factories or, say, facades
<whitequark>
so it's not, design-wise
<ggole>
Functor is a pretty confusing one
<mcc>
yeah.
<Drup>
ggole: is it ?
<mcc>
The thing that confuses me about functors is I KNOW ABOUT FOUR SEPARATE CONTRADICTORY DEFINITIONS FOR THAT TERM
<whitequark>
people with FP background tend to say things like "well, these two completely unrelated things are monads, so we can abstract same operations for them"
<ggole>
There's many extant uses of that word, so people are particularly likely to have conflicting memories attached to it
<Drup>
I mean, except that the term is highly overloaded :D
<ggole>
Right, that's the problem.
<ggole>
The thing itself is extremely simple.
<mcc>
I use functionoids instead of functors in C++ solely because I get to call them that
<ggole>
But there's all this association washing around.
<whitequark>
mcc: "functionoid" is a good way to call them.
<Drup>
whitequark: "those two completely unreleated things needs to do two completely unrelated things, so we apply the flycatcher pattern to them"
<whitequark>
I'd just say "callable class", because why not
<mcc>
Technically functionoid is a specific bit of terminology within the C++ community.
<whitequark>
Drup: *exactly*
<Drup>
"functionoid"
<ggole>
What's the distinction between a functionoid and a functor (in C++ parlance)?
<mcc>
but i guess a functor is also a functionoid
<whitequark>
and then goes a long tirade about point-free style and "thinking with functions"
<Drup>
you can't make a cutter theoretic word if you were going to try :D
<whitequark>
it's like "thinking with portals", except you don't get a cool gun, I guess
<mcc>
ggole: "functionoid" refers to the pattern of a class which is a callable object, but instead of saying operator(), you designate some particular function name.
<Drup>
what's a functionoid ?
<mcc>
Like "->run()"
<ggole>
mcc: ah, that's pretty simple
<Drup>
that's a function ? =')
<ggole>
And probably less confusing.
<mcc>
very simple yes.
<mcc>
It produces much, MUCH more readable code than using operator().
<Drup>
ok
<whitequark>
mcc: so, Executor pattern? ;D
<Drup>
it's a class that decided to be a function.
<Drup>
I can get behind that, functions are much nicer citizens.
<mcc>
whitequark: probably!
<whitequark>
"Of course "escort", being a Verb itself, is hardly allowed to run around naked; one must procure a VerbEscorter to facilitate the escorting. But what about "procure" and "facilitate?" As it happens, Facilitators and Procurers are both rather important Nouns whose job is is the chaperonement of the lowly Verbs "facilitate" and "procure", via Facilitation and Procurement, respectively.
<mcc>
whitequark: ok, so maybe OO is not actually less obscure than FP sometimes
<whitequark>
hahahahah
<mcc>
it's just using middle management terminology instead of mathematician terminology
<tane>
mcc, now that's a comparison i find pretty useful and never thought about it that way :)
<Drup>
I also thing that most math teaching is terrible and many programmers are traumatized by math after high school, so they get an allergic reaction when they see math terminology.
<whitequark>
that's absolutely true. and even more so in US
<btrace>
hi all, i am new to OCaml, just started playing with it recently. Nothing serious yet, but I could use some style advice for sure. Here's my simple code for factoring integers - http://codepad.org/sSmslkhA Any obvious mistakes?
<Drup>
mcc: do you know what a map function is ?
<mcc>
uh… i mean, i know the standard second-order function "map" which is in several languages? do you mean something else?
<Drup>
no, I mean this one
<Drup>
what does it do ?
<mrvn>
btrace: I would make the loop in line 6 go up to d * d <= n
<mcc>
btrace; what does the "loop" function in the final let _ do?
<mcc>
drup: i'm sorry, i do not think i understand what you are trying to get at.
<Drup>
mcc: follow me, and you'll see at the end :)
<btrace>
mcc, prints pair from the list
mcclurmc has quit [Remote host closed the connection]
<mrvn>
mcc: List.iter
<mcc>
btrace: oh, i see.
<mrvn>
btrace: in factor I would go from 2 upwards. Then you can also skip the prime test.
<btrace>
mrvn, nicoo, I know, but it works and doesn't require multiplication on every iteration
<Drup>
btrace: as mrvn said, you could replace this loop function by a List.iter
<mcc>
btrace: as someone who is not accustomed to ocaml, as far as style goes, i think my recommendations would be descriptive rather than single-letter variable names and more comments :)
<mrvn>
btrace: (d + 1) * (d + 1) = d^2 + 2 d + 1. You can carry d^2 along.
<mcc>
for example naming that last loop "printall" instead of "loop" would have made it more transparent
<mrvn>
btrace: algorithmically building a list of primes and only checking those is also much better.
<btrace>
mcc, good point, thanks
<nicoo>
mrvn: Depends on whether you use factor many times or not, on numbers with big factors or not, ...
<mrvn>
btrace: in line 15 use succ (succ d) and special case 2.
<mrvn>
nicoo: you can extend the list as needed
<Drup>
mcc: just try to explain what map does to me :p
<btrace>
mrvn, oh good catch, makes sense
<mcc>
drup: okay, fine. what map does is ('a->'b')->('a list)->('b list) and this is about the most clear way to describe it :P it filters a sequence by a function to produce a new sequence consisting of the function applied to each member.
<btrace>
but my concerns are mostly about me using the language correctly. Like should I move loop' out of loop or this is the correct style, etc
<nojb>
btrace: seems fine to me
<mcc>
Similar to btrace's question, something I keep wondering is whether there are any performance implications to defining a helper function inside of a loop rather than outside of it.
<companion_cube>
depends on whether this helper function is a closure or not
<Drup>
mcc: and things other than lists ?
<nojb>
it depends if the inner function has free variables
<Drup>
and on things*
<mcc>
drup: it has nothing in particular to do with lists, you can think of "list" in that previous type as an abstract concept.
<nojb>
mcc: but in any case the ‘performance implications’ are probably trivial in almost all situations …
<ggole>
OCaml is unfortunately quite naive about closure construction :(
<mcc>
nojb / companion_cube: so if in the code the iner rec loop', rather than capturing d, had been defined outside loop and taken d as an argument... would *that* be difference from a performance perspective?
* mcc
would tend to keep the loop' inside and capture anyway! seems a lot more readable because you're not thinking in what other situations loop' might be used...
<companion_cube>
mcc: if you can move the inner function outside, then there is no performance implication
<ggole>
Of course it isn't very common for it to matter, but it is a pain to have to manually lambda lift in the places where it does
<companion_cube>
well it's complicated and can go both ways
<companion_cube>
a closure on many parameters and only one argument can be more efficient sometimes (easy call to map/iter, etc.)
<Drup>
mcc: ok, so is "let f (g:'a -> 'b) (l: 'a list) : 'b list = []" a map, according to you ?
<Drup>
It has the right type.
<Drup>
(it's not a trick question)
<nojb>
mcc: if a function has free variables then generally a closure needs to be allocated for them … but allocation is extremely cheap in ocaml so almost always the difference does not matter from an efficiency standpoint
<btrace>
well, from what I see in ocamlopt -S output loop' is not 'call'd into, merely 'jmp'd
<btrace>
so there is no performance penalty
<btrace>
i was more concerned about readablity
<mrvn>
btrace: Usualy you can gain far more by optimizing the algorithm than by optimizing the code. Like testing divisibility by 2, and all odd primes >= 3 up to x^2 > n.
<btrace>
mrvn, I know, I just answered the question
<btrace>
testing odd primes is my mistake, dunno why I did that, because as you can see in is_prime I do exactly that
<mrvn>
btrace: I either put the whole if/then/else on one line or if/then/else each on a seperate line. Not like line 16.
<mcc>
nojb: ok, i see.
<mcc>
drup: i was being a bit snarky mentioning the type. what i would really mean is that a map is a second-order function which for some kind of sequence takes one sequence and a function and produces a second sequence consisting of that function applied to all members of the sequence.
<mcc>
drup: Is this moving toward trying to suggest monads provide a way of defining the map function without knowing what the underlying kind of sequence is?
<Drup>
mcc: well, done you just defined what a functor is.
<Drup>
(as in, Haskell's Functor, not OCaml ones)
<mrvn>
mcc: the monad can define a sequence as some object that has a value : unit -> 'a and next : unit -> 'a sequence function.
struktured has quit [Ping timeout: 272 seconds]
<mcc>
and not C++ ones. >_>
<ggole>
Don't forget Prolog functors!
<Drup>
mcc: my point was more along the lines "you know what it is, you just don't know the names " ;)
<Drup>
I didn't even told you anything, I just made you spell out what you already knew.
sheijk has joined #ocaml
<mcc>
so, i guess i already knew what a haskell functor was because i knew how haskell fmap worked.
<Drup>
muh :<
<mcc>
similarly, i suspect when i finally get monads (and i'm not reading haskellwiki early on a sunday morning, maybe later) i will be kind of annoyed at how simple it is also :P
<Drup>
indeed :)
matason has joined #ocaml
<mcc>
however, i can get it and still be frustrated at the social processes around making things seem more complicated than they are by ambiguous or unnecessarily pedagogical use of terminology >_>
<Drup>
ahah
<mcc>
and i think it's quite sensible to be frustrated that haskell, ocaml, c++, prolog, and category theory produce unique and contradictory definitions of functor...
<companion_cube>
monads aren't that hard, just read a few implementations (list, option, error, state, maybe Lwt) and you'll figure out why they're useful
<ggole>
That's terminology for you.
<ggole>
"type" is another fun one
<mcc>
ugh
<mcc>
there's a reason i kept saying "kind" and "sequence" a moment ago
<Drup>
beware
<Drup>
kind and sequence are also highly overloaded.
<mcc>
bah!
<ggole>
class!
<companion_cube>
:>
<Drup>
generics!
<Drup>
objects!
<Drup>
x)
<mcc>
companion_cube: yeah... i know some monads and i think i get why they're useful, i just… i want to understand the concept well enough to implement it from scratch in lua? by reading the implementations you're suggesting reading those things in the ocaml interpreter source?
<Drup>
(I think object is probably the worst)
<ggole>
The problem is that these are great umbrella terms that people assign very specific meanings to
<ggole>
And vast confusion results
<companion_cube>
mcc: read about how they are implementd, and try to use them, maybe
<mcc>
ok
<companion_cube>
the option monad is particularly useful
<ggole>
And exception
octachron has quit [Ping timeout: 255 seconds]
<mcc>
is the option monad unique from the option type in ocaml or would you suggest the option type is an implementation of an option monad
<mcc>
i just wish we could pick one word for each of these generic categories (kind, sequence, collection) and say NO ONE IS ALLOWED TO OVERLOAD THESE WITH ADDITIONAL MEANING OR APPLICABILITY TO A DOMAIN EVER
<mcc>
i can't even say "category". that's taken.
<Drup>
=D
<companion_cube>
mcc: hmmmm
<companion_cube>
with the option type comes a natural monad
<ggole>
Well for option map is obvious, unit is just fun x -> Some x, and join is function None -> None | Some x -> x
<ggole>
Writing these in lua should be pretty easy.
<Drup>
I think it's time I pick up some lua
<Drup>
I never bother to actually look at the language.
<mcc>
lua is lovely. it's just a little gem of language design.
<mcc>
doesn't do very much.
<Drup>
Let's see if I can implement an option monad in lua :D
octachron has joined #ocaml
<mcc>
it implements objects but not classes or prototypes, and just gives you enough ability you can add classes or prototypes or whatever through a library.
<whitequark>
lua is so painful to use
<mcc>
heh
<companion_cube>
well it's untyped
<mcc>
that's the problem yeah :(
<mcc>
it's lovely until your program reaches a certain size and suddenly you cannot remember the exact signatures of your ad hoc structures.
<companion_cube>
I can't really fathom what a statically-typed script language would look like
<whitequark>
for me it's mainly the fact that there is nothing in the stdlib, you can't easily install 3rd party libs, and the syntax is a big "fuck you" to anyone who knows basically any other language ever
<whitequark>
~= as not equals, seriously?
<Unhammer>
<Drup> [07:51:44] Unhammer: I have some code.
<Unhammer>
anything online?
<companion_cube>
not worse than <>
<Drup>
Unhammer: arg !
<whitequark>
<> is not used for anything except not equal
* companion_cube
just realizing he never uses <>
<whitequark>
~= is used for the regex match
<Drup>
whitequark: except in haskell :D
<mcc>
whitequark: <> is the stdin representation in perl.
<whitequark>
I regret saying that already
<Drup>
:D
<Unhammer>
?
<Unhammer>
(that was re: sedlex+menhir)
<ggole>
Wirth's revenge!
<mcc>
whitequark: i will be kind, and not explain <>'s etymology and the critical difference between scalar and list context for its use.
<whitequark>
mcc: I have a rough idea of that, yes
<mcc>
whitequark: the problem is that lua does not have an interpreter. you are basically expected to build your own.
<Drup>
mcc: why do people feel attacked when someone say something along the lines "I'm not clever enough not to use static typing" ?
<companion_cube>
I liked the idea of using ppx to define *efficient* parser combinators, btw
<mcc>
whitequark: …which is why you can't include libraries, and there's no helpful stdlib.
struktured has joined #ocaml
<whitequark>
mcc: well, that's a design fault.
<whitequark>
you totally can abstract library management. you need, what, one function? "read a file"
<whitequark>
doesn't even have to be a real file, could just peek at a map inside the executable.
<mcc>
i think it's a problem of distributions. the use case for the thing is really narrow.
<mcc>
basically, lua assumes itself to be support for a C program. … and THAT is a design fault.
<whitequark>
yeah, that's one way to look at it, too
<mcc>
companion_cube: i think what i want is a gradually typed script language. let me write my libraries with static typing and my "scripts" with duck typing. actionscript of all things does this pretty much fantastically.
q66[lap] has quit [Read error: Connection reset by peer]
<Drup>
(19:58:15) mcc: whitequark: i will be kind, and not explain <>'s etymology and the critical difference between scalar and list context for its use. <- don't be kind to me, I'm curious what you are talking about
* whitequark
hides
<mcc>
haha
<companion_cube>
Drup: you don't want to know about perl
q66[lap] has joined #ocaml
<Drup>
ah, so it's something perl related
<Drup>
that's a first information I didn't have !
<mcc>
drup: … <FILEHANDLE> is an operator in perl which for FILEHANDLE reads and returns either (1) a string containing the next line up to $/, in scalar context or (2) a list of all lines split on $/, in list context
<mcc>
drup: <>, with no FILEHANDLE provided, assumes stdin.
<whitequark>
$/ is global, isn't it? or is it some other weird case like frame-local or thread-local that looks like a global?
<mcc>
hence many perl programs begin with either {local $/; $_=<>} or while (<>)
<whitequark>
ruby's $(symbol) variables include four kinds of these. frame-locals, thread-locals, true globals, and globals backed by functions instead of memory
<mcc>
whitequark: see "local $/" trick
<whitequark>
... you can change the scoping of an existing special variable?
<mcc>
yes. perl is terrible.
<companion_cube>
Drup: why did you ask
<Drup>
companion_cube: I didn't know it was perl related !
<companion_cube>
whyyyyyyy
<mcc>
also, it's not… it's worse than that, i think? i think if you say "local $/" you're actually defining a new variable in the current scope named $/, and this somehow shadows the system-level global $/, probably because $/ is not actually a variable it just looks like one.
<Drup>
I must admit mcc, I didn't understood
<Drup>
but it's mostly because I have literally no idea about perl
<mcc>
Drup: I RECOMMEND KEEPING THINGS THAT WAY.
<Drup>
yes, that was my objective !
<mcc>
Note: Larry wall claims perl is like LISP, really
<whitequark>
LOL
<mcc>
I KNOW
<companion_cube>
perl is like lisp in that it's a programming language whose source code is text
<companion_cube>
I don't think there's much more in common
<Drup>
I mean, my PL background allows me to understand pretty much any language by looking at it (they are all the same, in the end) ..... except perl.
<companion_cube>
and prolog?
<whitequark>
Drup: you need a blood sacrifice, you see
<Drup>
well, I know prolog, so, no.
<mcc>
perl cannot be understood. it literally cannot be specified except by its own interpreter.
<whitequark>
mere PL background is not enough
<Drup>
and prolog is *cool*
<companion_cube>
but "they are all the same, in the end" doesn't apply to prolog
<Drup>
ok, you are right.
<companion_cube>
thanks :p
<whitequark>
also, forth
<Drup>
as, yes, stack based languages
<Drup>
it's on my tolearn list
<whitequark>
"to learn and never use"
<mcc>
that list is long for me
<companion_cube>
it makes for a good compilation target, though, doesn't it?
<whitequark>
I sorta just realized that I dislike concatenative langs and point-free style for much the same reasons
<whitequark>
actually, they're so similar, I think there should be some clever isomorphism or something
<mcc>
hey i think this PR is a response to an issue i filed, https://github.com/ocaml/ocaml/pull/118 can anyone recommend how i would go about testing the patch so maybe i could comment on whether it resolved my problem?
<Drup>
mcc: there is an automatic import from github PR to opam switchs
<whitequark>
opam switch 4.03.0+pr118
<Drup>
what whitequark said, exactly.
<whitequark>
you will need to do opam pin ppx_tools --dev-repo afterwards
<mcc>
fantastic
<whitequark>
and possibly other things, including merlin, because 4.03 changed AST format
<mcc>
ok. it sounds like this will take a while.
<whitequark>
yes, it is quite a bit of compilation
<mcc>
and then when i want to get back to the real world, i say opam switch 4.02.1 and then … uh… i delete something out of ~/.opam?
<Drup>
also, i'm not sure you will be able to test directly, it needs some adaption of the various tools, I think.
<whitequark>
opam switch remove 4.03.0+pr118
<mcc>
drup: you mean the vim->merlin layer?
<mcc>
whitequark: cool
<Drup>
mcc: yes, possible, I don't know.
<companion_cube>
oh, what changed in 4.03 AST?
<Drup>
companion_cube: inline records! \O/
<companion_cube>
ohhhhhh
<Drup>
/me dances around.
<companion_cube>
right
<companion_cube>
<3
<companion_cube>
any hope Chambart's work will be included, btw?
<Drup>
whitequark: "Point free stacks" would be a fabulous ICFP troll paper.
<whitequark>
Drup: write it
<Drup>
:<
<companion_cube>
saw a talk by Spiwack on a monad stack, and there are inlining issues related to this kind of code
<companion_cube>
(surprise, it was a mix of state, continuation and error monads)
<whitequark>
how to threat a functional programmer: "i'll kick you in the monads"
<nicoo>
Drup: Point-less stacks :>
<companion_cube>
I'll side effect in your neck
<nicoo>
whitequark: threaten*
nojb has quit [Quit: nojb]
<whitequark>
threaten, right
<companion_cube>
nicoo: you're playing a dangerous game
<nicoo>
“And Gandalf returned after seventeen years. ‘I have been busy studying the ancient tomes,’ he said. ‘And the answer is clear. You have a template error. But I will not speak of it, for it is a language so foul, it must never be repeated'”. <3
<companion_cube>
hmm, I frequently use at least 4 monads in ocaml, actually
<companion_cube>
random, option, error, and sequence...
JokerDoom has joined #ocaml
<Drup>
whitequark: I feel like you can insult languages with much more creativity than that.
<nicoo>
struktured: Speaking of that blog article, I recently was convinced that C# is a tiny bit less horifically awful than Java
<Drup>
hum, struktured, not whitequark, sorry.
<companion_cube>
sure it is
<companion_cube>
C# does include new ideas, from time to time
<struktured>
Drup: honestly I just like the title of the article. instantly will piss off millions of programmers
<companion_cube>
it started like java but kept getting better
<struktured>
Nicoo: they had benefit of not reproducing java's really crappy generic type system
<struktured>
orbitz: ping
<companion_cube>
also, including closures less than 20 years later
<companion_cube>
better generics
<companion_cube>
some monadic-ish things
<mcc>
at some point the C# team started hiring LOTS of functional people
<Drup>
and did F# ?
<mcc>
basically drained the brain trust of java researchers in academia
<mcc>
…also actually LISTENED to them, which the JCP never did
<companion_cube>
heh.
<Drup>
mcc: that's not actually true, java's generics came from the academia
<companion_cube>
the JVM really isn't suited to academia (functional) languages
engil1 is now known as engil
<companion_cube>
Drup: and they are meh
<mcc>
drup: ok, fair
<companion_cube>
because of retrocompatbility
<mcc>
The sense i got was that around the early 00s, java just made a big chunk of academia happy because anyone was paying attention to bytecode languages *at all*
<whitequark>
what.
* mcc
shrugs. in the commercial space.
<nicoo>
companion_cube: he thing which really nails it is that C#'s stdlib actually uses language features when it makes sense
<nicoo>
Unlike “I won't put useable generics in the stdblib” Java.
Hannibal_Smith has joined #ocaml
<companion_cube>
well java's stdlib was made before generics
<Drup>
eh
<Drup>
not most of it
<companion_cube>
also, I heard LINQ is nice
<companion_cube>
and their system of "await"
<Drup>
(LINQ also is an academia thing :p)
<nicoo>
s/he /The /
<Drup>
linq is an interesting thing, I have on my todo list a "ppx linq", still didn't bother to do it
<whitequark>
how would that work?
<companion_cube>
ouch
<companion_cube>
a full-fledged LINQ implementation is ambitious
<struktured>
whitequark: want your opinion. basically done with a fork of riakc that uses ppx stuff. I want to publish my changes. I see 3 paths. One is I make a true fork (separate repo) of riakc, call it riakc-ppx or something. The other possibility is I wait for orbitz to depend on your protobuf library, then I make another project (again say riakc-ppx) whic
<struktured>
h now depends on riakc. 3rd possibility is I try to usurp the main line of riakc and make it depend on ppx. Your thoughts?
<Drup>
whitequark: take a module as argument
<companion_cube>
the thing can plug into SQL, xml, ...
<companion_cube>
Drup: you can do it with GADTs too, mayb
<companion_cube>
e
<Drup>
companion_cube: meh
<companion_cube>
I had a kind of draft of this
<Drup>
yes I know
<companion_cube>
(it's in containers actually)
<Drup>
but it's not satisfying
<companion_cube>
why "meh" for GADTs but not ppx? -_-
<Drup>
the main strength of linq is that you use pretty much a normal syntax.
<companion_cube>
CCLinq is pretty much normal syntax, with |>
<whitequark>
struktured: riakc is orbitz' project? ask him, then
badkins has joined #ocaml
<struktured>
whitequark: yeah he's not around right on irc now. maybe I should just ask him on github and in the meantime do nothing.
<Drup>
companion_cube: let's just say it's not satisfying until you have implicits
<companion_cube>
but to me ppx isn't "normal syntax" either
<mcc>
Like I"m basically confused … *Which* expression has type 'a * 'b'? if i :TypeOf on the left paren which is highlighted it tells me string * Arg.spec * string
<companion_cube>
a * b * c is the type of (x,y,z) if x:a, y:b, z:c
<companion_cube>
not sure I understand the problem
matason has quit [Ping timeout: 256 seconds]
AlexRussia has joined #ocaml
<Drup>
mcc: wild guess, the "," before "(* No summary .."
<Drup>
it should be a ";"
<mcc>
drup: but i'm trying to make a tuple…?
<Drup>
and you should do a list.
<mcc>
OH
<mcc>
no, i… yeah.
<mcc>
urg, that , vs ; thing is messing me up so much. thanks :(
<Drup>
it's unfortunate that parentheses are not mandatory to build tuples.
<mcc>
does that ever actually come in handy?
<Drup>
like any syntax shortcut, it's handy when you are fluent
badkins has quit [Remote host closed the connection]
<mcc>
asking a different way, is there a real situation where it can be deployed without hurting code readability?
<mrvn>
Drup: use the revised syntax
<struktured>
mcc: its supposedly faster if you define the variants without them. type int_pair = Int of int * int is more efficient than Int of (int * int) or some I'm told due to an "unboxing" effect
<Drup>
struktured: that's not related :p
<mrvn>
struktured: type defionitions are special
<mcc>
struktured: yikes
<struktured>
Drup: I always tend to put the (..) around it so I can match the tuple easier..
<mrvn>
struktured: Tuple of 'a * 'b != Tuple of ('a * 'b)
<Drup>
struktured: but we were talking about the fact that "x , y" is as much a tuple as "(x, y)"
<struktured>
still confused when in the case of variants x,y != (x,y).. is it a correctness thing or optimization thing?
<Drup>
it's not a thing, it's the same
<Drup>
well, it's a syntax thing.
<mcc>
i understand it is the recommendation of the people here i not use Arg, but if i'm using Arg, do you suppose there's a way to use Arg.parse in such a way it will fail and print the error message if no arguments are provided?
<Drup>
companion_cube: what I have in mind would be of the form "begin%linq ... end" with normal ocaml syntax in the middle, reinterpreted. It would fake the fact that you don't have implicits
<Drup>
well, something like "begin[@linq List] ... end"
<orbitz>
struktured: pong
<companion_cube>
Drup: I find this really ugly
<companion_cube>
like, really ugly
<Drup>
companion_cube: bah.
<struktured>
orbitz: oh great. so did you say that manifesto I wrote whitequark earlier? trying to decided what do with this fork of mine
<struktured>
orbitz: say/see
<orbitz>
i never plan on depending on ppx stuff
<orbitz>
if that solves your dilemma
<struktured>
orbitz: ok then I need a separate project regardless. ideally though, you can depend on whitequarks protobuf, in which case I don't have to reproduce most of your api
<orbitz>
is there a particualr reason you care if riakc depends on pxx?
<orbitz>
ppx*
<orbitz>
from a user perspective there is nodistinction, so why do you need a separate project?
<struktured>
orbitz: there is an extended "cache" api which types the keys,values,indices,etc.. that requires ppx and would need to be separated out
<Drup>
companion_cube: your thing is nowhere near the expressivity of linq, you know, you can't have a sql translation.
<orbitz>
what do you mean by cache api?
<companion_cube>
Drup: I know
<companion_cube>
well everything could be polymorphic in some 'm
<companion_cube>
with a 'm monad argument
<hugomg>
since people are talking a lot about monads, how do Ocaml-ers handle them without the type classes? For example, the other day I wanted to make my decision-tree datatype into a monad but AFAIK there isn't something like Haskell's Control.Monad that gives me lots of operations for free (mapM, sequence, etc) once I implement bind and return.
bytbox has joined #ocaml
<companion_cube>
without implicits there's no good way to do it though
<Drup>
the point of my version would be to support that without any issue.
<orbitz>
hugomg: they have local imports or sepearte operators
<companion_cube>
hugomg: yeah it's hard
<Drup>
companion_cube: but anyway, there is a reason I didn't do it, I basically agree with you :p
<hugomg>
but does everyone have to reimplement monomorphic versions of sequence, forM, etc?
<orbitz>
struktured: why would that need to be part of riakc?
<companion_cube>
hugomg: you can write a functor that implements some of them
<companion_cube>
but things like Traversable aren't doable generically
<Drup>
please don't do that, it's horribly inefficient.
<struktured>
orbitz: it doesn't, really. hence the separate project possibility. my fork though, does use ppx on the internal riakc messages, but it doesn't have to at all, if riakc master got a little bit of ocaml 4.02+ face lift
<companion_cube>
hopefully Chambart will help :]
<Drup>
I don't think it would
<companion_cube>
why not?
<orbitz>
struktured: I would implement caching as a layer on top
<struktured>
orbitz: ok will do. but in the meantime I am going to use my own implementatoin of riakc, I don't think orbitiz/ master even builds yet with 4.02
<struktured>
orbitz: once I can depend on riakc as a library, I will delete all the duplicated code
<orbitz>
struktured: sounds good. I'm working bringing it up to date as well
<Drup>
companion_cube: defining traversable in term of bind like you did in I-don't-remember-which-module is inherently inefficient, even haskellers don't do that.
<struktured>
orbitz: cool. fwiw, I got rid of the bitstring campl4 dependency too, which was nice. (negative is it doesn't use the syntax extensions of course).
<companion_cube>
Drup: I don't have a choice
matason has joined #ocaml
<companion_cube>
of course if you can do better I'd be happy to have a patch.
<Drup>
I don't even remember why you did it.
<companion_cube>
because I use it?
<companion_cube>
to deal with lists of some monadic type
<Drup>
I mean, "where you used it"
<mcc>
is there ANYONE on this channel who actually likes camlp4
hausdorff has quit [Remote host closed the connection]
<whitequark>
yes, tell me their names
<mcc>
>_> oh dear
<companion_cube>
mostly a mix of delay (unit -> 'a) and n-ary constructors
Anarchos has joined #ocaml
<whitequark>
(I'm joking, obviously :)
Anarchos has quit [Client Quit]
<Drup>
mcc: someone expressed his taste for camlp4 and the revised syntax, the other day
<Drup>
but he also said he find Stream simple and nicely done, so, hum.
* companion_cube
pictures whitequark crushing the door of <some camlp4 fan> and throwing rocks at him
<Drup>
sorry, I have issues remembering names I can't pronounce :(
<companion_cube>
liking camlp4 *and* Stream
<companion_cube>
weird
<Drup>
mcc: otherwise, I think gasche finds camlp4 well done, and he's knowledgeable, so you can ask his opinion on the subject. Preferably by european day light hours.
AlexRussia is now known as Micro_AC_DC
manud has joined #ocaml
<mcc>
cool.
hugomg has quit [Ping timeout: 244 seconds]
samrat has joined #ocaml
Ptival has quit [Remote host closed the connection]
<Drup>
so, Daniel de Rauglaudre wrote the syntax extension system for OCaml, the OCaml PreProcessor and Pretty Printer
<Drup>
XL decided it would be nice to include it in the standard distribution
<Drup>
Daniel de Rauglaudre disagree strongly with that, and decided not to maintain anything in the standard distribution.
Thooms has joined #ocaml
<Drup>
after seeing that it would not be maintainde by the original author, the Cristal team give the task of rewriting camlp4 to a local phd student, Nicolas Pouillard
<Drup>
unfortunately, he was not really a caml programmer and more of a Haskellish guy.
hugomg has joined #ocaml
<adrien>
Drup: oh, cute heart!
hausdorff has joined #ocaml
<Drup>
he rewrote camlp4 and the rewrote got integrated in the standard distribution, Daniel de Rauglaudre then took back his version of camlp4 and distributed it alone, under the name "camlp5"
<whitequark>
oh god
<Drup>
did I mention that new camlp4 is not compatible with old camlp4
<Drup>
after that
<mcc>
(who is the Cristal team?)
<Drup>
Nicolas Pouillard finished his phd and .... completely left the ocaml community and went to Haskell, then Agda
<Drup>
making camlp4 equally unmaintaned.
manud has quit [Read error: Connection reset by peer]
<adrien>
you forgot that he co-made ocamlbuild too :P
<Drup>
adrien: calm, calm, each horror in its time.
<mcc>
ocamlbuild is nice…
<mcc>
… i think …
manud has joined #ocaml
<whitequark>
yay, someone else likes ocamlbuild
<Drup>
To wrap up the story
<Drup>
camlp4 got removed for the standard distribution in the last OCaml version.
<Drup>
from*
<adrien>
2014
<whitequark>
,,, and everything that implicitly depended on it broke
<struktured>
Drup: that is a sad story.
<Drup>
I know.
<mcc>
:(
<adrien>
we can manage non-monolithic sources
<MercurialAlchemi>
project politics
<adrien>
well
<struktured>
I actually think ocamlbuild is decent too.
<adrien>
it was nice to have a compiler that came with all the tools
<Drup>
and camlp4 is now un-maintained by the janestreet distribution guy, who sacrified himself for the cause.
<adrien>
but nowadays almost noone builds from sources
<whitequark>
"sacrificed himself for the cause" is a good way to describe it
<mcc>
What is the structure of the ocaml project? Cristal was mentioned, and everything is hosted by Inria which appears to be funded by the french government?
<Drup>
the organisation of the inria research is quite .. unique
<Drup>
we have team-projects with cute names
<Drup>
and they get reorganized and redefined every few years
<Drup>
and change name
<mcc>
oh
manud has quit [Read error: Connection reset by peer]
<Drup>
(this is why french researchers are *great* at finding names)
<adrien>
not specific to france nor to research
<MercurialAlchemi>
hence the puns
manud has joined #ocaml
<Drup>
adrien: research in another country don't function this way.
<Drup>
any other*
<Hannibal_Smith>
Am I wrong, or Inria is the most important software research organization in Europe, founded by the public?
<Drup>
mcc: and OCaml is the descendent of Caml, which is mostly the result of Xavier Leroy's research.
<Drup>
XL was in cristal
<Drup>
and cristal was renamed in gallium
<whitequark>
isn't the origin story of OCaml was that it was created to write Coq?
<mcc>
wait, really
<Drup>
whitequark: not exactly, in fact
<mcc>
so if caml is discontinued… why was ocaml a new language, why did they not just make it the new caml
<Drup>
Coq didn't really exist at the time
<Drup>
whitequark: but I must say, this part is a but unclear to me.
<Drup>
mcc: well, they changed a good amount of things
<mcc>
ok
<Drup>
mcc: funny part is that Caml Light contains currified constructors and a concurrent generational GC.
<mcc>
is the "categorical abstract" part of caml's name still relevant to ocaml's deisgn
<mcc>
drup: oh!
<Drup>
but XL though it was too complicated, and didn't keep it.
<mcc>
drup: I like both of those things!
<mcc>
…oh.
<whitequark>
hahaha
<Drup>
half the ocaml community is actively eating their fingers about these (and a few others) decisions.
<Drup>
mcc: yes, the "categorical abstract machine" is still relevant
<adrien>
apparently pretty much everyone found the concurrent GC too complicated
<Drup>
it's about the runtime system.
<mcc>
ok.
<adrien>
and currified constructors is not an actual hindrance
<Drup>
mcc: so, basically, OCaml's runtime system is something XL designed during his PHD, and it pretty much didn't change since.
<mcc>
adrien: I'd like it, though. is there a reason ocaml can't just add that?
<mcc>
drup: i see.
<adrien>
benefit/cost
<mcc>
i mean, what is the cost to changing this element? would it require other changes in the syntax?
<mcc>
or is it actually just that it is hard to implement…?
<Drup>
mcc: the funny part is that javascript with all the JITs is barely beating a 30 year old interpretor built by a PHD in 3 year.
<Drup>
:>
<mcc>
drup: that is not so surprising…
<MercurialAlchemi>
that's a bit unfair considering the difference in semantics
<adrien>
and JS as a language was built in 2 weeks
<Drup>
MercurialAlchemi: I don't think it's unfair, it drives the point that you should think about the semantic when you want efficiency.
<mcc>
there are a lot of things i like about js's semantics… maybe if he had had 3 weeks, i would actually like the language…
* whitequark
likes approximately nothing about js semantics
<mcc>
thank you
<mcc>
hah, references to Modula on the second page
<Drup>
to comes back to ocamlbuild
<MercurialAlchemi>
Drup: well, if you look at Ruby or Python they're not exactly speed demons either
<Drup>
I dislike the efficiency, the implementation, the code I need to write.
<Drup>
the semantic of the rules too.
<Drup>
it's the wrong way around, top bottom instead of bottom top
<companion_cube>
MercurialAlchemi: lua is
<Drup>
MercurialAlchemi: and their semantic is .. wait for it ... BLEUARB
<Drup>
:D
<MercurialAlchemi>
hehe
<whitequark>
ruby's core semantics is a decent smalltalk clone
<MercurialAlchemi>
I'm just saying that it's not uncommon
<whitequark>
the stdlib is hideous though
govg has joined #ocaml
<nicoo>
Drup: “Java's established now: it makes more sense to start giving Java programmers tools that let them program the way they think” -> It is me or does it sound like “you must make languages too simple to be useful in order for them to gain traction”
<Drup>
mcc: other historical questions ? n_n
expo873 has quit [Quit: Connection closed for inactivity]
mcclurmc has joined #ocaml
<Drup>
ah, last fun fact about Caml Light
<Drup>
it's still used in education in france's Classe Préparatoire, beside the fact that basically nobody even looked at it for the past 10 years, at least. <3
<mcc>
nicoo: I agree with "you must make languages too simple to be useful in order for them to grain traction" as a general proposition, i think
<MercurialAlchemi>
no shit
<whitequark>
pfff, when I was in high school, they still taught people using Turbo C
<MercurialAlchemi>
well, I guess it has an advantage
<whitequark>
~15 years, I think?
Micro_AC_DC is now known as AlexRussia
<Drup>
Classe Préparatoire have the choice
<Drup>
either Caml Light or Pascal.
<Drup>
:D
<mcc>
drup: i think that's what i was wondering! except… opam is or is not part of Inria/the standard distribution…?
<MercurialAlchemi>
as a teacher, you don't need to actually make new course materials because you're changing tech
<Drup>
and XL said "yeah, ok, why not, I have to talk about it at inria"
q66[lap] has joined #ocaml
<Drup>
then it starting doing rounds in the inria administration
<Drup>
JST said "ok, we ask other people too"
<Drup>
then Anil arrived and said "yes, I take it, right now, we do OCamllabs"
<Drup>
TADA, OCamllabs was born, and inria is still not funding OCaml.
<mcc>
i see
<whitequark>
it's like watching a train crash in slow motion
_JokerDoom has joined #ocaml
hausdorff has joined #ocaml
<mcc>
so for a moment there, i was every happy for europe that unlike the united states the government was actually able to effectively fund scientific research
<mcc>
maybe not tho
<Leonidas>
maybe it is just INRIA
<Drup>
the various places in europe I have been are mostly ok
<Leonidas>
the EU founded PyPy :-)
<Drup>
france, on the other hand ...
__JokerDoom has joined #ocaml
<MercurialAlchemi>
so INRIA people maintain OCaml with JST money outside of INRIA?
<Drup>
not INRIA people, no.
<Drup>
(ocamllabs is cambridge, btw)
<adrien>
Drup: "fund", not "found"
<Leonidas>
really looking forward for the results out of ocamllabs
<Drup>
adrien: I know, whitequark fixed it already :D
<Drup>
mcc: there is another story about the QPL thing.
_JokerDoom has quit [Ping timeout: 264 seconds]
sheijk has joined #ocaml
manud has quit [Quit: Be back later ...]
<mcc>
oh my
<mcc>
ocamllabs is cambridge? that's interesting
<whitequark>
why do you find it interesting?
manud has joined #ocaml
<mcc>
because i know a lot of people there and was thinking about applying with a company there at one point.
<mcc>
however everyone i know moved out. i think it got expensive
<Drup>
so, OCaml is not free software, you can't fork it, except when you are member of the OCaml consortium (in this case you have a version of the OCaml compiler under BSD, I think).
<Drup>
the reason is that, back in the Caml Light days
<adrien>
QPL is free software
<Drup>
let's not debate about this point, the bottom line is that you can't fork it.
<adrien>
it is free software, there's no debate
<sheijk>
you can. it's just very inconvenient to distribute
<whitequark>
oh?
<Drup>
MoscowML was created, which is basically an aggressive fork of Caml Light without acknowledgement.
<MercurialAlchemi>
never heard of it
<Drup>
and the cristal team panicked, and decided to use the QPL.
<mcc>
ugh
<mcc>
do you think they would ever reconsider this?
<Drup>
I doubt it
<Drup>
it's not really much of a problem in practice, it's not really enforced
<mcc>
ok
<Drup>
especially since opam
thomasga has joined #ocaml
<adrien>
for many things you need to remember the codebase is 20 years-old
<adrien>
and that things _can_ be reconsidered
<MercurialAlchemi>
I'm working on a 15 yo codebase, I've reconsidered away a number of things
<nicoo>
Drup: Yes. AFAIK, release tarballs of MetaOCaml are in violation of the QPL, for instance
<MercurialAlchemi>
but OCaml's can't be that terrible
<nicoo>
MercurialAlchemi: Ahah
<Drup>
nicoo: no, they are not.
<Drup>
so, you have the right to distribute *patches* on the compiler
<Drup>
and MetaOCaml is distributed like that.
<nicoo>
Drup: Ah, yes, they have a vanilla compiler and apply patches at compile-time
<nicoo>
True
<Drup>
yep.
<rom1504>
didn't know ocaml is not free software
<dmbaturin>
gnuplot is distributed under similar terms.
<adrien>
it is
<Drup>
MercurialAlchemi: "I've reconsidered away", I like this reformulation of "burning".
<rom1504>
so it's a bit like C# then
<adrien>
free software
<adrien>
Drup: congrats
<rom1504>
ok
<Drup>
adrien: :D
<adrien>
the license is 90s
<dmbaturin>
Also, don't mix the language and implementations. ;)
<adrien>
it has many quirks but that's it
<MercurialAlchemi>
Drup: isn't it
<Drup>
mcc: I hope this historic interlude didn't scare you off OCaml.
<MercurialAlchemi>
or "nobody knows how this code work, so if we patch it, we'll probably get a regression - let's just refactor it isntead"
struktured has joined #ocaml
<companion_cube>
dmbaturin: unless the language has only one implementation
pgomes has left #ocaml ["Leaving"]
<mcc>
it is useful to know.
<dmbaturin>
companion_cube: Well, it's never late to make another one.
<struktured>
whitequark: oh oops. I thought the guy running th elogs would be a mod
<whitequark>
Drup: /me in your client is broken
<adrien>
it's already in the topic
<Drup>
It's not :O
<whitequark>
it sends a PRIVMSG intead of CTCP ACTION
<whitequark>
and it shows as /me for everyone
<whitequark>
rather than * Drup whatever
<adrien>
:D
<Drup>
that's ... interesting.
<Drup>
It shows as all the other person doing /me in my client
<adrien>
as he said: broken :P
<whitequark>
Drup: two bugs compensating each other
<companion_cube>
dmbaturin: it's a huge undertaking!
<whitequark>
as my math teacher used to say, if the result is right, you probably have an even number of errors
<Drup>
whitequark: what surprises me the most is that you are the first one to tell me. :<
<MercurialAlchemi>
That's a good one
<mcc>
drup also does not reply to ctcp version. that's interesting…
<adrien>
Drup: /lastlog says it isn't new :P
<MercurialAlchemi>
Drup: I'd seen it but just assumed you were manually emulating /me due to a lack of support by your client
<whitequark>
I find it slightly disturbing that /ctcp finger exists
* companion_cube
surprised
<mrvn>
whitequark: only if your client implements that
<Drup>
adrien: did my client ever did it correctly ?
<whitequark>
mrvn: no, you didn't get it
<Drup>
huum, I wonder if the issue is on the bouncer side.
<adrien>
Drup: until at least 24/10/2014
<adrien>
broke on 27/10/2014 at latest
<dmbaturin>
Drup: I thought you are using non-command /me intentionally for some weird kind of self-expression. ;)
<whitequark>
I was just too lazy to mention it
<adrien>
/me
<mcc>
/say /me
<whitequark>
an IRC quine
<whitequark>
well, technically, any non-command is one
<companion_cube>
/me doesn't know what whitequark talks about
<mcc>
also /say /me is not a quine because i had to type /say /say /me to get htat.
* mcc
has working command line args and is trying to decide whether to tackle a package loading system or TCO next… maybe i could do an interactive mode, i guess.
willy__ has left #ocaml ["Leaving"]
octachron has quit [Quit: Leaving]
hausdorff has quit [Remote host closed the connection]
samrat has quit [Quit: Computer has gone to sleep.]
<mcc>
mrvn: is there a reason not to just do boxes 0,1 in a loop?
<Drup>
mcc: my opinion would be to clean up the core part before moving on, but I understand how that sounds boring :p
tane has quit [Quit: Verlassend]
<mcc>
drup: well, actually what i am thinking is get a package system in place, then use it to load a bunch of builtin methods
Submarine has quit [Remote host closed the connection]
<Drup>
sure, that's orthogonal
<mcc>
which will help in doing core things maybe
<Drup>
I don't see how having a package system would make you have a proper grammar.
hnrgrgr_ is now known as hnrgrgr
MercurialAlchemi has quit [Ping timeout: 264 seconds]
<companion_cube>
so, batteries' PR merging spree tonight
<companion_cube>
apparently
<mcc>
drup: the grammar may wind up being in a external library, inside the package system :)
matason has quit [Ping timeout: 265 seconds]
mcclurmc has joined #ocaml
NoNNaN has quit [Ping timeout: 250 seconds]
badkins has joined #ocaml
<Drup>
mcc: not sure how would that work without bootstraping the compiler
mcclurmc has quit [Ping timeout: 244 seconds]
<mcc>
well, there is no compiler yet. but when there is, i could run build-time support libraries in the interpreter, have them spit out ASTs, feed those to the compiler
Submarine has joined #ocaml
badkins has quit [Remote host closed the connection]
NoNNaN has joined #ocaml
Thooms has quit [Quit: WeeChat 1.0.1]
__JokerDoom has quit [Quit: Leaving]
* Drup
is wondering if it works now.
<Drup>
whitequark: ^
<Drup>
apparently it does
<whitequark>
it does
thomasga has quit [Quit: Leaving.]
<Drup>
apparently, it was a plugin doing dubious rewriting.
<Drup>
mcc: you need a serialisation format for the language then. In both cases you will need to parse something anyway
<companion_cube>
bah, s-expressions
q66[lap] has quit [Read error: Connection reset by peer]
q66[lap] has joined #ocaml
struktured has quit [Ping timeout: 258 seconds]
badkins has joined #ocaml
kakadu has quit [Quit: Konversation terminated!]
name2 has joined #ocaml
libertas has quit [Quit: Lost terminal]
<name2>
what does " let rec expr: expr -> .. " mean in ocaml
<Drup>
that whoever wrote this is trying very hard to confuse the reader :D
<srax>
:D
<Drup>
it defines a function, named 'expr' that is taking as argument a first element, of type "expr"