adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml 4.07.0 release notes: https://caml.inria.fr/pub/distrib/ocaml-4.07/notes/Changes | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml | Due to ongoing spam, you must register your nickname to talk on the channel
quipa has quit [Quit: Leaving]
thomas_scrace has quit [Ping timeout: 272 seconds]
thomas_scrace has joined #ocaml
Jesin has joined #ocaml
jao has quit [Ping timeout: 268 seconds]
pierpa has quit [Quit: Page closed]
mfp has quit [Ping timeout: 252 seconds]
thomas_scrace has quit [Ping timeout: 244 seconds]
thomas_scrace has joined #ocaml
_whitelogger has joined #ocaml
pierpal has joined #ocaml
gtrak has joined #ocaml
silver has quit [Quit: rakede]
gtrak has quit [Ping timeout: 252 seconds]
thomas_scrace has quit [Ping timeout: 264 seconds]
thomas_scrace has joined #ocaml
roygbiv has joined #ocaml
roygbiv has quit [Quit: ™]
tormen has joined #ocaml
tormen_ has quit [Ping timeout: 268 seconds]
thomas_scrace has quit [Ping timeout: 252 seconds]
thomas_scrace has joined #ocaml
_whitelogger has joined #ocaml
thomas_scrace has quit [Ping timeout: 244 seconds]
thomas_scrace has joined #ocaml
_whitelogger has joined #ocaml
_whitelogger has joined #ocaml
_whitelogger has joined #ocaml
thomas_scrace has quit [Ping timeout: 244 seconds]
wagle has joined #ocaml
thomas_scrace has joined #ocaml
thomas_scrace has quit [Ping timeout: 244 seconds]
thomas_scrace has joined #ocaml
<sshine> can I implode a char list into a string using any kind of standard function?
<sshine> I understand that Buffer exists, but it appears to be mutable.
magicLl has joined #ocaml
<_y> sshine, String.init ?
Orbifx[m] has quit [Ping timeout: 240 seconds]
flux[m] has quit [Ping timeout: 264 seconds]
copy` has quit [Ping timeout: 264 seconds]
jimt[m] has quit [Ping timeout: 264 seconds]
caseypme[m] has quit [Ping timeout: 260 seconds]
drsmkl[m] has quit [Ping timeout: 260 seconds]
Walter[m] has quit [Ping timeout: 260 seconds]
equalunique[m] has quit [Ping timeout: 260 seconds]
HDurer[m] has quit [Ping timeout: 255 seconds]
theaspiringhacke has quit [Ping timeout: 256 seconds]
regnat[m] has quit [Ping timeout: 252 seconds]
spectrumgomas[m] has quit [Ping timeout: 260 seconds]
h11[m] has quit [Ping timeout: 240 seconds]
yetanotherion[m] has quit [Ping timeout: 240 seconds]
smondet[m] has quit [Ping timeout: 240 seconds]
peddie[m]1 has quit [Ping timeout: 240 seconds]
Bluddy[m] has quit [Ping timeout: 240 seconds]
Haudegen[m] has quit [Ping timeout: 264 seconds]
bglm[m] has quit [Ping timeout: 264 seconds]
isaachodes[m] has quit [Ping timeout: 260 seconds]
sven[m] has quit [Ping timeout: 260 seconds]
srenatus[m] has quit [Ping timeout: 260 seconds]
<_y> /ww peddie[m]1
dl3br[m] has quit [Ping timeout: 260 seconds]
aspiwack[m] has quit [Ping timeout: 260 seconds]
Multiocracy[m] has quit [Ping timeout: 260 seconds]
ejpcmac has quit [Ping timeout: 260 seconds]
remix2000[m] has quit [Ping timeout: 260 seconds]
rgr[m] has quit [Ping timeout: 260 seconds]
<sshine> _y, init : int -> (int -> char) -> string, seems like I'd have problems sticking a list in there.
<_y> let string_of_chars chars = let r = ref chars in String.init (List.length chars) (fun _ -> match !r with c :: r' -> r := r' ; c | _ -> assert false)
<sshine> how do I load Base in utop? I did 'opam install base', but 'open Base' says that Base is an unknown module.
<sshine> _y, so in response to Buffer being mutable, you give me a ref cell? :D
<_y> sshine, well, i do not quite see how you would initialize a non-constant contiguous memory without mutability
Orbifx[m] has joined #ocaml
smondet[m] has joined #ocaml
spectrumgomas[m] has joined #ocaml
<_y> i guess having Haskell defining String = [Char] is a hint of that
Haudegen[m] has joined #ocaml
copy` has joined #ocaml
<_y> i may be wrong
bglm[m] has joined #ocaml
Walter[m] has joined #ocaml
isaachodes[m] has joined #ocaml
h11[m] has joined #ocaml
Bluddy[m] has joined #ocaml
theaspiringhacke has joined #ocaml
yetanotherion[m] has joined #ocaml
dl3br[m] has joined #ocaml
jimt[m] has joined #ocaml
Multiocracy[m] has joined #ocaml
regnat[m] has joined #ocaml
rgr[m] has joined #ocaml
peddie[m]1 has joined #ocaml
srenatus[m] has joined #ocaml
HDurer[m] has joined #ocaml
caseypme[m] has joined #ocaml
<_y> sshine, what’s the problem with mutability, by the way?
equalunique[m] has joined #ocaml
ejpcmac has joined #ocaml
drsmkl[m] has joined #ocaml
magicLl has quit [Ping timeout: 252 seconds]
remix2000[m] has joined #ocaml
flux[m] has joined #ocaml
<sshine> _y, do you mean what the problem is with mutability in general or in my particular case?
<_y> in your case
<_y> in general as well, since you’re programming in OCaml anyway
<_y> for your question about utop, you need to use findlib, which allows you to #require the package for Base: http://mirror.ocamlcore.org/wiki.cocan.org/tips_for_using_the_ocaml_toplevel.html
sven[m] has joined #ocaml
aspiwack[m] has joined #ocaml
<sshine> _y, thanks a bunch for that one!
<sshine> _y, I'll try and write my function using a Buffer and String.foldi from Base, and then I can try and write how I'd like to have written it in SML.
<_y> (or you can always find in your filesystem and load all the object files manually (those of your library AND of its dependencies), either by giving their full path in the command line invocation of utop, or later with the #load directive; but life would be a nightmare, so findlib is essentially a tool that automates this)
<_y> sshine, i am not sure i understood you, do you want “char list → string” or “string → char list”?
<sshine> _y, char list -> string
HDurer[m] has quit [Ping timeout: 264 seconds]
<_y> then String.foldi won’t help you, will it ?
<sshine> _y, I can see that it's common to put #use "topfind";; in your ~/.ocamlinit. is it also common to put #require "base";;?
<sshine> _y, well, with a Buffer it might. I can add stuff to the buffer, and eventually Buffer.contents
nullifidian_ is now known as nullifidian
<_y> sshine, dunno, as for myself i used to #require "batteries", and now i #require "containers" and some other things
HDurer[m] has joined #ocaml
<_y> i don’t see reasons not to do so
<sshine> _y, I started coding Ocaml less than a week ago, and while I have some experience with SML and Haskell, the ecosystem is super confusing. like, I think batteries is comparable to Jane Street's Base (and I assume that's what base/Base always refers to), and that some people don't like Batteries, except apparently a large part of who writes answers on StackOverflow. I learned that "containers" isn't exactly a
<sshine> replacement for batteries/base, but rather--I guess from the name--a collection of well-designed containers, but not an entire standard library.
<_y> that’s true
<_y> the stdlib being too restricted has long been a bone of contention
<_y> it’s improving slowly
<sshine> comparing this to Standard ML, I think it's nice to at least have too many options rather than too few.
<sshine> but I just don't know which to pick. so I'll go with Base for now.
<_y> and last release of OCaml sort of unlocked the situation around the stdlib, so that useful additions should come shortly
<sshine> what version is that?
<_y> 4.07
<sshine> what's the preferred way to get that? I can see that my system runs 4.04.0
<_y> sshine, and you missed the babel tower of build systems
<_y> i have been told recently that the war was over and that JaneStreet’s champion was the winner (“dune” is its name — forget about “oasis”, and the countless systems which have fallen)
<_y> sshine, oh! you definitely need opam before doing anything else
<sshine> I've got opam.
<_y> then “opam switch -A 4.07.0 name_of_your_new_switch && eval $(opam config env)”
<sshine> and opam will automatically download 4.07.0? what's a switch name?
<_y> whatever you like
<_y> if you lack imagination, you can just do “opam switch 4.07.0” and the switch name will reflect the version number
<sshine> ok. :)
<_y> but a good practice is to have one switch per project, with a specific ocaml version and just the packages you need for that project, so as to isolate your project’s environment
<sshine> right, ok.
<_y> plus a switch for daily fun :-)
<sshine> I'm confused about something: https://gist.github.com/sshine/8a43ce5c6bdf1deb664c1f5726ebebe2 -- it looks like String.foldi takes three args: a string, an initial accumulated value 'a, and a function (int -> 'a -> char -> 'a). 'String.foldi "Hello" (Buffer.create 4)' gives me this weird type: init:(Buffer.t -> '_a) ->
<_y> so giving meaningful names to your switches is a good idea (especially so since opam switches cannot be renamed afterwards)
<sshine> it's like the second argument (Buffer.create 4) isn't fed into init, since the accumulating type has become (Buffer.t -> '_a) rather than Buffer.t
<_y> that’s because of the labelled arguments
<sshine> so init isn't the second argument?
<_y> yes, but here you have to name it explicitely
<_y> String.foldi "Hello" ~init:(Buffer.create 4)
<sshine> what did I do then? where did (Buffer.create 4) end up?
<sshine> ok.
<_y> String.foldi : bytes -> init:'a -> f:(int -> 'a -> String.elt -> 'a) -> 'a
<_y> here, the return type is a type variable, so it may very well be a function type 'b -> 'c
<_y> so the type system cannot say that this is a function of 3 variables only, 2 of them being named
<_y> so when you write this: String.foldi "Hello" (Buffer.create 4)
<_y> the first unnamed argument ("Hello") is mapped to the first unnamed parameter (of type bytes)
<sshine> ahhh
<sshine> no, wait. I still don't get it.
<sshine> (Buffer.create 4) couldn't possibly become ~f.
<discord> <Christophe> let l = ['H';'e';'l';'l';'o'] in String.init (List.length l) (List.nth l);;
<discord> <Christophe> Int pure stdlib 😃
<discord> <Christophe> in*
<_y> and the second unnamed argument (Buffer.create 4) is mapped to a second unnamed parameter, so there must be a second unnamed parameter, so type inference guess that 'a is an arrow type 'b -> 'c
<_y> with 'b the type of (Buffer.create 4), that is, Buffer.t
<_y> hence the result utop gives you
<_y> sshine, a feature of named arguments is that they allow to write arguments in another order than the type says
<_y> the thing to remember is: there is a distinction between named parameters and unnamed parameters. when you have a function whose type interleaves N named parameters and U unnamed parameters, you can call it by interleaving N named arguments (with the same names, of course) and U unnamed arguments
<_y> you have to preserve the order between the U unnamed arguments, but you can reorder the N named arguments as you wish
Rosslaew has joined #ocaml
<discord> <Christophe> (is the bridge working ...)
<discord> <Christophe> Yes, good 😃
<Rosslaew> sshine, did you see the code I gave ? :)
<sshine> Rosslaew, I didn't!
<sshine> Christophe: thanks for the String.init thing :) I had hoped I could fold.
<_y> Rosslaew, that’s O(n²) !
<sshine> Rosslaew, oh, you are Christophe. yes, I did get that.
<sshine> _y, okay, I understand what went wrong with the unnamed parameter. thanks a bunch.
<_y> (maybe http://paste.awesom.eu/0eqk&ln would have been easier to read)
<Rosslaew> _y, true :(
<Rosslaew> Actually, I believe in 4.07 we could do String.of_seq (List.to_seq l)
<Rosslaew> Shouldn't seqs be efficient ?
orbifx1 has joined #ocaml
<Rosslaew> (I believe because I'm still installing the switch :))
<sshine> apparently Base has String.of_char_list...
<_y> you believe correctly
<_y> as for performance, you should asc companion_cube ;-)
<Rosslaew> sshine, didn't you ask for a stdlib option ?
<Rosslaew> and _y I was thinking of the stdlib ones, but I suppose the performance should be similar at least :)
<_y> (there is no magic immutability though, String.of_seq uses Bytes.of_seq which mutates things https://github.com/ocaml/ocaml/blob/trunk/stdlib/bytes.ml#L353 )
<sshine> Rosslaew, I'm not even sure what I'm asking for. as long as it compiles and people don't say "Wow, you really shouldn't do that!" ;-D
<_y> Rosslaew, yes i know, but c*mpanion_cube is your local expert on this topic, and the author of stdlib’s Seq
<Rosslaew> Oooh did he do that one also ? Nice :)
<sshine> https://gist.github.com/sshine/ef8c7c2e3c4f3f6c702a88b6cadf7f4a -- question: why do I get this type error, when f's signature is (int -> 'a -> String.elt -> 'a) and 'c' is in the third place and is compared against ' '?
<_y> i believe that stdlib’s Seq is a compromise, so that it has reasonable performance, particularly if using flambda. it should be faster than more elaborate generators, but nothing can beat raw iterators (('a -> unit) -> unit) for pure speed
AltGr has joined #ocaml
orbifx1 has quit [Ping timeout: 264 seconds]
<_y> sshine, i do not have base at hand, but the only explanation i see is that B
<_y> sshine, i do not have base at hand, but the only explanation i see is module Base redefining the comparison operator (=) as the comparison between integers
<Rosslaew> it does
<Rosslaew> If you want the polymorphic = you need Polymorphic_compare.equal
<sshine> ohhh.
<sshine> but there's a reason they don't like polymorphic equality comparison, right?
<Rosslaew> Or Poly.equal apparently
<_y> the default (=) is polymorphic: it has type 'a -> 'a -> bool, it works on values of any type by inspecting their runtime representation, which is considered unsafe / bad practice
<Rosslaew> There is, it can lead to subtle errors
<_y> sshine, so in fact, you want string -> string, not char list -> string ?
<sshine> _y, yes, the task is acronym "Blue Screen of Death" ~> "BSoD"
<sshine> _y, I'm going with a Buffer for now.
<_y> you’re right, using a buffer is the better (only?) way for this kind of tasks
<_y> note that in this snippet, you only complicate things by using fold and passing around your buffer, while in fact you only perform an imperative operation (of type unit)
<_y> you’d better start with “let buf = Buffer.create 4” then simply iterate on the string, and finally call Buffer.contents
<sshine> _y, and what would you use for iterating a string?
<_y> String.iter / String.iteri / for-loop
<sshine> apparently, String.iteri isn't part of Base.
<_y> it’s part of stdlib
<sshine> ok, so no Base.
<_y> it seems to me that you do not need the index anyway, but maybe your actual task is more complicated
<sshine> it seems to me that I do need the index, since I'd want to add the letter if it's prefixed by a space.
<_y> hmm right
<sshine> but String.iteri seems cleaner, thanks.
ozzymcduff has joined #ocaml
caltelt has quit [Ping timeout: 272 seconds]
Rosslaew has quit [Remote host closed the connection]
ohama has quit [Remote host closed the connection]
<sshine> when I 'open Base', it seems that I can no longer write 'module CharSet = Set.Make(Char)'. do I create sets differently using Base? I'd like to use Base because it has String.foldi.
<_y> yes, base gives up on being compatible with stdlib iirc
<_y> what is the error?
<sshine> that Set.Make isn't a functor in Base, it seems from the documentation.
quipa has joined #ocaml
<sshine> I feel like switching standard library every other exercise.
rpcope has joined #ocaml
ohama has joined #ocaml
quipa has quit [Max SendQ exceeded]
<sshine> or doing stuff like: 'module CharSet = Set.Make(Char)' and *then* 'open Base' :D
quipa has joined #ocaml
<sshine> can I localize .ocamlinit to a specific project?
quipa has quit [Read error: Connection reset by peer]
<_y> yes
Guest8532 has joined #ocaml
<octachron> sshine, Base sets and maps use a different approach, see https://discuss.ocaml.org/t/examples-of-using-base-map/1197/2
<_y> sshine, pro-tip, here is the one i wrote just yesterday and which lets me take profit of my global ~/.ocamlinit : http://paste.awesom.eu/mtkd
<sshine> octachron, oh, headache.
<sshine> _y, and why do you disable interactive mode while running these?
freyr69 has joined #ocaml
<_y> sshine, to make these commands quiet, as much as possible; this is common in .ocamlinit files
<sshine> _y, ok.
<_y> octachron, so is it only for me that discuss.ocaml.org is super super super (super) slow?
<sshine> _y, it isn't for me.
<_y> :-(
<_y> it took me the whole afternoon for the following sequence: [sign up] → [check username availability] → [check it again] → [a confirmation mail has been sent] → [mail received, confirming] → [congratulation, you are now— wow look, a notification] → [load the notification pane] → [load the page of the notification]
<_y> at least i know it by heart now :o
<_y> (for instance, i did not start yet to have the beginning of the start of a glimpse of the shadow of having received something from the server for your url)
<sshine> do I understand it correctly that it's never idiomatic or efficient to use a function composition operator in ocaml?
<sshine> (SML's o, Haskell's :)
<sshine> whoops
<sshine> Haskell's .
<sshine> (a little auto-completion there)
Guest8532 has left #ocaml [#ocaml]
<_y> or maybe some js blocks rendering and i just have to wait for it to overflow and crash
<_y> sshine, i guess that nowadays with flambda, writing (g % f) should be just as efficient as (fun x -> g (f x)), and ((g % f) x) should be just the same as (g (f x))
<_y> but you should wait for more expert answers
Haudegen has joined #ocaml
<_y> stdlib still does not define (%) (but some “augmented standard libraries” do), but it does define (|>) : 'a -> ('a -> 'b) -> 'b, and chaining things with |> is idiomatic (and just as efficient, because (|>) is most certainly always inlined)
<octachron> part of the problem with composition is the value restriction that makes `fun x -> f(g x)` not completely equivalent to `f%g`
<ZirconiumX> One of the most beautiful things I've found about OCaml is that you can figure out what a function does from just its type signature
<sshine> ZirconiumX, that seems to be a general thing in FP.
<sshine> ZirconiumX, sorry, in typed ML, of course. :-P
<sshine> ZirconiumX, and in extension, by looking at a signature of a function that does one thing, it is written almost mechanically.
<ZirconiumX> The equivalent thing is not generic in C, and not idiomatic or clear in C++ or Rust
<ZirconiumX> Some people didn't get used to the arrow notation though
mfp has joined #ocaml
<dmbaturin> ZirconiumX: Well, to some extent. The classic: 'a M.t -> ('a -> 'a M.t) -> 'a M.t :)
<dmbaturin> Generally I agree of course.
<ZirconiumX> Which is (>>=) AKA bind, right?
<dmbaturin> Speaking of which, do we have a working ocamloscope anywhere?
<dmbaturin> ZirconiumX: Yes.
<ZirconiumX> Ocamloscope?
<reynir> ZirconiumX: like "hoogle" from Haskell if you know that. You can search by type etc
<dmbaturin> Ocamloscope was a service for searching functions by types, like hoogle.
<ZirconiumX> I didn't know of that, no
<ZirconiumX> ^^;
<dmbaturin> Then it dies, then the author rewrote it and sort of deployed it, but I've never seen it working since then.
<dmbaturin> And I miss that service.
thomas_scrace has quit [Ping timeout: 244 seconds]
thomas_scrace has joined #ocaml
bartholin has joined #ocaml
<xvilka> dmbaturin: was it opensource?
<reynir> Yes, I believe so
thomas_scrace has quit [Ping timeout: 268 seconds]
Rosslaew has joined #ocaml
<Rosslaew> sshine, you can access the OCaml standard library after opening Base, it resides in the Caml module
<Rosslaew> (like Caml.Set.Make)
<Rosslaew> Of course it's probably not compatible with Base's stuff
leastbit has joined #ocaml
leastbit has quit [Excess Flood]
leastbit has joined #ocaml
leastbit has quit [Excess Flood]
leastbit has joined #ocaml
leastbit has quit [Excess Flood]
thomas_scrace has joined #ocaml
leastbit has joined #ocaml
leastbit has quit [Excess Flood]
<sshine> since X.compare returns -1, 0 or 1, what's the convention for matching these but not causing missing pattern warnings.
<sshine> (SML and Haskell have a compare type with constructors like LT, EQ, GT).
moolc has joined #ocaml
<octachron> sshine, compare returns 0 for equality but (< 0) for inferior and (> 0) for superior
<octachron> the fact that a specific function always return 1 or -1 is an implementation details
<sshine> octachron, would you ever write 'match Int.compare x y with ...'?
bezirg has joined #ocaml
<sshine> (assuming Int is a valid library in your world.)
ziyourenxiang has joined #ocaml
<octachron> in this case I would probably write an if/then/else if/else rather than a match with two guards
<sshine> https://stackoverflow.com/a/18416055/235908 -- this one suggests either have my own custom compare type, or use a library that does this. but Base doesn't do this, and I'm trying to not switch standard library every time I solve a new exercise because this other standard library does this tiny part slightly different at the convenience of this particular task.
bezirg has quit [Ping timeout: 252 seconds]
<reynir> sshine: Write your own standard library! :D
<sshine> hehe.
moolc has left #ocaml ["ERC (IRC client for Emacs 27.0.50)"]
<Rosslaew> Beware, absolutely beautiful comparison that everyone will love :
<Rosslaew> type compare = | Lt | Eq | Gt
<Rosslaew> let my_compare x y : compare = Obj.magic (compare x y + 1)
<Rosslaew> (I'll see to the door)
<reynir> Rosslaew: lol D:
<sshine> Rosslaew, what's the joke?
<sshine> Rosslaew, that -1, 0, 1 is just a convention that Ocaml always had and always will have?
<reynir> sshine: it abuses the memory representation of the type `compare` and integers to convert {-1,0,1} into {Lt,Eq,Gt}
<octachron> Obj.magic should not be used outside of dire and imperious circumstances
<Rosslaew> What they said :)
<Rosslaew> Some say we should not talk about its existence to newcomers, I'd say it's good to know it exists and that you should not use it as a general rule
Haudegen has quit [Remote host closed the connection]
<Rosslaew> and sshine the -1. 0 or 1 is a convention inherited from C that I am told people have tried to change, but that was too ingrained in code to change anymore
<octachron> also like I said "let compare x y = List.length x - List.length y" is a valid "compare" function
<octachron> Rosslaew, the problem with Obj.magic is that the good use cases (implementing a stronger type system in OCaml) and the beginner's use case (casting away type errors) are diametrically opposed
<Rosslaew> I'll trust you on it, I am not good enough in type systems to see how it can make it stronger :)
<sshine> Rosslaew, ah, okay. I know Obj.magic from Moscow ML. :)
<octachron> Rosslaew, for instance, Coq uses Obj.magic when extracting code to OCaml, but those uses are safe because they have been checked by Coq's type system.
<Rosslaew> I'm thinking though, one *could* use compare in conjunction with Int.sign, if they really don't like the int representation, I guess
<Rosslaew> I see, thanks octachron , once again :)
jao has joined #ocaml
shw has joined #ocaml
<sshine> Rosslaew, I don't like the int representation because I'm used to restricting the range of my function to as few values as are needed, but given that it's an idiom in Ocaml, I sort of like 'match Int.compare x y with | z when (z < 0) -> ... | z when (z > 0) -> ... | _ -> ...'
<Rosslaew> oh anyway my bad, Int.sign is in Base not in the std lib, I had opened Base earlier and forgot :/
quipa has joined #ocaml
unyu has quit [Quit: Reboot.]
quipa has quit [Read error: Connection reset by peer]
rpcope has quit [Ping timeout: 264 seconds]
unyu has joined #ocaml
bezirg has joined #ocaml
bezirg has quit [Remote host closed the connection]
<Leonidas> how do I avoid accidental module capturing in ppx_metaquot?
<Leonidas> I have an ppx which uses Array.length but if I use it in a Core library it picks up Core's versions of things and that's not what I want
<Leonidas> In 4.07 I could use Stdlib.Array.length but the problem is a general one.
dacid has joined #ocaml
<discord> <Christophe> This is not a general solution, but in the case of Core how about using Caml.Array.length ?
<Leonidas> Christophe: This is what I currently have, but this requires my ppx to depend on Core/Core_kernel/Base just for the `Caml` module.
<ZirconiumX> Isn't Caml just the OCaml standard library?
<ZirconiumX> Then maybe just conditional compile?
Haudegen has joined #ocaml
<Leonidas> ZirconiumX: conditional on what? I do not know in my ppx if the code it is used in has overridden stdlib modules.
<ZirconiumX> No, but the user does
<ZirconiumX> So have one which accesses Array.length and one which accesses Caml.Array.length as Core compatibility
remix2000 has joined #ocaml
<octachron> Leonidas, one solution might be to have a runtime alias module that just defines aliases to the modules that the ppx requires
<Leonidas> octachron: Yes, that's an idea, thanks.
<Leonidas> Unhygienic macros strike again :D
<reynir> D:
<sshine> with Base, how do I check if a list is empty?
<ZirconiumX> I can suggest a solution without Base
<ZirconiumX> sshine: ^
<discord> <thangngoc89> ouch. too late
<ZirconiumX> Ninja'd
<discord> <thangngoc89> ooh. our code looks the same 😄
<sshine> I can write this function. I am asking if it exists in Base, but if there's some other library in which it exists, I'll accept that as well.
bezirg has joined #ocaml
<sshine> oh, my_list = [] is apparently not problematic (except for those who object to polymorphic equality testing?)
<discord> <Christophe> This should not be a problematic case
noitakomentaja has joined #ocaml
silver has joined #ocaml
jaar has joined #ocaml
noitakomentaja has quit [Ping timeout: 250 seconds]
<sshine> hmm
pierpal has quit [Read error: Connection reset by peer]
chindy has quit [Ping timeout: 252 seconds]
<discord> <Christophe> sshine: you can read that for more explaination : https://dev.realworldocaml.org/maps-and-hashtables.html
<discord> <Christophe> erf
thomas_scrace has quit [Ping timeout: 252 seconds]
tg has quit [Ping timeout: 265 seconds]
chindy has joined #ocaml
thomas_scrace has joined #ocaml
tg has joined #ocaml
noitakomentaja has joined #ocaml
Rosslaew has quit [Ping timeout: 264 seconds]
gtrak has joined #ocaml
thomas_scrace has quit [Ping timeout: 268 seconds]
thomas_scrace has joined #ocaml
pierpal has joined #ocaml
pierpal has quit [Read error: Connection reset by peer]
pierpal has joined #ocaml
noitakomentaja has quit [Ping timeout: 250 seconds]
nullifidian has quit [Read error: Connection reset by peer]
noitakomentaja has joined #ocaml
<Leonidas> ZirconiumX: What. You use the is-list-empty OPAM package, of course.
<companion_cube> wait, do you use ppx-is-list-empty, ocp-is-list-empty, isle (from Bunzli) or core_is_list_empty?
nullifidian has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
<reynir> bs-is-list-empty if you're using bucklescript
bezirg has quit [Ping timeout: 252 seconds]
magicL has joined #ocaml
Haudegen has quit [Remote host closed the connection]
_andre has joined #ocaml
pierpal has quit [Read error: Connection reset by peer]
pierpal has joined #ocaml
ehirdoy has quit [Ping timeout: 268 seconds]
pierpal has quit [Ping timeout: 252 seconds]
pierpal has joined #ocaml
gtrak has quit [Quit: WeeChat 2.1]
gtrak has joined #ocaml
Guest76242 has joined #ocaml
ehirdoy has joined #ocaml
Guest76242 has quit [Remote host closed the connection]
ozzymcduff has quit [Quit: Textual IRC Client: www.textualapp.com]
magicL has left #ocaml ["Leaving"]
chindy has quit [Quit: No Ping reply in 180 seconds.]
ehirdoy has quit [Ping timeout: 276 seconds]
chindy has joined #ocaml
ehirdoy has joined #ocaml
spew has joined #ocaml
noitakomentaja has quit [Quit: WeeChat 2.0.1]
ehirdoy has quit [Ping timeout: 264 seconds]
FreeBirdLjj has quit [Remote host closed the connection]
Denommus has joined #ocaml
pierpal has quit [Ping timeout: 244 seconds]
ehirdoy has joined #ocaml
FreeBirdLjj has joined #ocaml
dhil has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
<Leonidas> companion_cube: I think you meant Iisle from Bunzli.
FreeBirdLjj has joined #ocaml
<Drup> Leonidas: too long
<Drup> Bunzli follows the bytecode convention of only having 4-letter names
<Leonidas> RRRRRRrrrresult!
<Leonidas> Cmdliner does not fit his own convention at all. It is neither short nor cryptic.
Rosslaew has joined #ocaml
<Drup> Well, that's sort of the exception that confirms the rule: uu.{2}, tsdl, tgls, xmlm, otfm, ....
<Drup> Leonidas: cmdliner is pretty old. his style was still in developement
<flux[m]> cool. I have the same approach to my host names :)
<reynir> oh, I have that for reyn.ir! :D
<companion_cube> is there a llvm.ir? :D
<companion_cube> y'all, I think I really like rust
al-damiri has joined #ocaml
<Leonidas> companion_cube: is it like a coming-out?
<Leonidas> I have a rust book on my desk and the same as ebook but for the life of me couldn't find a usecase for it.
<Leonidas> Also my last impression of 0.10 was pretty unusable :|
<Leonidas> I do respect their amazing community though and their approach on designing things exactly right, which is also what I like in OCaml
<ZirconiumX> The language has progressed quite a bit from 0.10
<ZirconiumX> But honestly I'm not a massive fan of the function syntax
leastbit has joined #ocaml
<ZirconiumX> Call me a member of the Obfuscated OCaml Club, but I like how terse the OCaml function declaration syntax is
gtrak has quit [Ping timeout: 272 seconds]
<ZirconiumX> Granted, it's a lot less explicit
Denommus has quit [Read error: Connection reset by peer]
gtrak has joined #ocaml
leastbit has quit [Read error: Connection reset by peer]
bezirg has joined #ocaml
dhil has quit [Quit: Leaving]
<reynir> \x->x
<companion_cube> 0.10 is so old
<companion_cube> rust 1.0 and beyond is really impressive though
<companion_cube> ZirconiumX: rust is more verbose on that, for sure, it's not exactly targeting the same kind of programs
<companion_cube> but I was amazed at how simple and clean multi-trheading was (even compared to lwt)
<companion_cube> (I now have a flagship program of 300loc that I can boast over :DDD)
Rosslaew has quit [Ping timeout: 264 seconds]
freyr69 has quit [Remote host closed the connection]
wagle has quit [Quit: http://quassel-irc.org - Chat comfortably. Anywhere.]
wagle has joined #ocaml
roygbiv has joined #ocaml
leastbit has joined #ocaml
leastbit has quit [Client Quit]
gtrak has quit [Ping timeout: 268 seconds]
bezirg has quit [Ping timeout: 272 seconds]
<flux[m]> I don't quite consider lwt concurrency very clean, but I guess I should look at how rust does it.
<ZirconiumX> flux[m]: C++ like, but with sharing through library data structures
<companion_cube> flux[m]: well here I was just using a thread pool and channels to communicate
<companion_cube> with the benefit that you can't get a data race
|jbrown| has joined #ocaml
<spew> why does everyone use lwt and not the threads library that comes with ocaml?
<companion_cube> the threads library works, I sometimes use it, but it's not as polished as rust's
<spew> I'm not comparing it to rust, I'm asking about lwt vs. threads
<companion_cube> ah well, it's not the same use case I suppose
gtrak has joined #ocaml
<ZirconiumX> spew: cooperative threading and preemptive threading have different use cases
<spew> I thought lwt was cooperative too
<ZirconiumX> Lwt is, yeah
<ZirconiumX> Threads is preemptive
<ZirconiumX> And also uses pthread, I think
<spew> oh
<spew> I thought threads was cooperative
<ZirconiumX> Right, I messed that up
leastbit has joined #ocaml
leastbit has quit [Excess Flood]
<ZirconiumX> Lwt is cooperative
<spew> that's what you said
leastbit has joined #ocaml
<ZirconiumX> Threads is concurrent
<spew> concurrent doesn't imply preemptive
<ZirconiumX> No, it doesn't, which is why I said I messed up
<spew> that whole "concurrency is not parallelism" thing
<ZirconiumX> But it is parallel
<spew> I thought it wasn't parallel though
<spew> "The threads library is implemented by time-sharing on a single processor."
jnavila has joined #ocaml
<spew> hence concurrent but nothing parallel
leastbit has quit [Client Quit]
<ZirconiumX> "System threads. This implementation builds on the OS-provided threads facilities: POSIX 1003.1c threads for Unix, and Win32 threads for Windows."
<spew> it's weird
<Drup> It's not parallel.
<spew> I don't understand how they are implemented on top of pthreads and yet they claim it's not parallel
<spew> I should probably just read the implementation
<Drup> (there is a lock to prevent parallel execution because the GC can't deal with it)
<ZirconiumX> Okay, yeah, I'm messing this up ^^"
<spew> nonetheless, it seems weird to me that EVERYONE uses lwt when there is a perfectly good concurrency library already included
<spew> and which in my opinion has a much saner concurrency model
<ZirconiumX> Lwt does a better job at hiding itself
<Drup> spew: lwt is better though as a promise library, not a thread library
<Drup> (people use to say "green thread", which were not threads at all really)
<spew> but aren't those just two different ways of modelling concurrency?
<Drup> Anyway, you can spawn lot's of promises with lwt, it's very lightweight
<Drup> It's much more adapted to a functional programming style
<spew> that makes sense
<spew> since reading a channel is necessarily destructive
<spew> ok good I feel better now
<Drup> lwt has a special module, Lwt_preemptive, that uses normal Threads to deal with ... preemptive things (like external C libraries)
<Drup> And so everyone can live happy together, as long as you're not trying to call blocking things in Lwt promises :p
<ZirconiumX> Or if you do, that you tell Lwt that it will block
<ZirconiumX> Plus I think OCaml threads doesn't scale as well as Lwt, because Lwt has a libev backend
rpcope has joined #ocaml
roygbiv has quit [Quit: ™]
dacid has quit [Ping timeout: 272 seconds]
Haudegen has joined #ocaml
<flux[m]> is there any point in "future proofing" Lwt code by using ie. Lwt_mutex instead of assuming multitasking is not pre-emptive? could there ever be a migration from Lwt to ocaml multicore in a way that pre-empting is introduced?
<Armael> I really doubt so
<Armael> it would probably break most of the code using lwt (and probably lwt's implementation itself)
<flux[m]> well, lwt could fix itself, but yeah, there's ton of apps that would break as well
<flux[m]> but there could be fork "lwtmc" that would actually be a migration path
<Armael> sure, but it's better to wait for that to appear
rpcope has quit [Ping timeout: 272 seconds]
Jesin has quit [Quit: Leaving]
ziyourenxiang has quit [Ping timeout: 252 seconds]
dmiles has quit [Read error: Connection reset by peer]
Jesin has joined #ocaml
jnavila_ has joined #ocaml
AltGr has quit [Ping timeout: 264 seconds]
kamog has joined #ocaml
pierpal has joined #ocaml
jnavila has quit [Ping timeout: 252 seconds]
jnavila_ has quit [Ping timeout: 252 seconds]
dmiles has joined #ocaml
Anarchos has joined #ocaml
tokomak has joined #ocaml
<Drup> flux[m]: it's far too early to worry about that.
wagle has quit [Quit: http://quassel-irc.org - Chat comfortably. Anywhere.]
zv has joined #ocaml
jnavila_ has joined #ocaml
roygbiv has joined #ocaml
wagle has joined #ocaml
jaar has quit [Quit: Leaving]
orbifx1 has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
Anarchos has quit [Quit: Vision[0.10.3]: i've been blurred!]
Anarchos has joined #ocaml
Anarchos has quit [Remote host closed the connection]
Anarchos has joined #ocaml
<reynir> huh
<reynir> Ast_convenience_XXX seems to have disappeared from META in latest ppx_tools_versioned ?
Haudegen has quit [Read error: Connection reset by peer]
void_pointer has joined #ocaml
Guest78852 has joined #ocaml
bezirg has joined #ocaml
Haudegen has joined #ocaml
jack5638 has quit [Ping timeout: 272 seconds]
pistachio has quit [Ping timeout: 268 seconds]
pistachio has joined #ocaml
void_pointer has quit [Quit: http://quassel-irc.org - Chat comfortably. Anywhere.]
FreeBirdLjj has joined #ocaml
jack5638 has joined #ocaml
Anarchos has quit [Quit: Vision[0.10.3]: i've been blurred!]
FreeBirdLjj has quit [Ping timeout: 244 seconds]
sillyotter has joined #ocaml
sillyotter has quit [Client Quit]
erkin has joined #ocaml
pierpal has quit [Read error: Connection reset by peer]
pierpal has joined #ocaml
roygbiv has quit [Quit: ™]
erkin has quit [Remote host closed the connection]
picolino has quit [Remote host closed the connection]
gtrak has quit [Ping timeout: 252 seconds]
jnavila_ has quit [Remote host closed the connection]
gtrak has joined #ocaml
spew has quit [Quit: going home]
<_y> so i played with dune and everything is simple, but there is a something that i fail to do
leastbit has joined #ocaml
<_y> say that i am making a library mylib, i would like to pack everything into a single toplevel module Mylib
<_y> my library contains modules A and B, which would only be visible externally as Mylib.A and Mylib.B
<_y> dune with wrapped=true does that, but the internal names Mylib__A and Mylib__B remains visible from outside, what i would like to avoid
<_y> a second, related issue, is that i would like to hide module C that is for internal use only
<_y> dune’s documentation says to write the toplevel module Mylib myself, so that i can choose what to expose
<_y> if i do that, i indeed get a toplevel module Mylib with the expected interface, but the formely-auto-generated module Mylib, with everything exposed, is still generated with the name Mylib__
<_y> and of course, Mylib__A, Mylib__B, Mylib__C are still visible from outside
<_y> is there a way around this?
leastbit has quit [Quit: Mutter: www.mutterirc.com]
<_y> hmmm, “The files _build/install/default/lib/Mylib/Mylib.cma and _build/install/default/lib/Mylib/Mylib.cma disagree over interface Mylib”
<_y> interesting
<_y> for my 2nd issue, i guess that i can just remove _build/install/default/lib/Mylib/Mylib.* manually…
<_y> i mean, remove _build/install/default/lib/Mylib/Mylib__.*
td123 has joined #ocaml
<_y> oh, maybe it is just as simple as writing “module A = struct include A end” instead of “module A = Mylib__A” in Mylib.ml
<_y> then i can get rid of all Mylib__* files
gtrak has quit [Ping timeout: 244 seconds]
<_y> in the generated documentation, too
<_y> and it seems that odoc is smart enough so as to replicate the documentation of the included module :-) the only disturbing thing is that the documentation shows “include Mylib.A” which does not make sense for the external user, but well, i can live with it
<_y> still it seems to me that dune should have a way of not exposing Mylib__* in the first place
<_y> i found https://github.com/ocaml/dune/issues/99 and https://github.com/ocaml/dune/pull/106 , the PER has been unmerged if i understand correctly
_andre has quit [Quit: leaving]
bezirg has quit [Remote host closed the connection]
tokomak has quit [Quit: http://quassel-irc.org - Chat comfortably. Anywhere.]
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]
caltelt has joined #ocaml
orbifx1 has quit [Ping timeout: 272 seconds]
pierpa has joined #ocaml
Haudegen has quit [Remote host closed the connection]
troydm has joined #ocaml
dx- has joined #ocaml
richi235 has quit [Ping timeout: 268 seconds]
dx has quit [Ping timeout: 268 seconds]
dx- is now known as dx
brettgilio has joined #ocaml
Jesin has quit [Quit: Leaving]
Jesin has joined #ocaml
brettgilio has quit [Quit: Konversation terminated!]
brettgilio has joined #ocaml
thomas_scrace has quit [Ping timeout: 268 seconds]
jao has quit [Ping timeout: 276 seconds]
thomas_scrace has joined #ocaml
zv has quit [Ping timeout: 252 seconds]
jao has joined #ocaml
brettgilio has quit [Quit: Konversation terminated!]
zv has joined #ocaml
jao has quit [Ping timeout: 268 seconds]