companion_cube changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml 4.11 release notes: https://caml.inria.fr/pub/distrib/ocaml-4.11/notes/Changes | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
ansiwen has quit [Quit: ZNC 1.7.1 - https://znc.in]
ansiwen has joined #ocaml
tryte has quit [Remote host closed the connection]
tryte has joined #ocaml
<companion_cube> It's normal, it's just a function
aquijoule_ has joined #ocaml
richbridger has quit [Ping timeout: 268 seconds]
waleee-cl has quit [Quit: Connection closed for inactivity]
narimiran has joined #ocaml
<d_bot> <mimoo> what's a good way to write tests in ocaml? I see alcotest but I'm not if it's well integrated with dune
<hackinghorn> hi
<hackinghorn> I want to cut the last 2 character of a string, I got this: String.sub s ~pos:0 ~len:(String.length s - 2)
<hackinghorn> can I get a simpler one?
boxscape has quit [Ping timeout: 260 seconds]
wonko7 has joined #ocaml
vicfred has quit [Ping timeout: 260 seconds]
wonko7 has quit [Ping timeout: 268 seconds]
Serpent7776 has joined #ocaml
mro_name has joined #ocaml
mro_name has quit [Quit: Leaving...]
TheLemonMan has joined #ocaml
boxscape has joined #ocaml
<d_bot> <mimoo> does that work? I would have imagined you would have to do String.sub s (String.length s - 3) 2
<d_bot> <mimoo> ah maybe you're using core?
Haudegen has joined #ocaml
<schlaftier> Looks like StringLabels
<schlaftier> There's also Str.first_chars and Str.last_chars that might simplify it a little bit
Serpent7776 has quit [Read error: Connection reset by peer]
Serpent7776 has joined #ocaml
jbrown has quit [Ping timeout: 260 seconds]
<hackinghorn> schlaftier, wow, thats great, I will do that
hackinghorn has quit [Quit: Leaving]
jbrown has joined #ocaml
olle has joined #ocaml
dash has quit [Ping timeout: 245 seconds]
labor[m] has quit [Ping timeout: 245 seconds]
dash has joined #ocaml
labor[m] has joined #ocaml
xandkar has quit [Remote host closed the connection]
st8less has quit [Quit: WeeChat 2.9]
bartholin has joined #ocaml
zebrag has joined #ocaml
<d_bot> <darrenldl> i use alcotest + qcheck, a fair bit of libs use inline tests in comments i think
<d_bot> <darrenldl>
<d_bot> <darrenldl> i don't find much trouble, but depends on what you mean by "well integrated"
boxscape has quit [Quit: Connection closed]
boxscape has joined #ocaml
peterbb has joined #ocaml
peterbb has quit [Quit: peterbb]
zebrag has quit [Quit: Konversation terminated!]
Haudegen has quit [Quit: Bin weg.]
zebrag has joined #ocaml
Haudegen has joined #ocaml
robogeoff has joined #ocaml
robogeoff has quit [Client Quit]
neiluj has quit [Ping timeout: 252 seconds]
seliopou has quit [Ping timeout: 252 seconds]
bartholin has quit [Quit: Leaving]
mxns_ has joined #ocaml
mxns has quit [Ping timeout: 250 seconds]
seliopou has joined #ocaml
neiluj has joined #ocaml
neiluj has quit [Client Quit]
Haudegen has quit [Quit: Bin weg.]
olle has quit [Ping timeout: 240 seconds]
drakonis has quit [Quit: WeeChat 3.1]
<d_bot> <Cyclomatic Complexity> I heard that:
<d_bot> <Cyclomatic Complexity> - One can submit projects to Coq, where Coq automatically takes care of their migration on breaking changes.
<d_bot> <Cyclomatic Complexity> - There is a big opam CI that tries to build literally all opam projects. It can be tried to see if anything breaks with a new OCaml version.
<d_bot> <Cyclomatic Complexity> Is any of those things true? If so, is there a link where I could check this out?
drakonis has joined #ocaml
bjorkintosh has joined #ocaml
<d_bot> <octachron> For the opam CI: http://check.ocamllabs.io/
boxscape has left #ocaml [#ocaml]
TheLemonMan has quit [Quit: "It's now safe to turn off your computer."]
<d_bot> <mimoo> Interesting! There's no reason for these functions to live in Str right :D? They act on strings
<d_bot> <mimoo> oh Str is not in the stdlib
neiluj has joined #ocaml
neiluj has joined #ocaml
<companion_cube> also str is bad
TheLemonMan has joined #ocaml
<d_bot> <mimoo> why?
<d_bot> <mimoo> I just made use of it in my lib
<d_bot> <mimoo> should I avoid it? It had a function to split a string that was very handy 😄
<companion_cube> it's full of global state :)
<companion_cube> just fyi
<d_bot> <mimoo> any alternative to split a string?
_ks has joined #ocaml
<companion_cube> String.split_on_char
<companion_cube> or directly `re`
<companion_cube> I mean str would be great if the API was a bit more modern
<d_bot> <mimoo> split on char doesn't take an index, it takes a char
<d_bot> <mimoo> maybe I could convert it to bytes and then use sub
<companion_cube> ah splitting on an index…
<companion_cube> tbh a helper for that is 2 lines :)
<companion_cube> maybe `astring` as well, I don't remember what's in there but it should be good
Tuplanolla has joined #ocaml
<d_bot> <mimoo> trying to use QCheck to generate a valid hexstring (even length, 0-9a-f)
<d_bot> <mimoo> looks like there's `QCheck.Gen.char_range 'a' 'f'`
<companion_cube> yep
vicfred has joined #ocaml
vicfred has quit [Quit: Leaving]
kakadu has quit [Remote host closed the connection]
<d_bot> <mimoo> ok that worked:
<d_bot> <mimoo>
<d_bot> <mimoo> ```
<d_bot> <mimoo> let arbitrary_hexstring =
<d_bot> <mimoo> let open QCheck.Gen in
<d_bot> <mimoo> let c = char_range 'a' 'f' in
<d_bot> <mimoo> let d = char_range '0' '9' in
<d_bot> <mimoo> let elem_gen = oneof [ c; d ] in
<d_bot> <mimoo> let size_gen = nat in
<d_bot> <mimoo> list_size size_gen elem_gen
<d_bot> <mimoo> ```
vicfred has joined #ocaml
<zozozo> anyone know if there is an implementation of strings tries in the opam-repo currently ? I searched and I couldn't find one
waleee-cl has joined #ocaml
<schlaftier> zozozo: there’s lazy-trie (based on lists), would that work for your usecase?
<zozozo> schlaftier: not really, in this case, I'd really want something optimised for strings (else the CCTrie in containers would have worked)
<zozozo> and the lazy-trie, being polymorphic and base on lists of characters, can't really perform as well as I'd want it to
<schlaftier> I see. Sorry I don’t know of any other implementation
<companion_cube> there's some C libraries by antirez :p
<zozozo> companion_cube: interesting, but I think I'll prefer a pure ocaml implementation for the moment
<zozozo> even if it means implementing one myself, ^^
<d_bot> <Anurag> Maybe https://github.com/dinosaure/art/ will be suitable?
<companion_cube> ahh!
<companion_cube> I looked for `trie` on opam but no luck
<d_bot> <Anurag> @dinosaure should add the tags field in the opam file so its easier to fine `art` via opam search 😉
<companion_cube> yep
<companion_cube> sadly it's mutable, zozozo :p
<zozozo> oh, why art thou mutable !
<companion_cube> faster? :D
<zozozo> meh, flambda won't even try to optimize mutable things ! :p
<companion_cube> booooo flambda, boooo
<companion_cube> (really? :/)
<zozozo> how dare you !
<zozozo> well, it's really tricky to get thigns right when mutation is involved
<zozozo> in the future flambda might try some things, but currently mutable structures are not optimized (i.e. never unboxed, values cannot be propagated thourhg a struct with at least one mutabel field, etc..)
<companion_cube> ah, mutable types, ok
<companion_cube> but surely local references are put on the stack if they don't escape?
<zozozo> yes, but that occurs during a simplification pass before flambda
<zozozo> flambda understand the notion of local mutable variables that this optimization generates
<zozozo> but flambde will not on its own introduce such local variables, even though you could want to do taht on e.g. a record with two mutable field, which is local (and can act as two refs)
<companion_cube> ah cool, so it even works outside of flambda indeed
<zozozo> most notably, if the reference becomes local only after you's inlined a function (think let r = ref 0 in Array.iter (fun i -> r += i) a ), then I think that the ref will not be transformed
<zozozo> (but let me check)
<companion_cube> :/
<zozozo> oh well, I'm actually wrong, seems like flambda1 can od the transformation on its own
<companion_cube> nice
<companion_cube> that's one quite important thing if you write imperative code…
<zozozo> yeah, but the thing is, iirc, the code that does that in flambda1 is really specifically made for references
<companion_cube> better than nothing!
<companion_cube> I mean it'd be great to have `let mut` instead I think
<companion_cube> replace heuristics with cold hard errors
<zozozo> and seems I was again wrong, and I should apologize to Pieree chen I see him, because it looks like it also works if you define your own mutable record
<zozozo> *Pierre
<zozozo> I should probably stop talking about flambda1 since I didn't work on it and it does pretty awesome things, :p
<companion_cube> :)
<zozozo> though that does mean that we'll need to also do all that in flambda2...
<companion_cube> I think that the one killer feature flambda2 could have, compared to flambda1, would be to be able to compile all packages :p
<companion_cube> and thus, maybe, become the default
<zozozo> yeah, there have been a lot of efforts that went into making flambda2 reasonable in terms of resource consumption during compilation
<d_bot> <EduardoRFS> if flambda2 could be as fast as flambda1 in opaque mode I would be so happy
<companion_cube> \o/
<d_bot> <EduardoRFS> > if flambda2 could be as fast as closure in opaque mode + Oclassic I would be so happy
<d_bot> <EduardoRFS> fixed
tane has joined #ocaml
vicfred has quit [Quit: Leaving]
pizzafrank13 has joined #ocaml
<pizzafrank13> Are There Any Al1ens Or T1me Travelers In Here Today Which Can Help Me?? PM me Please.
Haudegen has joined #ocaml
pizzafrank13 has quit [K-Lined]
<zozozo> companion_cube: so I think I'll go on and write a persistant implementation of tries based on the same paper as the art package, ^^
TheLemonMan has quit [Quit: "It's now safe to turn off your computer."]
narimiran has quit [Ping timeout: 240 seconds]
tane has quit [Quit: Leaving]
Serpent7776 has quit [Quit: leaving]
zebrag has quit [Quit: Konversation terminated!]
Tuplanolla has quit [Quit: Leaving.]
Haudegen has quit [Quit: No Ping reply in 180 seconds.]
Haudegen has joined #ocaml