adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml 4.09 release notes: https://caml.inria.fr/pub/distrib/ocaml-4.09/notes/Changes | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
vicfred has quit [Quit: Leaving]
_whitelogger has joined #ocaml
dhil_ has quit [Ping timeout: 240 seconds]
h14u has quit [Quit: Leaving]
vicfred has joined #ocaml
mfp has quit [Ping timeout: 240 seconds]
jaar has quit [Ping timeout: 240 seconds]
waleee-cl has quit [Quit: Connection closed for inactivity]
spew has quit [Quit: Connection closed for inactivity]
mbuf has joined #ocaml
spew has joined #ocaml
xvilka has quit [Remote host closed the connection]
narimiran has joined #ocaml
zmt00 has quit [Quit: Leaving]
_habnabit has quit [Read error: Connection reset by peer]
_habnabit has joined #ocaml
NSA_Spy has quit [Ping timeout: 256 seconds]
osa1 has joined #ocaml
ggole has joined #ocaml
_whitelogger has joined #ocaml
decentpenguin has quit [Read error: Connection reset by peer]
decentpenguin has joined #ocaml
dckc has quit [Ping timeout: 246 seconds]
nkly_ has joined #ocaml
dckc has joined #ocaml
<rwmjones> how do I get dune to pass the -g flag to everything, no exceptions?
<rgrinberg> rwmjones where does it make exceptions currently?
<rwmjones> so building migrate-parsetree for Fedora:
<rwmjones> we don't get debug symbols, and I think the problem is the final binary
<rwmjones> sorry, wrong log
<rwmjones> let me find the right log ...
<rwmjones> anyway, it wasn't passing -g when linking ppx.exe
<rwmjones> the log will be here, but it's still building at the moment: https://kojipkgs.fedoraproject.org//work/tasks/241/48600241/build.log
<rwmjones> we need every invocation of ocamlc, ocamlopt, ocamlmklib to use -g
<rwmjones> if you look at the line "Running[207]:" you'll see that -g is not used
<rgrinberg> I see. Indeed dune doesn't pass -g here. I can fix it, but you'll need a new version of dune to fix your problem. There's no way to customize how ppx binaries are compiled.
<rwmjones> rgrinberg: does it need changes to the package as well, or just a new dune? anyway if you send me a suggested patch/fix to dune I can try it out
<rgrinberg> Upgrading dune should be sufficient to fix the problem for all packages.
<rwmjones> ok
spew has quit [Quit: Connection closed for inactivity]
nullcone has joined #ocaml
webshinra has quit [Remote host closed the connection]
<rwmjones> rgrinberg: I'll try it out in a few mins
ggole has quit [Quit: Leaving]
webshinra has joined #ocaml
malc_ has joined #ocaml
webshinra has quit [Ping timeout: 272 seconds]
webshinra has joined #ocaml
waleee-cl has joined #ocaml
jco has joined #ocaml
<jco> Hi! So from what i understood Arrays are mutable, but you cannot append elements without recreating a new array
<jco> there aren't lists so this makes sense
<jco> *they
<jco> same for hashmaps, they are immutable (at least in Base)
<jco> so the question is, should i use an immutable hashmap in my program or an immutable one (looks like i'd need to reimplement it)
<jco> in an asynchronous program
<jco> using an immutable hashmap means that i'll need to pass it to each function
<flux1> I think it really "depends". mutable ones can be easier to use exactly because you don't need to pass it back and forth; on the other hand it can be more difficult to see where it is used and when it is mutated.
<rwmjones> jco: there was a thing for resizing arrays, but I don't think it's maintainer any more
* rwmjones thinks back to what that was called
<rwmjones> oh yes, ocaml-res
<rwmjones> ISTR it was not compatible with modern OCaml or something broke it
<flux1> I think common stdlib enhancement libraries come with vector data types that do growing/shrinking
<flux1> rwmjones: seems nice. and given the source it's probably quality :).
<jco> oh thanks for the answers!
<jco> I'm a bit hesitating but since i'd like the program to scale i'll go with an immutable hashmap
<jco> it'll be a bit heavier, but in the other hand it'll be safer in concurrent i/o right?
<Leonidas> you'll be less likely to screw yourself over, yes.
<Leonidas> I'd still like a decent selection of HAMT-backed data structures for ocaml
<Leonidas> kinda like they exist in clojure by default
jaar has joined #ocaml
<Leonidas> rgrinberg: interested in a PR to update ocaml-hamt to build on OCaml 4.10?
<jco> thanks, i have a technical question on how to handle the hashmap (i'm starting with a list to make things simple)
<jco> the first function computes a new list, then the result is used to execute a command
<jco> but how can the list be returned after the command is executed?
<jco> does this means that any function from the api (including functions like git_push or execute_command) take the list in argument even though they do nothing with it?
nkly_ has quit [Ping timeout: 240 seconds]
mfp has joined #ocaml
dhil_ has joined #ocaml
<jco> hum there's hashtbl in fact
ggole has joined #ocaml
jbrown has joined #ocaml
<vsiles> Is it possible to use Set.Make with a type that has parameters ? like in module MyO = struct type 'a t = 'a foobar ... end as the ordered type ?
<def> no
<def> (yet another example why functors are wrong :P)
<jco> is it possible to name the different outputs of a function?
<jco> like named parameters
<jco> like if you return a tuple, name each of the two elements
<vsiles> def: 'k, thanks !
<theblatte> jco: you need to create a record type, or use a poly variant, depends on your use case
<vsiles> theblatte: poly are evil, a variant would suffice too
<theblatte> they avoid a type definition, the use-case would be a non-perf-critical function that is internal to a module, for example
<theblatte> I usually don't bother with either and just return a tuple and add a doc comment, but it's not the best
<vsiles> I have to say I usually use polymorphic variants while prototyping, but the error messages are unreadable so I move to normal variant / tuples
<vsiles> rather quickly
<jco> thanks, a variant will do it!
<Leonidas> is there a fun incantation to depend on stdlib-shims only on versions of ocaml that need it?
<Leonidas> in opam files
<Leonidas> vsiles: poly variants are not evil per-se, there's plenty of good uses for them
greenbagels has quit [Ping timeout: 258 seconds]
<jco> def: by curiosity, in which ways do you think functors are wrong?
greenbagels has joined #ocaml
<Leonidas> rgrinberg: I made it anyway, https://github.com/rgrinberg/ocaml-hamt/pull/6
malc_ has quit [Ping timeout: 256 seconds]
<vsiles> Leonidas: agreed
FreeBirdLjj has joined #ocaml
mengu has joined #ocaml
spew has joined #ocaml
mengu_ has joined #ocaml
mengu_ has quit [Client Quit]
mengu has quit [Ping timeout: 256 seconds]
superherointj has joined #ocaml
malc_ has joined #ocaml
<Leonidas> in jco's case this is kinda valid, JST code sometimes has types like [`Ok | `Duplicate] for which you don't want to declare separate, kinda nonsensical types.
<jco> yeah, but why these types are polymorphic here? Ok | Duplicate of string could do the same no?
superherointj has quit [Quit: Leaving]
<Leonidas> jco: yes, but then your type has to have a name
<Leonidas> like type return_value_of_function = Ok | Duplicate of string
<Leonidas> and then your code can become a mess of named types and indirection
artart78 has quit [Ping timeout: 244 seconds]
<Leonidas> There's some cases where you want to reuse these (this is also happening in JST code, where they are sometimes unifying previously polymorphic types into a named variants)
<Leonidas> It's mostly about readability I'd argue
dhil_ has quit [Ping timeout: 246 seconds]
<flux1> I think it helps a lot dealing with polymorphic if you annotate a bit more than perhaps needed with plain sum types
<flux1> but there are cases where polymorphic types hit the bill. for example maybe you want to express three states inside a single function.
<flux1> and then there there is of course the special feature of being able to handle matching a set of constructors and then then other constructors in some other function, and this all is still verified to be complete by the compiler
<Leonidas> I think there is a filter function that uses a predicate which is supposed to return `Fst or `Snd depending on what is decided. I think this is a rather elegant solution
<Leonidas> instead of 0 or 1 or having to use a type provided by the library
<flux1> let's not forget the most important case: talking with a LISPer and show that yeah OCaml can do symbols just fine with static typing, no ceremony needed
<jco> Leonidas: oh so polymorphic variants don't require to define a type with a name?
<Leonidas> jco: no, polymorphic variants are defined by their set of variants
<flux1> you can just do let a = `Hello "world" and that's a complete program there
<Leonidas> `String "foo" is of type [`String of string]
<jco> Leonidas: oh that's neat, gonna take a closer look at this
<jco> i guess it's much more than this
<Leonidas> Yojson uses polymorphic variants in a rather useful way that avoids everyone to have to have Yojson types flying around everywhere in their code
<Leonidas> also, they are extremely useful to implement this: https://keleshev.com/composable-error-handling-in-ocaml
<jco> Leonidas: yeah, I struggled parsing yojson types :(
<Leonidas> jco: how so? Can I help you somehow?
<flux1> you can also use it for "accidental" compatibility between libraries without them usign the same types
<flux1> well, they use the same types but no the same names for the types
<Leonidas> flux1: you call it accidental, I call it modular :p
<jco> especially with option types, the errors become huge and it's really hard to se what's going on
<flux1> Leonidas: fragile :)
<flux1> and quite difficult to cross-reference
<jco> Leonidas: thanks! I already solved them :)
<flux1> ..in a robust fashion
<Leonidas> Heh, we have Deferred.Result.t with 20ish polymorphic variants
<Leonidas> flux1: you can always annotate them if you name them
<Leonidas> but yes, there is some complexity for sure
<Leonidas> and I am somewhat annoyed the compiler does not warn you if you accidentally match on a variant that can't happen
<flux1> Leonidas: yes, but I believe the compiler loses track very soon of the constructor and the name of the type if you don't religiously annotate
<flux1> so automatic cross-referencing remains difficult
<Leonidas> So when removing error variants we actually have to be really careful otherwise there's dead match branches that will never be taken
<Leonidas> not a silver-bullet for sure.
<flux1> let foo (x: [`x]) = match x with `x -> () | `y -> () does fail
<flux1> but I guess you mean maybe case where the type is inferred
<Leonidas> flux1: yes. We don't want to write out 20+ variants in signatures, so we often write (t, _) Deferred.Result.t
<Leonidas> if the compiler could not infer this the whole concept would be dead on arrival, repeating the exact same issues that checked exceptions in Java have
<flux1> we may share the same opinion, that checked exceptions failed due to lack of polymorphism in Java
<companion_cube> checked exceptions would be a great idea if we had effects
<companion_cube> (but you need a full effect system because of higher-order functions)
<Leonidas> companion_cube: so, will we have that with multicore?
<companion_cube> with effects, possibly
<companion_cube> typed effects*
<companion_cube> this might take a long time though
nullcone has quit [Quit: Connection closed for inactivity]
<sadiq_> indeed, effects won't arrive until at least 2021
<tizoc> can caml_alloc_* functions ever fail? what do they do in that case, return NULL?
<def> jco: functors serve different purposes. when used as language level construct for linking, they don't scale well (there is work from Benjamin Pierce on this topic specifically), when used for making polymorphic data structure, they don't interact well with type level polymorphism (as is the case here)
<def> jco: ML module system is very good for data abstraction (encapsulation ?!), but functors are not the best part :P
<companion_cube> tizoc: I doubt they can :D
<jco> def: okay i can imagine, i always used functors for polymorphic data structures. Functors are parametrized modules right?
dckc has quit [Ping timeout: 256 seconds]
dckc has joined #ocaml
<jco> functors are nice, it looks like a more cleaner way to make polymorphism (vs polymorphism on objects in Java)
<tizoc> companion_cube: I'm calling ocaml allocation functions from rust, and at the moment I'm calling them as if they cannot fail (or at least, signal failure in any way other than crashing the runtime), but wanted to be sure that this is the right thing (couldn't find anything on the docs)
<def> jco: yes, and yes. they are just not a silver bullet :)
<companion_cube> tizoc: are you doing it without helpers? (like ocaml-rs)
<tizoc> yes, I'm following an approach based on caml-oxide
malc_ has left #ocaml ["ERC (IRC client for Emacs 28.0.50)"]
<jco> def: ok thanks, good to know whenever you hit these limitations
<companion_cube> tizoc: any plan to contribute to ocaml-rs? :)
<companion_cube> (it's very ergonomic)
<tizoc> yes, I was using ocaml-rs at first, it is good
<tizoc> but right now I don't need most of what it provides, and enforcing safety is more important
<companion_cube> well now I'm curious
<tizoc> companion_cube: it is nothing new, just enforcing correct (in regards to the GC) usage of ocaml values like in https://github.com/stedolan/caml-oxide
<tizoc> could be done in ocaml-rs too, but would break the API
<jco> (a bit off-topic, but) does rust have advantages over ocaml? rust takes many functional constructs it seems
<companion_cube> I mean, you're using caml-oxide directly? or just drawing inspiration?
<companion_cube> afaik ocaml-rs could break (internal) stuff, what matters to users is the macros
dhil_ has joined #ocaml
<companion_cube> jco: it's lower level and generally faster (ymmv, etc.)
<tizoc> jco: more control over memory representation of values, the borrow checker is cool, the macros are easier to work with than ppx (for trivial stuff at least), you can go prepare coffee while the compiler builds your libs/programs (I'm quite new to rust, but my impression is that the two languages are for different use cases, I would use ocaml for most stuff)
<tizoc> companion_cube: drawing inspiration, imo caml-oxide is not very complete, just an example of the (very cool) approach to safety
<companion_cube> tizoc: are you making a library? or bindings?
<tizoc> I'm making a library, but it is very minimal, for the specific use case I have, maybe it could become an actual thing later (or even made a patch to ocaml-rs, since it is what I have used so far I also drew inspiration from there)
<companion_cube> ahh, nice.
<companion_cube> well if you got a link, I'm very interested in rust<->ocaml .
<tizoc> companion_cube: https://github.com/tizoc/znfe working on a better interface to calling ocaml closures, will probably push that later today
<tizoc> see the small examples in testing/
<companion_cube> ouch, that's ambitious
nullcone has joined #ocaml
<companion_cube> jco: there is this thread https://discuss.ocaml.org/t/how-can-we-make-ocaml-libraries-useful-outside-of-the-ocaml-ecosystem/6176 which imho is better solved by rust
<companion_cube> you can make OCaml binaries useful to everyone, but libraries, less so, imho
<jco> thanks companion_cube and tizoc, so yeah you have more control on the memory than ocaml
<jco> with a "functional c++" style
<tizoc> I haven't touched C++ in a long time, but writing rust code gave me some C++ vibes (just much, much saner, to me rust feels comfortable to work with, I never enjoyed C++)
<tizoc> and so far the tooling looks quite good, my major complaint it slow compile times (ocaml compilation feels instantaneous)
<jco> so this may be preferrable for system programming/cryptography over ocaml
<jco> tizoc: i read they're doing a lot of work on improving build time, with an "incremental compiler"
<tizoc> cool, thats good to know
<jco> that might change
<companion_cube> compile times are also a lot worse in release mode
<companion_cube> (a bit like with ocaml flambda)
nkly_ has joined #ocaml
nkly_ has quit [Ping timeout: 256 seconds]
muskan has joined #ocaml
vicfred has quit [Quit: Leaving]
waleee-cl has quit [Quit: Connection closed for inactivity]
osa1 has quit [Ping timeout: 260 seconds]
TC01 has quit [Ping timeout: 240 seconds]
zmt00 has joined #ocaml
raver has quit [Read error: Connection reset by peer]
vicfred has joined #ocaml
narimiran has quit [Quit: leaving]
muskan has quit [Ping timeout: 245 seconds]
osa1 has joined #ocaml
nullcone has quit [Quit: Connection closed for inactivity]
jnavila has joined #ocaml
Haudegen has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
osa1 has quit [Ping timeout: 240 seconds]
superherointj has joined #ocaml
artart78 has joined #ocaml
eureton has joined #ocaml
<d_bot> <Anurag> compile times with flambda seem a little better in the current releases (compared to what i remember from a couple years ago). This could just be me getting used to longer compiles now, but i've been on a flambda switch since 4.09 and don't find the compile times to be too bad.
<companion_cube> the problem is mostly that some packages OOM before compiling, imho
<companion_cube> like dose3
TC01 has joined #ocaml
osa1 has joined #ocaml
mbuf has quit [Quit: Leaving]
eureton has quit [Read error: Connection reset by peer]
eureton has joined #ocaml
osa1 has quit [Remote host closed the connection]
eureton has quit [Quit: Simple IRC: The quit option.]
eureton has joined #ocaml
eureton has quit [Remote host closed the connection]
eureton has joined #ocaml
ggole has quit [Quit: Leaving]
eureton has quit [Ping timeout: 260 seconds]
waleee-cl has joined #ocaml
vicfred has quit [Quit: Leaving]
amiloradovsky has joined #ocaml
bacam has quit [Quit: reboot]
amiloradovsky has quit [Ping timeout: 244 seconds]
bacam has joined #ocaml
nullcone has joined #ocaml
raver has joined #ocaml
jnavila has quit [Quit: Konversation terminated!]
vicfred has joined #ocaml
zmt00 has quit [Ping timeout: 240 seconds]
dhil_ has quit [Ping timeout: 246 seconds]
amiloradovsky has joined #ocaml
<Leonidas> ah, bad memories, yeah
<Leonidas> that's also when I stopped using flambda
<d_bot> <Anurag> I do remember some issues around dose3 with opam plugin (i think it was depext). It was usually when i'd try to do something in a small VM on digitalocean
<companion_cube> like opam-publish just can't be installed on an flambda switch, in my experience
<companion_cube> but then I only have 16GB of ram :)
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
NSA_Spy has joined #ocaml
amiloradovsky has quit [Ping timeout: 244 seconds]
dhil_ has joined #ocaml
amiloradovsky has joined #ocaml
amiloradovsky has quit [Ping timeout: 240 seconds]
Haudegen has quit [Ping timeout: 260 seconds]
jco has quit [Quit: WeeChat 2.8]
tobiasBora2 has quit [*.net *.split]
Serpent7776 has quit [*.net *.split]
Exagone313 has quit [*.net *.split]
haskell_enthusia has quit [*.net *.split]
runciter has quit [*.net *.split]
tobiasBora2 has joined #ocaml
haskell_enthusia has joined #ocaml
runciter has joined #ocaml
Serpent7776 has joined #ocaml
Exagone313 has joined #ocaml
vicfred has quit [Quit: Leaving]
vicfred has joined #ocaml
nullcone has quit [Quit: Connection closed for inactivity]
dhil_ has quit [Ping timeout: 240 seconds]