moei has quit [Read error: Connection reset by peer]
moei has joined #ocaml
Robdor has quit [Quit: Ping timeout (120 seconds)]
Robdor has joined #ocaml
ratschance has quit [Remote host closed the connection]
ratschance has joined #ocaml
donviszneki has quit [Ping timeout: 260 seconds]
tarptaeya has joined #ocaml
malina has joined #ocaml
tarptaeya has quit [Ping timeout: 260 seconds]
tarptaeya has joined #ocaml
argent_smith has joined #ocaml
TarVanimelde has joined #ocaml
<ZirconiumX>
So, I find myself missing `constexpr` functions in C++ to generate a table at compile time. Any suggestions?
<ZirconiumX>
I have an algorithm for generating the JPEG zig-zag pattern, but I don't know how to make the compiler generate that table
<ZirconiumX>
Unless I'm blind and it's just a plain function call
jaar has joined #ocaml
malina has quit [Ping timeout: 260 seconds]
<octachron>
Why do you need the table at compile time?
<ZirconiumX>
It's used as an index converter in, and it's nontrivial to generate in a function, and I would rather not go through the hassle of `ref None`
<octachron>
In other words, you can generate the table at runtime
<octachron>
since its cost should be negligible compared to the jpeg DCT
<ZirconiumX>
Guess there's only one way to find out
zolk3ri has joined #ocaml
letoh has quit [Ping timeout: 260 seconds]
<flux[m]>
ZirconiumX: the practical solution is to generate an .ml file in your build system
<flux[m]>
the cool solution is to use meta-ocaml maybe?
<octachron>
ZirconiumX, this seems correct? Except that the direction/move boolean are redundant
larhat has joined #ocaml
<ZirconiumX>
Good point, yeah
<ZirconiumX>
I do think the direction is useful
mfp has joined #ocaml
dhil has joined #ocaml
TarVanimelde has quit [Quit: TarVanimelde]
al-damiri has joined #ocaml
donviszneki has joined #ocaml
donviszneki has quit [Ping timeout: 268 seconds]
wilfredh has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 276 seconds]
malina has joined #ocaml
nephanth has joined #ocaml
ziyourenxiang has joined #ocaml
wilfredh has quit [Ping timeout: 265 seconds]
johnelse1 is now known as johnelse
wilfredh has joined #ocaml
<wilfredh>
I can save a reference to the > function by writing: let x = (>)
<wilfredh>
is there an equivalent for ** ?
<wilfredh>
(**) is a comment
dakk has joined #ocaml
<octachron>
wilfredh, ( ** )
<wilfredh>
aha, thanks :)
MercurialAlchemi has joined #ocaml
silver has joined #ocaml
sagotch has quit [Ping timeout: 268 seconds]
mk9 has joined #ocaml
mk9 has quit [Client Quit]
mk9 has joined #ocaml
mk9_ has joined #ocaml
mk9 has quit [Ping timeout: 240 seconds]
mk9_ has quit [Read error: Connection reset by peer]
mk9 has joined #ocaml
jim7j1ajh has joined #ocaml
jimt has quit [Ping timeout: 256 seconds]
jao has joined #ocaml
freyr69 has quit [Ping timeout: 248 seconds]
jim7j1ajh is now known as jimt
troydm has quit [Quit: What is Hope? That all of your wishes and all of your dreams come true? To turn back time because things were not supposed to happen like that (C) Rau Le Creuset]
troydm has joined #ocaml
tarptaeya has quit [Read error: Connection reset by peer]
tarptaeya has joined #ocaml
<flux[m]>
wilfredh: actually that's one reason why some (most?) prefer to use ie. ( + ), so the ** case doesn't stick out.
Mercuria1Alchemi has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 260 seconds]
<discord3>
<Christophe> Checking how they wrote it in the Pervasoves page (like that), I accidentally learned that the unary operators with a tilde have highest precedence
<discord3>
<Christophe> abs -4 (* type error *) and abs ~-4 (* 4 *)
<discord3>
<Christophe> My life has been a lie
<flux[m]>
whaat? the missing whitespace -operator doesn't have the highest precedence?
<flux[m]>
;-)
<thizanne>
christophe: that's not really a precedence issue, that's a unary/binary issue
<thizanne>
- isn't parsed as an unary operator by default, so when you write abs -4 it's expected to be binary
jaar has quit [Remote host closed the connection]
<thizanne>
~- is unary only, so there is no ambiguity
jaar has joined #ocaml
<discord3>
<Christophe> yes, I didn't necessarily express myself well here
<discord3>
<Christophe> I learned that there is the ~- version that has the highest precedence, higher that function application, and that the common "gotcha" of abs -4 being a type error can be corrected with the tilde version
MercurialAlchemi has joined #ocaml
<thizanne>
it's not that the "precedence" is higher than application function, it's that there is no other possibility anyway to parse abs ~- 4
<thizanne>
as opposed to, say, abs 1 + 3 where you could parse as abs (1 + 3) or (abs 1) + 3
<flux[m]>
sure there is, "Error: expected binary operator, encountered ~-" :-)
<thizanne>
and that's where precedence happens: function application has priority so it's parsed as the latter
larhat has quit [Quit: Leaving.]
Mercuria1Alchemi has quit [Ping timeout: 260 seconds]
<thizanne>
but you don't need to priorise things when there is no choice to be made
pierpal has quit [Quit: Poof]
pierpal has joined #ocaml
<discord3>
<Christophe> Hum, makes sens, I really need to pull myself together
sagotch has joined #ocaml
dakk has quit [Remote host closed the connection]
dakk has joined #ocaml
<discord3>
<Christophe> Yes got it, it can be useful in cases like f 5 ~-3, though I don't imagine cases where it would save a lot of characters compared to parentheses
donviszneki has joined #ocaml
<reynir>
ooh, didn't know (~-) existed
donviszneki has quit [Ping timeout: 248 seconds]
letoh has joined #ocaml
<thizanne>
I actually distinctly remember using it once
<thizanne>
but I don't remember why
wilfredh has quit [Ping timeout: 276 seconds]
dhil has quit [Ping timeout: 260 seconds]
Haudegen has quit [Remote host closed the connection]
gareppa has joined #ocaml
gareppa has quit [Client Quit]
MercurialAlchemi has quit [Ping timeout: 260 seconds]
pierpal has quit [Remote host closed the connection]
_andre has joined #ocaml
mbuf has quit [Quit: Leaving]
gtrak has quit [Ping timeout: 268 seconds]
gtrak has joined #ocaml
FreeBirdLjj has joined #ocaml
ziyourenxiang has quit [Quit: Leaving]
<discord3>
<Bluddy> companion_cube: the read barrier is only for mutable values, and it's very cheap and can be inlined
<companion_cube>
well, what if I have tons of mutable fields? :p
<companion_cube>
clearly I'll have to benchmark …
ziyourenxiang has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 248 seconds]
Haudegen has joined #ocaml
<discord3>
<Bluddy> It can also be eliminated for unboxed types, and for boxed types, there's a good chance cache access will dominate on aggregate. You'd lose some performance on mutable boxed fields that are already in cache.
<companion_cube>
oh, so at least it'll not penalize stuff like vectors' size field
<companion_cube>
but I suppose array assignment will… -_-
<discord3>
<Bluddy> yeah there'd be a stronger push for a specialized array type for ints and such
<discord3>
<Bluddy> except for places that the type parameter can be deduced
<discord3>
<Bluddy> we already need a specialized int array type anyway for GC
<companion_cube>
no but arrays of boxed types
<companion_cube>
where we already pay some stupid cost for floats -_-
<discord3>
<Bluddy> wait, no -- we don't pay the cost for floats
gtrak has quit [Ping timeout: 260 seconds]
<companion_cube>
right now we do
<companion_cube>
afaik there are dynamic checks for all array operations
<companion_cube>
(unless you know it's not float)
<discord3>
<Bluddy> right
<discord3>
<Bluddy> yeah arrays of boxed types will get a penalty. but that penalty is small
<discord3>
<Bluddy> though it's per-access
<discord3>
<Bluddy> if you loop through an array, cache costs will dominate
<companion_cube>
good chances that multicore will make my code slower, not faster /o\
gtrak has joined #ocaml
<discord3>
<Bluddy> yes
<discord3>
<Bluddy> everything has a cost
<discord3>
<Bluddy> a multicore GC is insanely more complicated
<discord3>
<Bluddy> but flambda should help -- the more code is specialized, the less we need to worry about violating the invariants of the multicore model
<companion_cube>
I wonder, will there still be a possibility to use the normal GC?
<companion_cube>
(otherwise all of my code will become slower, that kind of sucks)
<discord3>
<Bluddy> Looks like initially they're planning to keep it that way
<discord3>
<Bluddy> I don't know if it's doable long-term
<discord3>
<Bluddy> In haskell you choose which GC you want
<companion_cube>
or I can learn rust, too :p
<discord3>
<Bluddy> The cost is just shifted elsewhere
<Drup>
It's far too early to really worry about this. Maybe we can start (not) panicking when we can make actual measurement ?
<ia0>
companion_cube> or I can learn rust, too :p <= sounds like a decent idea :-)
dhil has joined #ocaml
<companion_cube>
yeah I know, it's just that I know I'll miss merlin…
<companion_cube>
Drup: indeed, but a read barrier does sound awful for some of my code
<companion_cube>
(the stuff where all structures are vec or hashtables… you know)
<Enjolras>
companion_cube: well, rust also has some kind of "barrier"
<companion_cube>
a read barrier, really? :o
<Drup>
companion_cube: but you don't even know how it'll work yet .. u_u'
<Enjolras>
no but if you are going to share mutable values accross thread you need a ock
<Enjolras>
or at least an atomic
<companion_cube>
Enjolras: I'm talking about single threaded stuff, ofc
<Drup>
maybe the read barrier will only be on the shared heap, would that really be so bad? Probably not
<companion_cube>
Drup: will there be a major heap per domain? I missed that
<discord3>
<Bluddy> no minor heap per domain
<Enjolras>
right. Well the good thing with rust is that the cost is opt-in
<Enjolras>
but imo it's far too early to be concerned about the multicore runtime
<Enjolras>
i will worry in 2 years
<companion_cube>
that's true
<Drup>
^
<Drup>
companion_cube: stop panicking
<companion_cube>
I have time, I'm just a bit pessimistic
<discord3>
<Bluddy> companion_cube: but you'll be able to spawn a couple of threads to do the work that you do in vectors effortlessly, and gain performance.
<companion_cube>
nope
<companion_cube>
code is not automatically parallelizable, Bluddy… please
<Enjolras>
haha
<discord3>
<Bluddy> parmap with minimal cost
<Enjolras>
parallelizing stuffs is never as easy as it sounds
<discord3>
<Bluddy> I didn't say automatically
<Drup>
Yeah right, and I'm the queen of england
<Enjolras>
often, what you get is a 3X ...
<Enjolras>
... slow down
<companion_cube>
parallelizing the kind of stuff I'm interested in is a research domain by itself, thanks but no thanks
<discord3>
<Bluddy> Fine. I'm not naively suggesting it. But if you find a parallelizable portion, it's easy to take advantage of it.
<discord3>
<Bluddy> e.g. you need to loop over a vector
<companion_cube>
it's still funny that most parallelizable algos are numerical code, which can alraeady release the lock when it calls lapack functions
<Enjolras>
i would not qualify parallell programming as "easy"
<companion_cube>
so multicore is mostly useless :/
<Enjolras>
data parallelism with proper abstraction and work stealing yeah not too hard
<companion_cube>
Bluddy: I need to loop over a vector, mutating a huge structure on every step… good luck speeding that up if you have to lock the structure
<discord3>
<Bluddy> simple algorithms like parmap aren't hard
<Enjolras>
but that's very specific usecase similar to parmap and it's not super widespread
<Enjolras>
but that's niche
<discord3>
<Bluddy> companion_cube: ok, that's not parallelizable
<companion_cube>
"yeah let's write a parallel SAT solver, it must be simple… oh ok no one has ever succeeded"
<discord3>
<Bluddy> what i'm saying is, you don't need to parallelize the whole algorithm
<discord3>
<Bluddy> you can find chunks where the work can be split up
<companion_cube>
Drup: I think the ephemerins had a cost on the GC already, btw
<Enjolras>
I use rust a lot and i barely use threads
<companion_cube>
what if my whole code is this kind of algos?
<discord3>
<Bluddy> then yes, you're not going to benefit from multicore
<companion_cube>
exactly
<discord3>
<Bluddy> ephemerons are a real pain for multicore
<Enjolras>
the only way i use thread is because "lwt" like lib has a way to schedule futures to a threadpool
<companion_cube>
they're also a pain for the normal GC, afaict
<Enjolras>
but that has high overhead
<discord3>
<Bluddy> they had to introduce another stage in the GC just to deal with ephemerons
<discord3>
<Bluddy> multicore GC
<discord3>
<Bluddy> and I'm not sure it even handles all the cases yet
<flux[m]>
parallelizing is often simple. the difficulty is in getting >100% out of it, though :-)
<companion_cube>
(I htink the GC got slower for weak tables, even without using ephemerons :()
<Drup>
Tbf, I'm still not sure what are the use cases for ephemerons
<Drup>
I suspect the only users are employed by the CEA
<discord3>
<Bluddy> CEA?
<Enjolras>
the only case i used them is the advertized cache usecase
<Enjolras>
it's nice, but i'm not sure it deserves to be in the languages
<Drup>
Bluddy: French research adgency. Employs the frama-c people (more or less), along others
<discord3>
<Bluddy> thanks
donviszneki has joined #ocaml
<Enjolras>
I blame go for the multicore hype. They made it sound like you can have your cake and eat it, for free.
<Enjolras>
but this kind of M:N threads is not working as well as they pretend beyond network programming
<discord3>
<Bluddy> no. multicore was really hyped in the really 00s
<discord3>
<Bluddy> and it's the only way we have to advance since cores aren't getting any faster
<companion_cube>
the funny thing is that multicore won't help adoption, because apparently Reason is going to be much more popular
<discord3>
<Bluddy> and then we found out that it's really hard to do multicore
<companion_cube>
and reason users use node.js !! :D
<Enjolras>
and even with network programming i'm not convinced it has better performance per core than a pure coroutine approach
<discord3>
<Bluddy> It depends
<Enjolras>
Bluddy: people had already found out it was really had to do multicore in the 00's
<discord3>
<Bluddy> no, it wasn't popular knowledge
<Enjolras>
i remember when all the OS went the "fiber" way, then all fall back because it was not working
<discord3>
<Bluddy> companion_cube: the effect system is another incompatibility with node.js
<companion_cube>
dragonfly? :]
<Enjolras>
companion_cube: pretty much all OS.
<companion_cube>
Bluddy: well they don't use the native backend, so it'll just be the old time users
<discord3>
<Bluddy> reason is hoping by the time multicore/effects land, we'll have compilation to webassembly
donviszneki has quit [Ping timeout: 260 seconds]
<Enjolras>
Bluddy: i do agree the only way to scale is to distribute work
<Enjolras>
i'm just not convinced this required shared memory
<companion_cube>
but webassembly won't have a multicore GC
<companion_cube>
… or will it? :/
cryptocat1094 has joined #ocaml
<discord3>
<Bluddy> enjolras: right and the question is, do you want to use the memory bus
<Enjolras>
companion_cube: it will
<Enjolras>
soon(tm)
<discord3>
<Bluddy> ie shared memory
<companion_cube>
anyway, it's all driven by people who do networking, ofc they compile to node.js instead of using the native backend
twopoint718 has joined #ocaml
twopoint718 has joined #ocaml
twopoint718 has quit [Changing host]
<discord3>
<Bluddy> Enjolras: sharding can work under some circumstances, but in other circumstances, it's not feasible
<Enjolras>
companion_cube: really ? people are compiling reason to node.js to run backend stuffs ?
<Enjolras>
that's just crazy
<companion_cube>
well I think the default toolchain for reason (+BS) is based on node
<companion_cube>
they all compile to js anyway…
<discord3>
<Bluddy> they have BS-native now
<companion_cube>
reason's syntax even has custom stuff for BS, afaik
<discord3>
<Bluddy> yes. a little bit
<discord3>
<Bluddy> BS-native bundles the whole ocaml compiler and compiles everything to native ocaml
<discord3>
<Bluddy> but I believe it can only do so if you have no JS dependencies
<discord3>
<Bluddy> which of course makes sense
<Enjolras>
companion_cube: this is just crazy.
<Enjolras>
wow
<discord3>
<Bluddy> check out reprocessing https://github.com/Schmavery/reprocessing, which they use to build games for web, then compile using ocaml down to ios and android
<rks`>
« BS-native » :DDD
FreeBirdLjj has joined #ocaml
cbot has joined #ocaml
<Enjolras>
the abbrevation in the ecosystems are nice latelly. "Bullshit-native", "http As fuck"
<Armael>
>BS-native
<Armael>
what
<Armael>
like, ocaml but compiled to javascript but compiled to machine code
<Drup>
it changes the semantics. You can't compile some libraries
<discord3>
<Bluddy> such as?
<Drup>
Core.
<Enjolras>
anything using Obj afaik
<discord3>
<Bluddy> doesn't Core have native dependencies?
<rks`>
that's not a problem, just write a .js stubs file
<cryptocat1094>
Enjolras: That sounds mostly compatible to me.
<discord3>
<Bluddy> I see. Well Obj isn't going to scale to other backends
<Enjolras>
cryptocat1094: well, yes, but that's not getting better
<discord3>
<Bluddy> The first-class FFI is obviously to JS
<Drup>
native dependencies are not the issue
<Enjolras>
and, think about it : you cannot use the same merlin or tooling, or even cmi
<cryptocat1094>
Enjolras: That's not too good.
silver_ has joined #ocaml
<Drup>
Bluddy: Obj *should* scale to other backends. Obj talk about the representation of objects in OCaml, not about anything from the target plateform
<discord3>
<Bluddy> Hmmm...
<Drup>
In particular, all Obj tricks are valid in jso_of_ocaml
silver has quit [Read error: Connection reset by peer]
<discord3>
<Bluddy> OK I guess that makes sense.
<Drup>
(if they are valid in native, ofc)
<Enjolras>
cryptocat1094: it's not a lost cause but it's definitely annoying
<discord3>
<Bluddy> So Obj assumes acompatibility up to the lambda level
<discord3>
<Bluddy> which BS doesn't have
<discord3>
<Bluddy> Well, we warned people not to use Obj, so there :p
<Drup>
There are other various subtle changes here and there. The point is that it's really not the same semantics, and the only justification for those changes is that "the code is more readable"
<discord3>
<Bluddy> I believe the other things are syntactic sugar
<companion_cube>
not using merlin… why would anyone want that
<discord3>
<Bluddy> They're using merlin... for now
<Drup>
Bluddy: No, that's a bullshit argument. Obj has valid uses, and many of them are garanteed by the semantics of OCaml
<Enjolras>
reason uses merlin, via Languages Server
demonimin has joined #ocaml
<discord3>
<Bluddy> Drup: I don't know about that. Code that uses Obj is not guaranteed to be compatible going forward.
<Enjolras>
Drup: i'm not sure about that though. I don't think even ocaml should adhere to the "semantic" of Obj
<Drup>
Ok, to give you a comparison that will make sense, it's like having Java code that talks about the JVM representation
<Drup>
Yes, it's not recommended, and you shouldn't use it, and still, Spring exists.
<Enjolras>
If ocaml team decided to change and break value representation which would break Obj next release
<Enjolras>
i would find this perfectly fair
<discord3>
<Bluddy> A good example of this was Coq's recent inability to use Flambda due to heavy use of Obj
<Enjolras>
eg i don't think the float array hack is part of the "semantic" of the language
<Enjolras>
it's more like implementation detail
sgnb has joined #ocaml
<Enjolras>
Drup: are you willing to take java as an example of good practices ? :p
<Drup>
I never said all uses of Obj that works are good ones
<companion_cube>
right, the language would still work with arrays of boxed floats
demonimin has quit [Remote host closed the connection]
<discord3>
<Bluddy> There's a deeper question lurking here, which is, what is a language defined by?
<discord3>
<Bluddy> The most stable surface of a language is... the syntax? Semantics?
<discord3>
<Bluddy> In reality, Reason is least likely to mess with the typechecker, because that takes the most effort
<Enjolras>
both ?
<discord3>
<Bluddy> and the typechecker determines semantics
<discord3>
<Bluddy> within a certain margin
<Enjolras>
hm. A very lose margin
<discord3>
<Bluddy> well, if you just change ocaml's syntax, that doesn't seem like a new language
<Enjolras>
float -> float -> float
<Enjolras>
that gives you very very loose information on the semantic of this functin
shinnya has joined #ocaml
<discord3>
<Bluddy> true, but the semantics sit behind the typechecker for the most part, and since modifying the typechecker is so hard, you don't get to create whatever semantics you want either
<discord3>
<Bluddy> just explaining where Reason is
gtrak has quit [Ping timeout: 255 seconds]
bezirg has quit [Quit: Leaving.]
bezirg has joined #ocaml
<companion_cube>
reason is just ocaml, but reason + bs + node.js starts being a new language imho
<companion_cube>
(nothing is common anymore except the typechecker)
gtrak has joined #ocaml
mbuf has joined #ocaml
donviszneki has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
<Drup>
(and that might not last :p)
FreeBirdLjj has joined #ocaml
<discord3>
<Bluddy> well the semantics are still the same also. the data representation isn't
<discord3>
<Bluddy> but yeah, it may not last
<discord3>
<Bluddy> and if we adopt effects, it'll immediately diverge
<discord3>
<Bluddy> effects require a unique runtime
<discord3>
<Bluddy> which you can't really do with node
<discord3>
<Bluddy> multicore also, but most code probably won't use multicore stuff
donviszneki has quit [Ping timeout: 260 seconds]
demonimin has joined #ocaml
<discord3>
<rizo> Maybe not multicore but effects will certainly be used a lot (eventually,)
bezirg has quit [Quit: Leaving.]
demonimin has quit [Remote host closed the connection]
<discord3>
<Bluddy> yeah if effects are integrated, they'll immediately be used
<discord3>
<Bluddy> which is why divergence will happen immediately
<discord3>
<Bluddy> but there's a (justified, IMO) effort to only integrate effects once they're typed
<discord3>
<Bluddy> so it could actually take a really long time
<discord3>
<Bluddy> ie much longer than multicore itself
artart78 has quit [Quit: WeeChat 2.1]
artart78 has joined #ocaml
<flux[m]>
typed effects would be so very sweet. basically OCaml 5.0.
<discord3>
<Christophe> What would it mean? Effectful functions would carry the effects they do in their type?
<flux[m]>
yes
<discord3>
<Christophe> Oh nice :D
<discord3>
<Bluddy> it's like haskell, but better
demonimin has joined #ocaml
<discord3>
<Bluddy> no need for monads to carry out effects
<discord3>
<rizo> It will also change the way we do IO and work with monads for example.
<discord3>
<rizo> Exactly, monads are not required.
<discord3>
<Bluddy> in the meantime, who wants to help us build stdlib-v2?
<discord3>
<rizo> Bluddy: let me outline the scope of the work first 😃
demonimin has quit [Remote host closed the connection]
<discord3>
<Bluddy> yeah, but now that we have 'namespacing' (stdlib), we want to integrate these improvements into the proper stdlib using versioning. So initially you'd use open Stdlib.V2 or some such thing, and immediately get access to the kind of functionality Containers et al has been developing.
<flux[m]>
I'm not sure if a new stdlib is really what is needed at this point. maybe if it was built on top of typed effects from the start ;-).
<discord3>
<Christophe> Khady : I'm not implicated in it but the idea was to have a community design :)
<flux[m]>
what namespacing?
<dinosaure>
Ocsigen_baselib
<discord3>
<rizo> So many stds, surely we need yet another one 😃
<Drup>
dinosaure: ohno you didn't
<discord3>
<Bluddy> exactly. we want a community design
<discord3>
<Bluddy> this will help attract new people
<discord3>
<Bluddy> because one of the friction points is the current stdlib
<discord3>
<Bluddy> and full backwards compatibility has been a limitation in the past
<discord3>
<rizo> Well, the idea is to clean things up and unify efforts. Base is too opinionated, containers but could be improved if stdlib compatibility wasn't required.
<discord3>
<Bluddy> And regarding effects: once we have a proof-of-concept that the stdlib can be versioned, it'll lead the way to doing it again whenever typed effects arrive
<companion_cube>
flux[m]: typed effects, as far as I'm concerned, are as much vaporware as implicits
<discord3>
<rizo> Regarding effects: we can start experimenting with effects in parallel.
<flux[m]>
how is backwards compatibility not a problem anymore?
<companion_cube>
let's not wait for 3 more years
<discord3>
<rizo> Backwards compatibility is a problem and a serious one. The suggested approach does preserve backwards compatibility by creating a separate namespace (V2) that extends and adapts the current stdlib.
<discord3>
<Bluddy> flux[m] we'll need some level of backwards compatibility (e.g. data structure), but not much beyond that hopefully
<discord3>
<rizo> This way, new code can benefit from a modern stdlib design and no existing code is broken.
dhil has quit [Ping timeout: 240 seconds]
dhil has joined #ocaml
<discord3>
<Bluddy> rizo 👍 (for our IRC friends)
<discord3>
<rizo> I was wondering if reactions exist in IRC.
bezirg has joined #ocaml
<thizanne>
so what's the difference with Containers again ?
<thizanne>
apart from being different, I mean
<discord3>
<Bluddy> a. Containers has to stick to stdlib's conventions, which are sometimes not great, since it's an extension (e.g. exceptions everywhere)
<discord3>
<Bluddy> b. Containers are only used by a group of people, rather than being standard
<flux[m]>
does it, though? containers isn't like an overlay to standard library, or at least I don't use it that way ;-).
<Khady>
Let's base this work on Belt
<discord3>
<Bluddy> Belt is built to be easy to use for JS people. I don't think that's the target, though there could be interesting ideas to learn from.
<discord3>
<rizo> I think in theory it's an improved version of Containers with the following question in mind: how would Containers look without the constraints of backward compatibility? But promoting this as V2 is important to make it a community effort.
<flux[m]>
I don't see how this new stdlib v2 would end up being "the standard". It would come bundled with the compiler? doesn't seem very likely to actually happen.
<discord3>
<Bluddy> the idea is that it would be bundled with the compiler, yes
<discord3>
<rizo> flux[m]: I honestly don't believe it myself. But I think it's worth trying. Worst case scenario this work could be contributed to Containers.
<Khady>
there is no seq module in this V2
<thizanne>
I don't think you can contribute the "everybody uses it" part to containers
<thizanne>
but please try
<discord3>
<rizo> Well, there's no V2 now, so there's nothing in it 😃
<flux[m]>
and then the politics of this topic. how would the Base folks feel about this, given something like this would be what they would like to happen with their module..
<flux[m]>
whatever happened to seq, btw..
<thizanne>
Bluddy: what's your problem with Base ?
<thizanne>
more precisely : why don't you take Base and try to bundle it with the compiler ?
<discord3>
<rizo> The political fragmentation already exists. I don't think this is going to make things worst. Base is not designed the same way Containers or Stdlib is. There's now open contribution process and it's not maintained by the main part of the community.
<flux[m]>
I don't think being opinionated is a bad thing. Though personally I haven't used Base or Core about at all.
bezirg has quit [Quit: Leaving.]
<thizanne>
Base is not designed the same way Containers or Stdlib is -> that's good, since you don't like the Stdlib design
<cryptocat1094>
Other than BuckleScript, what other option is there?
<thizanne>
and I understood that you wanted to solve the community contribution problem by putting your lib in the compiler
<Khady>
cryptocat1094: js_of_ocaml
<Khady>
what is "the main part of the community"?
<cryptocat1094>
Khady: Thanks.
<discord3>
<rizo> thizanne: by "not designed the same way as Containers or Stdlib" I mean the open development and contribution process.
lokydor_ has quit [Ping timeout: 276 seconds]
<thizanne>
but you could fork Base and adopt an open development process right
<discord3>
<rizo> Khady: The community behind other popular open source projects. By no means I want to say that Jane Street is not part of the community, on the contrary! They simply have different priorities and processes in my opinion.
<discord3>
<rizo> thizanne: that's one option yes. But I personally prefer the simple design of Containers. And other people I discussed this idea with seem to agree.
mk9 has quit [Remote host closed the connection]
<discord3>
<rizo> This might end up being a totally crazy idea. I understand your concerns. I'd be glad to listen to your criticism when we actually have something to present.
<discord3>
<Perry> The more I use OCaml, the more I've been concluding some advanced features should be treated like interesting spices. Occasional use makes the dish tastier, constant use ruins the meal.
<discord3>
<Perry> The analogy is probably bad.
<ZirconiumX>
I see what you mean
<Armael>
yea not having several levels of functors and signature inclusion helps a lot with the readability
<discord3>
<Perry> Maybe a better one is that some of them are specialized tools, and not meant for driving in nails when you have a good hammer.
<ZirconiumX>
Honestly both OCaml and the C++ STL have taught me what I'd term as a subtractive programming model
<discord3>
<Perry> Sometimes you really want the tool, and it is exactly right, but you shouldn't use it when something simpler does the job better.
<discord3>
<Perry> Subtractive?
<ZirconiumX>
Imagine you need all the even primes
<discord3>
<Perry> All one of them, yes. 😃
<ZirconiumX>
Bad example
<ZirconiumX>
Even squares then
<ZirconiumX>
In C, you'd have a loop which generated a single square, checked if it was even, and added it to an array/list/whatever
<discord3>
<Perry> The odd squares are quite unusual. 😃
<companion_cube>
hopefully we'd use iterators for that :°
<discord3>
<Perry> Pardon, I'm tired, my sense of humor is not working.
<companion_cube>
Sequence.(1 -- max_int |> map (fun x->x * x) |> filter (fun x -> x mod 2 = 0))
<ZirconiumX>
In C++ and OCaml, you can do it by generating all numbers from 1 to N, square them, and then filter out the ones which aren't even
<ZirconiumX>
Yeah, like that
<ZirconiumX>
Do you see what I mean by subtractive now?
<ZirconiumX>
It's a term from music (additive and subtractive synthesis), but I think it shows the method
Haudegen has quit [Remote host closed the connection]
mcspud has quit [Ping timeout: 265 seconds]
<discord3>
<Perry> I don't quite see, as I sort of see the two methods (in C and using a filter in OCaml) as being the same idea, but one is a nice composition of functions and thus a bit cleaner looking.
FreeBirdLjj has quit [Remote host closed the connection]
<ZirconiumX>
They achieve the same end result, sure
<discord3>
<Perry> and in the same way. both iterate through all the integers and check if they're squares.
<ZirconiumX>
I'm not saying either is wrong
<discord3>
<Perry> The distinction is that one is explicit and mutating and the other is more implicit and functional, but the machine is doing something almost the same underneath the surface.
<ZirconiumX>
Just different
<Armael>
hopefully, when using flambda, companion_cube's snippet even gets compiled into the same loop
<Armael>
(!)
<ZirconiumX>
I haven't actually benchmarked flambda
<companion_cube>
with Sequence, it's likely, it's quite inlining-friendly :-)
lokydor has joined #ocaml
<companion_cube>
I wonder if merlin could give info on how stuff is compiled…
<discord3>
<Perry> The way I see the distinction here is in the ease for the programmer. One method is nearly setbuilder notation, and another makes the programmer think about the details too much.
<def`>
merlin does not do compilation, it would be very difficult to do that, without clear benefits.
<def`>
however, flambda can produce a separate file with these information
<def`>
it is reasonable to make merlin act as a frontend to these files
<discord3>
<Perry> btw, I didn't know about the -- operator.
FreeBirdLjj has joined #ocaml
<companion_cube>
def`: ♥
<ZirconiumX>
One of my friends complained that C++ didn't give enough power, so I helped her by replacing 100 lines of for loop with std::copy
<discord3>
<rizo> Sequence is almost a free abstraction for push-based iteration.
<companion_cube>
exactly
<rks`>
def`: actually, we have a intern currently working on making the inlining reports of flambda more useful
<companion_cube>
especially the flat_map ♥
<rks`>
and he will start looking into displaying that information in the editor (probably using merlin) in a week or two
<discord3>
<rizo> I now think optimal flat_map is only possible in push-based iteration models. There are ways to specialize it with pull iterators but it's not trivial and less flexible.
<companion_cube>
rks`: that's amazing
<discord3>
<Perry> Grrr. It's impossible to google for ocaml operators. Where is -- documented?
<discord3>
<rizo> The title-level thing was the main problem that didn't work with most packages. I have been testing the current master with multiple packages and yes, it does generate warnings, but it works.
<discord3>
<rizo> rks`: It's nice to meet you here, trefis 😃
<Drup>
rks`: huh, I like the open refactoring thing
<rks`>
Drup: well, give a big kiss to def` next time you meet him
mcspud has joined #ocaml
Haudegen has joined #ocaml
<discord3>
<rizo> rks`: AFAIK antron doesn't have time now to work on odoc and I personally don't think it's currently ready for a release. If you spot any critical issues, please let me know. Feel free to mention me in the existing issues too
<rks`>
ack, thanks
gareppa has quit [Quit: Leaving]
gtrak has quit [Ping timeout: 260 seconds]
jbrown has joined #ocaml
jbrown has quit [Client Quit]
gtrak has joined #ocaml
jbrown has joined #ocaml
<discord3>
<rizo> The open refactoring feature seems amazing. How will it qualify symbols that are defined in multiple opened modules?
demonimin has joined #ocaml
<discord3>
<rizo> (I guess the last opened module will be used? ie, the one actually being used)
<discord3>
<Perry> rks`: Will it search for operators though?
<rks`>
yes.
<discord3>
<Perry> Do I have to use (parens)? Since it takes - and + I'd imagine just saying -- wouldn't work.
<rks`>
(yes to Perry, for rizo I assume so but can't confirm, I haven't looked at the implementation)
<rks`>
Perry: you're doing it wrong. You're not looking for/with a name (normal completion gives you that)
<thizanne>
rizo: the doc says "when the cursor is on an open statement"
<rks`>
you're looking with a type
<companion_cube>
hmm I've been using odoc for my packages for a while now :3
<companion_cube>
(well, no, but at least in 2018)
<discord3>
<Perry> Is there a real manual for Merlin? I don't know half of what it does. (My definition of a "real manual" is something like Menhir's manual.)
<rks`>
so, say you're looking for "(+.)" you'd say "-float +float"
<rks`>
(i.e. "consumes some float, and produce a float")
<discord3>
<Perry> Ah, but what if I see "--" and I want to jump to the docstring for it, can I?
<companion_cube>
merlin can show the doc
<rks`>
… yes?
<rks`>
but that's completely unrelated.
<discord3>
<rizo> thizanne: in which case a wrong symbol might be qualified I pick the "wrong" module...?
<discord3>
<Perry> sure, but it would be what I'd need right here.
<discord3>
<rizo> I think Perry wants to find all occurrences of the symbol. That's what ocamlscope did.
<discord3>
<Perry> Exactly, yes.
<rks`>
right, just try it. (M-x merlin-document or :MerlinDocument with your cursor on the thing)
<thizanne>
well then don't pick the wrong module, I guess
<rks`>
well
<rks`>
if Perry was more clear about what he wants
<rks`>
then we'd be able to give him an answer
<rks`>
"I want hoogle", "I want the doc", "I want all the occurences"
<discord3>
<Perry> BTW, after half a year or nine months of using OCaml I still feel lost in the maze a lot. I find that's happening less, but for example I still really don't know enough about the tooling.
<discord3>
<rizo> thizanne: I'll try 😃
<discord3>
<Perry> I really want all three. 😃
<discord3>
<Perry> I suppose what I truly want is another six months of free time to learn all the tools well. 😃
<thizanne>
this features lets you (un)qualify the identifiers brought to the environment by an open statement
<ZirconiumX>
Putting aside the fact I'm comparing floats for equality
<ZirconiumX>
That's not what I'm talking about
<companion_cube>
because you're not iterating on the sequence
<companion_cube>
I'd advise to `take 10 |> iter (fun (x,y,z) -> printf…)`
<ZirconiumX>
That's... counterintuitive, but okay
<companion_cube>
well an iterator is lazy
<companion_cube>
(that's usually the point)
<ZirconiumX>
Of course
<companion_cube>
so if you don't force its traversal… :)
<ZirconiumX>
But since iter makes no mention of forcing the sequence, I mentally discarded it
<ZirconiumX>
This is probably going to take me a while
<companion_cube>
"consume the sequence"
<companion_cube>
you can open an issue about the parts of the doc that are confusing
<ZirconiumX>
... I mixed up iter with iterate
<ZirconiumX>
Sorry
<companion_cube>
ah yes
<ZirconiumX>
Also sequence produces some very fun type errors
<companion_cube>
^_^' I know
donviszneki has quit [Ping timeout: 264 seconds]
<ZirconiumX>
Not that the compiler's interesting text wrapping helps much
<companion_cube>
that's one of the inconvenients to use a structural type for `'a Sequence.t`
cryptocat1094 has quit [Quit: WeeChat 1.6]
<discord3>
<Bluddy> structural type? huh?
<companion_cube>
('a -> unit) -> unit
<companion_cube>
by opposition to a nominal type that could be defined in only one place, it's possible to define `'a sequence` in many places and still have them be compatible
<discord3>
<Bluddy> ah ok because you don't hide it
<discord3>
<Bluddy> i guess that makes sense
<companion_cube>
that's very useful, imho
<discord3>
<Bluddy> definitely more convenient
donviszneki has joined #ocaml
jnavila has quit [Ping timeout: 240 seconds]
<thizanne>
more than not hiding it, you don't need to use variants, so two totally independent projects could use sequences and when you happen to use both projects, their sequences are compatible
<companion_cube>
^
<thizanne>
compared to, say, type 'a sequence = Foo of ('a -> unit) -> unit, where even if you don't hide it, two `Foo` variants coming from different modules are not compatible
<discord3>
<Bluddy> ah. very cool
isd has quit [Ping timeout: 256 seconds]
<companion_cube>
that's why containers is compatible with sequence, even though it doesn't depend on it
<discord3>
<Bluddy> Does containers mention sequence in the docs?
<discord3>
<Bluddy> Probably a good idea to do so if it doesn't.
<companion_cube>
it does, as far as I remember
<companion_cube>
see "common type definitions" in the readme
<discord3>
<Bluddy> ok yeah I see it
<discord3>
<Bluddy> how does oseq fit into the picture?
<discord3>
<Bluddy> we now have gen, sequence and oseq
<companion_cube>
it targets the new standard iterator, which is not structural
<companion_cube>
it's purely functional, as a suspension list
<companion_cube>
a list where the tail is hidden under `unit -> …`
<Armael>
companion_cube: sequence and oseq serve different purposes, but what about gen vs oseq?
<Armael>
is gen "deprecated" in some way by oseq?
<companion_cube>
not particularly, it's just a different type
<Armael>
yea but featurwise
<Armael>
+e
<companion_cube>
it might be less useful, if that's the question
<discord3>
<Bluddy> we need some guide about these things
<Armael>
to reformulate, is there a situation where you would want to use gen instead of oseq
<companion_cube>
in generaly the standard Seq (and OSeq) should be favored, I think
<companion_cube>
Armael: except for very imperative things, probably not
<companion_cube>
Drup: btw would you be interested by seq-ready Re operators?
<Armael>
companion_cube: yeah, ok
<Armael>
would it make sense to indicate that in the readme of gen, say?
<Drup>
I like how you ask like I'm the maintaner of Re
<companion_cube>
:D
<Drup>
Currently we have gen operators, right ?
<thizanne>
isn't gen faster than oseq ?
<companion_cube>
… aren'tcha? :p
<Armael>
like "you should probably use stdlib's seq/oseq instead"
<companion_cube>
yeah, but we should have both, I think
<Drup>
transitionning to seq would make sense
<Drup>
thizanne: negligeable compared to re matching
<thizanne>
yeah I guess
<Drup>
companion_cube: I disagree
<discord3>
<Bluddy> guidelines are very much needed here
<thizanne>
I was answering to "is there a reason for using gen"
<companion_cube>
Drup: breaking compat… :/
<discord3>
<Bluddy> most people don't have the time to shop around
<thizanne>
which I guess could be "it's faster and still has map2" ?
<Drup>
companion_cube: deprecate the gen ones
<companion_cube>
deprecating means keeping, at least for now
<Drup>
thizanne: compared to seq, not really
<Drup>
seq also has map2
<thizanne>
Bluddy: most people will pick the stdlib one, which is the one the guidelines would advice anyway
<Drup>
companion_cube: well, yes, but it doesn't mean "having both"
<Drup>
it means "having one, and keeping the other one temporarly"
<companion_cube>
i.e for at least 1 year :)
<Drup>
that's like, one Re release
<Armael>
gotta start some day
<Armael>
:p
<Drup>
companion_cube: In any case, I kinda agree it makes sense to try to deprecate gen
malina has quit [Ping timeout: 240 seconds]
<companion_cube>
yeah…
argent_smith has quit [Quit: Leaving.]
tarptaeya has quit [Quit: Konversation terminated!]
neatonk has quit [Ping timeout: 245 seconds]
isd has joined #ocaml
isd has quit [Ping timeout: 260 seconds]
SomeDamnBody has quit [Ping timeout: 256 seconds]
larhat has quit [Quit: Leaving.]
ousado has quit [Ping timeout: 264 seconds]
donviszneki has quit [Ping timeout: 265 seconds]
cbot has quit [Ping timeout: 260 seconds]
donviszneki has joined #ocaml
ousado has joined #ocaml
shw has joined #ocaml
mk9 has quit [Quit: mk9]
btbytes has joined #ocaml
mk9 has joined #ocaml
Haudegen has quit [Remote host closed the connection]
gtrak has quit [Ping timeout: 260 seconds]
gtrak has joined #ocaml
zolk3ri has quit [Remote host closed the connection]