Leonidas changed the topic of #ocaml to: Discussion about the OCaml programming language | http://www.ocaml.org | OCaml 4.13.0 released: https://ocaml.org/releases/4.13.0.html | Try OCaml in your browser: https://try.ocamlpro.com | Public channel logs at https://libera.irclog.whitequark.org/ocaml/
namkeleser has quit [Quit: Client closed]
namkeleser has joined #ocaml
namkeleser has quit [Quit: Client closed]
mro has quit [Quit: Leaving...]
namkeleser has joined #ocaml
rgrinberg has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
<d_bot> <cemerick> @companion_cube didn't know about the colors support in CCFormat, that's fun 👍
Tuplanolla has joined #ocaml
<companion_cube> :)
Techcable has quit [Ping timeout: 256 seconds]
Haudegen has quit [Ping timeout: 260 seconds]
rgrinberg has joined #ocaml
namkeleser has quit [Quit: Client closed]
<d_bot> <Shon> I like some functional idioms over matrices: in particular a fold operation that also supplies indices, and mapping operations to transform the matrices. In general, I don’t much like having to reason about bounds for indices. That said, it’s nice to be able to just mutate an array cell sometimes 🙂
Tuplanolla has quit [Quit: Leaving.]
<companion_cube> you can have fold and map, with mutable arrays!
<companion_cube> it's probably better this way anyway
<companion_cube> matrices are meant to be arrays (bigarrays probably even)
Techcable has joined #ocaml
namkeleser has joined #ocaml
xiongxin has joined #ocaml
<companion_cube> https://github.com/c-cube/ocaml-avro alright, first draft is ready
<companion_cube> 😁
zebrag has quit [Quit: Konversation terminated!]
mbuf has joined #ocaml
shawnw has joined #ocaml
<remexre> if I have a module type with a large number of items that can be defined in terms of others, and typically are, is there a way to add defaults?
chrisz has joined #ocaml
xiongxin has quit [Ping timeout: 256 seconds]
xiongxin has joined #ocaml
Tuplanolla has joined #ocaml
<d_bot> <Continuation Calculus> might just be tired: let's say i have a recursive datatype, and i want one of the case to be a set. like `type fbs = Foo of int | Bar of string | Set of fbs set`. How should I do it given that `Set.Make` is a functor?
namkeleser has quit [Quit: Client closed]
<d_bot> <Continuation Calculus> or, if there is no good way to do it (like, one would have to use `module rec` and stuff), is there a good library that exposes "a universal type", as in https://blog.shaynefletcher.org/2017/03/universal-type.html ?
<d_bot> <octachron> recursive types with embedded sets are one of the motivation for recursive modules.
Serpent7776 has joined #ocaml
<d_bot> <octachron> (And with the type-only module trick, this can be done without any duplication)
rgrinberg has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
Colt has quit [Remote host closed the connection]
namkeleser has joined #ocaml
Haudegen has joined #ocaml
chrisz has quit [Quit: leaving]
waleee has quit [Ping timeout: 268 seconds]
bartholin has joined #ocaml
mro has joined #ocaml
mro has quit [Remote host closed the connection]
xiongxin has quit [Remote host closed the connection]
xiongxin has joined #ocaml
bartholin has quit [Ping timeout: 252 seconds]
<d_bot> <Kakadu> If I want to use State monad in my code, where should I get it's implementation? Opam `monads` package depends on core_kernel which looks like a little bit heavy... Any alternatives?
<d_bot> <Kakadu> Should we put any definition of the monads in stdlib, by the same motivation as for `('a, 'b) result` data type?
bartholin has joined #ocaml
mro has joined #ocaml
mro has quit [Ping timeout: 260 seconds]
<Leonidas> companion_cube: haha, only yesterday I discussed that ;* would be nice (along with match*)
<companion_cube> Oh yes, match*
<companion_cube> remexre: functor?
<Leonidas> the original ppx_let had match%bind and I am somewhat confused why this wasn't upstreamed too
<Leonidas> (as in, it would be quite simple to do and the semantics are pretty clear, so if it is more complex I don't understand why)
<companion_cube> Because the core team is conservative I guess
<Leonidas> let* is not particularly conservative and from let* match* is a rather conservative extension
<Leonidas> also let punning feels weird
<Leonidas> but that's just a purely syntactic thing
<Leonidas> I recently converted a codebase to let* and it was... quite pleasant.
<companion_cube> Well there must be an issue discussing match* somewhere
<companion_cube> I think it was in the initial proposal
<companion_cube> It's definitely nice when you have monadic code, to remove the >>=
Sofi[m] has joined #ocaml
<d_bot> <Kakadu> Actually, I realized that I don't need full-blown state monad. Now I'm struggling of lack of higher-kinded types
<d_bot> <Ulugbek> You can have a look at Jane street/higher_kindled repo, if you haven’t already
<d_bot> <Kakadu> No, I mean proper higher kinded types
<companion_cube> You're out of luck then
<d_bot> <Kakadu> One of my frustration about higher_kinded lib is a lot of Make1,2,3,... functors. Do you know any (research?) language with higher-kinded types and non-currified type operators like in OCaml? I may try to get some insight from this language...
Colt has joined #ocaml
bartholin has quit [Ping timeout: 252 seconds]
Colt has quit [Remote host closed the connection]
Colt has joined #ocaml
Colt has quit [Remote host closed the connection]
Colt has joined #ocaml
Colt has quit [Remote host closed the connection]
namkeleser has quit [Quit: Client closed]
Colt has joined #ocaml
Colt has quit [Remote host closed the connection]
Colt has joined #ocaml
Colt has quit [Remote host closed the connection]
bartholin has joined #ocaml
xiongxin1 has joined #ocaml
<d_bot> <Shon> Yes, I meant folding over mutable arrays. I’ve had nice outcomes lately folding/mapping over arrays for traversal, then mutating for updates.
xiongxin has quit [Ping timeout: 252 seconds]
xiongxin1 is now known as xiongxin
chrisz has joined #ocaml
shawnw has quit [Ping timeout: 256 seconds]
xiongxin1 has joined #ocaml
xiongxin has quit [Ping timeout: 268 seconds]
xiongxin1 is now known as xiongxin
bartholin has quit [Ping timeout: 250 seconds]
<d_bot> <darrenldl> is there equivalent to JNDI (the main feature that allowed the log4j vuln it seems?) in ocaml?
chrisz has quit [Ping timeout: 240 seconds]
chrisz has joined #ocaml
waleee has joined #ocaml
Anarchos has joined #ocaml
bartholin has joined #ocaml
hackinghorn has quit [Ping timeout: 265 seconds]
<companion_cube> probably not
<companion_cube> 1. OCaml doesn't have reflection so you don't typically pass foo.class around
<companion_cube> 2. OCaml doesn't have hot class loading (you can load .cmxs but it's… a lot more fragile)
<d_bot> <darrenldl> the entire log4j situation seems a bit counterintuitive, but oh well
<d_bot> <darrenldl> companion_cube: cheers for the info
hackinghorn has joined #ocaml
xiongxin has quit [Remote host closed the connection]
bartholin has quit [Ping timeout: 250 seconds]
bartholin has joined #ocaml
shawnw has joined #ocaml
mro has joined #ocaml
gravicappa has joined #ocaml
mro has quit [Read error: Connection reset by peer]
mro_ has joined #ocaml
mro has joined #ocaml
mro_ has quit [Ping timeout: 250 seconds]
mro has quit [Remote host closed the connection]
mro has joined #ocaml
bartholin has quit [Ping timeout: 250 seconds]
rgrinberg has joined #ocaml
Corbin has quit [Ping timeout: 256 seconds]
bartholin has joined #ocaml
mbuf has quit [Quit: Leaving]
bartholin has quit [Ping timeout: 252 seconds]
mro has quit [Remote host closed the connection]
rgrinberg has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
<Leonidas> darrenldl: Maybe you can ask Daniel? Logs doesn't even seem to support injecting template variables via formatting parameters ;-)
<Leonidas> Or template variables to begin with
vicfred has joined #ocaml
sluigi has joined #ocaml
<sluigi> what's the easiest way to check if two maps have conflicting values for the same key if I'm using Core.Map?
perrierjouet has quit [Quit: WeeChat 3.3]
perrierjouet has joined #ocaml
kadir has joined #ocaml
gravicappa has quit [Ping timeout: 260 seconds]
kadir has left #ocaml [WeeChat 3.3]
kadir has joined #ocaml
vicfred has quit [Quit: Leaving]
kadir has left #ocaml [WeeChat 3.3]
Haudegen has quit [Quit: Bin weg.]
bartholin has joined #ocaml
sluigi has quit [Ping timeout: 256 seconds]
mro has joined #ocaml
waleee has quit [Ping timeout: 250 seconds]
Anarchos has quit [Quit: Vision[]: i've been blurred!]
Anarchos has joined #ocaml
mro has quit [Remote host closed the connection]
mro has joined #ocaml
tomku has quit [Ping timeout: 250 seconds]
tomku has joined #ocaml
rgrinberg has joined #ocaml
perrierjouet has quit [Quit: WeeChat 3.3]
perrierjouet has joined #ocaml
perrierjouet has quit [Client Quit]
perrierjouet has joined #ocaml
mro has quit [Remote host closed the connection]
mro has joined #ocaml
mro_ has joined #ocaml
perrierjouet has quit [Quit: WeeChat 3.3]
mro_ has quit [Remote host closed the connection]
mro_ has joined #ocaml
mro has quit [Ping timeout: 260 seconds]
namkeleser has joined #ocaml
perrierjouet has joined #ocaml
<rgrinberg> thizanne \o/
<thizanne> rgrinberg: o/
<companion_cube> thizanne \o/
Anarchos has quit [Quit: Vision[]: i've been blurred!]
<thizanne> companion_cube: \o
<rgrinberg> Shall we re-org the interface a little and get 1.0 out the door?
average has quit [Quit: Connection closed for inactivity]
<thizanne> ok now you're frightening me :)
<companion_cube> 1.0 of what? :D
<thizanne> hamt
<rgrinberg> I'm thinking Hamt.Stdlib for a drop in replacement to Stdlib's map
<rgrinberg> and a slightly saner api by default
<thizanne> yeah I'd vote for that too
<rgrinberg> Also, wdyt of asking users to provide compare so that we can use a good old map for collision nodes?
<rgrinberg> It seems like a better way to degrade the perf in that case
<thizanne> it seems reasonable to ask for compare anyway
<thizanne> and using a map seems legit too
<companion_cube> waaaaaaaaaaaa
<thizanne> what does hashtbl do nowadays ?
<companion_cube> omg omg
<companion_cube> rgrinberg: does that imply popcnt as well?
<rgrinberg> companion_cube maybe post 1.0 since it's just an optimization. I'm always working on the CHAMP optimizations rn
<companion_cube> ah wait, misread. thought you were proposing to upstream HAMT into ocaml
<thizanne> yeah don't be too excited yet, the core code is mostly the same bad one that I wrote so many years ago
<rgrinberg> and i think those are a higher priority
<companion_cube> "just"
<thizanne> but rgrinberg has been putting a lot of work into making it usable these days
<rgrinberg> thizanne stdlib's hash table uses a list. core's hash table uses a map like a suggested
<rgrinberg> *i suggested*
<thizanne> let's use a hash table then
<rgrinberg> you mean a map?
<thizanne> yes
<companion_cube> weirdly it's hard to make a hashtbl that's faster than the stdlib's, in my experience
<companion_cube> at least, trying to make a flat one, without lists :/
<thizanne> regarding the CHAMP stuff: that's something I've wished to do since quite a long time
<thizanne> but never did
<thizanne> before that I believe that it could be worth reading the paper again, and look at the code a bit more carefully
<rgrinberg> thizanne should give the library a little extra oomph
<companion_cube> what's the CHAMP stuff anyway
<thizanne> I think I made some things a little differently, which may actually have been bad ideas
<thizanne> canonical hamt and I don't know what P stands for
<companion_cube> thizanne: I wrote a kinda-sorta-hamt like at the same time roughly, and wlel
<rgrinberg> companion_cube standard optimizations to hamt
<companion_cube> it was similar perf I think
<companion_cube> rgrinberg: is there a short explanation?
<thizanne> companion_cube: someone also wrote an implementation that was consistently faster than mine, also around the same time
<thizanne> that was bob atkey I believe
<rgrinberg> yeah, if your nodes are type t = Emtpy | Leaf of .. | Bitmap of t array
<thizanne> I didn't look at it in depth though
<rgrinberg> you're kind of killing perf with all the Leaf's in the array
<rgrinberg> so you store the Leaf's in a separate bitmap
<rgrinberg> thizanne do you have a link?
<rgrinberg> i read the champ paper btw. any other paper you have in mind?
<companion_cube> bitmap + vec, you mean?
<rgrinberg> yes
<companion_cube> interesting
<companion_cube> wow thizanne that's full of Obj
Guest9603 has quit [Quit: Konversation terminated!]
<rgrinberg> thizanne yes that paper skips the whole non bitmap nodes stuff
<rgrinberg> i'm also skeptical of how helpful that stuff is
<thizanne> yeah, in a conversation with gasche, he said (bob):
<thizanne> For the array mapped trie library, I'd also started it just before I saw the HAMT announcement. At the moment, my library is not ready for real use: it only works on 64bit machines (it assumes that there are at least 32 bits available in the 'int' type), and the interface is not yet complete. I have experimented with a 'packed' version that attempts to reduce memory usage by adhering more closely to the memory
<thizanne> layout described in Bagwell's 'Ideal Hash trees' paper -- at the cost of using the Obj module to do type coercions.
<thizanne> rgrinberg: I think I tried to move the thresholds to never use bitmaps, and the opposite
<thizanne> and both extremes were performing worst than the default
<d_bot> <dinosaure> for instance, `art` is faster than `hashtbl` if you want
<companion_cube> for me Obj is a no no
<thizanne> I'm not sure how that plays with champs though
<companion_cube> @dinosaure it's not generalistic, is it?
<thizanne> yeah companion_cube if that's why he's faster, then I'd be fine with being slower
<d_bot> <dinosaure> it's not :/ must be a string as a key
<companion_cube> heh, then it doesn't count
<d_bot> <dinosaure> you can serialize your key to a string :p
<companion_cube> in some ways, OCaml comes short when it comes to implement a good vector or a good hashmap
<companion_cube> you simply can't do it cleanly if you can't have a partially uninitialized array
<rgrinberg> thizanne i think hamt's bitmap hot path can be optimized enough so that the array path will be useless
<rgrinberg> i'll experiment with that
<rgrinberg> dinosaure what's good about art again?
<companion_cube> better memory usage for strings, i think?
<companion_cube> it's a trie specialized on strings so it got to be good
<rgrinberg> how good are we talking?
<rgrinberg> i actually want something like that for dune
<rgrinberg> we have a ton of path maps and sets
<rgrinberg> and obviously those share long prefixes
<d_bot> <NULL> companion_cube: I still have the idea of an unboxed option type (where the sanity check for unboxing is bypassed) for partially uninitialised structures, but I'm too much of a noob to implement it
<companion_cube> well rgrinberg, ask @dinosaure :p
<d_bot> <dinosaure> rgrinberg: as companion_cube, it's like a light raidx tree
<companion_cube> it's also a good concurrent structure iirc
<d_bot> <dinosaure> radix*
<d_bot> <dinosaure> you can see benchmark here:
<d_bot> <dinosaure> so you have kind of compression and it's not a naive radix tree, it wants to be lighter than a radix tree (and offers 4 kind of nodes)
<companion_cube> the graphs are nice, really
<rgrinberg> dinosaure how many elements in that tree in each benchmark?
<d_bot> <dinosaure> 1000 elements
Anarchos has joined #ocaml
<rgrinberg> hmm, in dune we have plenty of small sets
<d_bot> <dinosaure> in my case, I mainly test that the given distribution of strings are "normal"
<d_bot> <dinosaure> (and you can check that via the histogram)
<d_bot> <dinosaure> after yeah, we should check more elements but we can easily say that, via the path compression, the result should be more interesting than an hashtbl in anyway
<companion_cube> rgrinberg: you could have one big string set, and a bitmap for each small set :p
<companion_cube> I hear about these "roaring bitmaps" regularly
<rgrinberg> companion_cube rawr. not a bad idea
<d_bot> <dinosaure> (this is the big diff between `art` and `hashtbl`, `art` can jump in some cases some bytes where it saw a common parT)
<rgrinberg> there's a few more requirements, such as being able to do Filename.relative efficiently to every element.
<companion_cube> oof
bartholin has quit [Quit: Leaving]
<rgrinberg> we need unboxed arrays badly in ocaml
<companion_cube> seems like a trie might help for that too, tho
<companion_cube> yes please
<rgrinberg> companion_cube yes, something trie like. but optimizing tries is a headache
<rgrinberg> and the naive ones are quite poor
<companion_cube> that's what art is for, indeed
<companion_cube> ART*
Serpent7776 has quit [Quit: leaving]
<rgrinberg> thizanne there's a few more pr's up :)
<thizanne> lalala not hearing you
<companion_cube> :D
<d_bot> <Shon> Could someone help me prove out my understanding of the advantage/tradeoffs using Seq, vs. Lazy lists, vs. just reading everything into memory say as a list? In particular, I want to be sure I understand the tradeoffs when reading in data from an in_channel, so statefulness is key.
<d_bot> <Shon> My current understanding is this: Seq.t is nice and can save the amount of memory you need to allocate at any given time IF you can deal with each item one at a time or small batches AND (critically) you won't traverse the Seq.t more than once. Otherwise, the statefulness of the channel while break your logic (been bit by this twice this week).
<d_bot> <Shon> Proper lazy lists allow for building up collections incrementally, and traversing them multiple times, but unless you need to do expensive computations to construct each element of the list, there's no advantage if you're gonna end up needing all the lines eventually, because the memoization will mean you end up keeping everything in memory.
<companion_cube> lazy is a bit more expensive than `fun() -> …`
<companion_cube> that's it basically
<d_bot> <Shon> Right, and it's also more expensive than just a thunk.
<rgrinberg> tbh Seq.t is also kind of a pig and should be avoided anywhere where performance is needed
<companion_cube> it's… the status quo that was able to make it in
<d_bot> <Et7f3> Seq.t isn't like generator in other languages ?
<d_bot> <Shon> I thought there was memory savings if you read, e.g., a file line by line using Seq.t, I assume because you can free the memory for each line after processing it?
<companion_cube> it's one that's functional in some cases
<companion_cube> the imperative version was never accepted
<companion_cube> yeah, the GC will do that
<d_bot> <Shon> Whereas, I assume this doesn't happen for Lazy.t, since it needs to keep the data in memory for memoization?
<companion_cube> not *immediately* after, but it can
<companion_cube> lazy can also be GC'd if it's not referenced anywhere
<d_bot> <Shon> (Assuming you still have a handle to the lazy list in scope)
<Anarchos> i made a version of ppxlib, assuming that 5.00 has same AST as 4.14, should i do a pull request ?
<d_bot> <Shon> Hmm, ok, so if it's true that Seq.t should be avoided (I have found it very dangerous when trying to use with in_channes, cause you get to thinking in functional terms, but the state is actually critical)
<companion_cube> if you have a handle, neither will be collected
<companion_cube> Seq + in_channel is ok if you consume the seq inside the `with_file_in` or whatever.
<d_bot> <Shon> is there anything better then either reading the while file into a list, or just doing it imperatively?
<companion_cube> Anarchos: maybe to ppxlib
<Anarchos> companion_cube not sure if i did things right
<rgrinberg> doing it imperatively or using a list both sound a lot better than Seq to me
<companion_cube> I think it's premature, Anarchos
<companion_cube> rgrinberg: unless you don't need the list
<Anarchos> companion_cube but i was amazed to see nobody began work on it
<companion_cube> because 5.0 is not out yet I guess
<companion_cube> but maybe they have a branch
<Anarchos> companion_cube i understood that 5.00 was 'mostly' multicore, so not much ast tweeaking
<rgrinberg> Anarchos why do it early? the parsetree might change later anyway
<rgrinberg> it's done quite quickly anyway
<Anarchos> rgrinberg sure, but as i need a trunk version of the compiler, i needed it already.
perrierjouet has quit [Quit: WeeChat 3.3]
<rgrinberg> might be good to open a PR then. I'm not sure if it will be accepted in the near future though
<Anarchos> ok
oriba has joined #ocaml
Techcable has quit [Ping timeout: 260 seconds]
<d_bot> <Shon> Thanks for the POVs, rgrinberg and companion_cube. I'm still not convinced to be fully anti Seq, as having something that allows a mostly functional idiom over a stream of lines seems nice, except I've also been gunning my foot with it 😐 -- maybe use of something like `with_file_in` will help provide the logical supports I need. Thanks!
<rgrinberg> i'm not anti Seq, I just wouldn't mix it with IO or performance sensitive code
namkeleser has quit [Quit: Client closed]
namkeleser has joined #ocaml
<thizanne> damn rgrinberg we've used all my travis credits with the last PRs
<thizanne> which is why it doesn't trigger anymore
<rgrinberg> we need to switch to actions anwyay
<thizanne> yeah I was looking at it
<companion_cube> rgrinberg: depends how performance sensitive I'd say
<thizanne> (re. travis, that really doesn't matter for me, I wasn't using it for anything else anyway)
<companion_cube> In a core loop of a cpu intensive thing, maybe not, but it's not *that * slow
<rgrinberg> I think the problem is that a lot of people use it for "optimization"
<rgrinberg> to avoid having to allocate some intermediate lists for example
<rgrinberg> not realizing the overhead this introduces is usually much greater than throwing away a couple of lists
<companion_cube> ah, that
<companion_cube> I mean, you should allocate the same amount, more or less
<companion_cube> except it's closures instead of cons nodes
<companion_cube> (so perhaps slightly bigger, but same number of allocations)
<companion_cube> for me the "optimisation" part is that you only produce stuff when you need to.
<d_bot> <Shon> Yeah, I think what rgrinberg described is my scenario actually. Premature optimization, and then reaching for something of which I didn't have a clear understanding of the tradeoffs. I think the new preamble introduced with the expansion of the Seq library should help with this a lot! (https://github.com/ocaml/ocaml/blob/trunk/stdlib/seq.mli)
average has joined #ocaml
<rgrinberg> in general, laziness and IO don't mix well. I suppose this applies to Seq as well
rgrinberg has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
<d_bot> <Shon> But a couple days ago I was producing a Seq from lines of input, and tried to then convert it into an array (using Containers), and didn't consult the docs first, and the array conversion traverses the whole seq to get the length before allocating the array, initializing with the first element, so I was getting very surprising behavior 🙂 -- good reminder to RTFM, also perfect illustration of your warning about mixing laziness and
<companion_cube> Hmm right
<companion_cube> This particular part could be improved tbh
<companion_cube> But then it requires a vector or similar
<d_bot> <Shon> I was thinking about opening an issue/pr. the best idea I came up with was constructing a list and counting length in one go, then traverse the reversed list, using the length index to store each item into the array in reverse order?
<d_bot> <Shon> Would require allocation of the list, but I think would only take the same amount of traversals of the seq? If you think that'd be helpful, I'd be happy to make note in an issue or open a PR with the suggestion.
<companion_cube> you can do to_rev_list followed by an array.of_list (but reversed)
<companion_cube> it's just also a lot of allocations
<companion_cube> it's only worth it if you do a lot of intermediate work imho
<companion_cube> for years I also used an imperative version (`unit -> 'a option`) which is actually somewhat faster
<companion_cube> but it's less general as it can't be used twice, ever
Tuplanolla has quit [Quit: Leaving.]
oriba has quit [Read error: Connection reset by peer]