ChanServ changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml 4.02.1 announcement at http://ocaml.org/releases/4.02.html | Public channel logs at http://irclog.whitequark.org/ocaml
<Algebr> I'm interested in using ctypes and just a small confusion, how do you bind to functions not part of posix? say your custom library. It seems you have to compile it separatenly and then pass a -l argument to ocamlc?
<Algebr> oh to -cclib i guess
swgillespie has joined #ocaml
hilquias has joined #ocaml
<Drup> yes
<Algebr> can utop do something like -cclib?
<Drup> no, you can still do bindings in ctypes using libffi
<Drup> (it's the default way of doing things anyway)
<Algebr> I looked at doing it that way and it looks way more tedious. But in any case I just tried the simpliest attempt at getting a separate c libary. I'm getting this exception Fatal error: exception Dl.DL_error("dlsym(RTLD_DEFAULT, adder): symbol not found"). I defined a functionc called adder in simple.c. all compiled fine together.
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
keen___________ has joined #ocaml
keen__________ has quit [Ping timeout: 264 seconds]
shinnya has quit [Ping timeout: 256 seconds]
victoroak has joined #ocaml
<victoroak> topic
victoroak has quit [Client Quit]
psy_ has quit [Ping timeout: 264 seconds]
psy_ has joined #ocaml
<blech_> Let's say I'm working with a tree data structure composed of a recursive variant type. I'm going to have to transform it to another format and back. I am going to be using the same structure in my construction step (through composition) and in my decomposition step (pattern matching)
<blech_> though for each of these I'm going to have to duplicate the structure
<blech_> is there something I can do to reuse that definition?
AndChat|618624 has joined #ocaml
TSMI has quit [Ping timeout: 246 seconds]
<jcloud> what do you mean? why do you have to redefine a new variant type each time?
<jcloud> to define*
Algebr has quit [Ping timeout: 272 seconds]
<struktured> curious..why doesn't partial function application type check for this? let f ~x ~y z = if z then x else int_of_string y in f 3 "2" . I thought it would work because it's unambiguous here, despite not using the labels.
<blech_> jcloud, I don't mean that I'm defining a new variant every time
<blech_> jcloud, let's say I'm trying to pull some data out of a JSON object. If I've got a function that's extracting that content I'm going to do something like match json with Object [ ("name": String realname ) ] -> (*act on realname*). Later on if I'm trying to go from my intermediary format back to the JSON representation I'm going to do Object [ ("name", String realname) ] again as my final expression to return it
<blech_> for larger structures this duplication gets to be troublesome
<struktured> computationally? I don't undestand your problem, but maybe I don't know the scope.
<blech_> not computationally, I just don't like having the same structure defined twice
<jcloud> Why do you have to define it twice? I am not sure what is the problem.
<struktured> yeah.. you can wrap that in a function..but if thatsthe whole pattern what do large structures have to do w/it?
<tobiasBora> Does anyone knows how to remove the warning "Warning: ocp-indent input contains indentation by tabs, partial indent will be unreliable." in ocp-indent ?
<struktured> tobiasBora: do you inssit on keeping tabs?
<struktured> tobiasBora: *insist
rock_neurotiko has quit [Ping timeout: 272 seconds]
<blech_> jcloud, let's say we're dealing with JSON as the recursive variant type. If I've got a function json -> mytype I'm going to pull the content out from the json structure and wrap it in mytype. If I have a function mytype -> json I'm going to compose the appropriate JSON structure. If I then change the layout of that JSON object that I'm generating I have to update it in both places and my naive idealistic thought is I'd like to be
<blech_> able to define this mapping once and be able to apply it in either direction.
<tobiasBora> struktured: No I don't really want to keep tabs
<struktured> tobiasBora: http://vim.wikia.com/wiki/Converting_tabs_to_spaces then? if u sing vim
darkf has joined #ocaml
AndChat|618624 has quit [Ping timeout: 258 seconds]
leafac has joined #ocaml
<jcloud> blech_: this sounds almost like the expression problem... So you are saying that you don't like having to update the code that handles the structure whenever you change the structure?
TSMI has joined #ocaml
<jcloud> if you are going to change the layout, it seems to me as if you will have to change the code; unless there is some way for the code to automatically find out how to do the conversion both ways, or to compute the inverse of an ocaml function :P
<tobiasBora> struktured: Actually I'm using emacs, but I think that (setq indent-tabs-mode nil) should do the job. Thank you !
<blech_> jcloud, I've got no problem changing the structure and changing the code to match
<blech_> I'd just like to only have to change it in one place rather than two
BitPuffin|osx has quit [Ping timeout: 256 seconds]
<jcloud> okay, so to clarify, you would prefer to update only, say, the json -> something code, rather than both that and the something -> json code?
<jcloud> if it would really save you time, you might program functions that operated more generally on some sort of specification structure + either the json or the other type, I.e. when you changed the layout you would change the specification rather than the code itself
<struktured> blech_: ppx deriving json out of the question?
<struktured> blech_: I felel like you can't really do what you're saying without a declarative approach.
<struktured> *feel
<tobiasBora> Hum
<tobiasBora> Lwt seems to have removed the module Lwt_util, but what should I use to iter on lists now ?
<Drup> Lwt_list
<tobiasBora> Thank you (and I'm stupid the doc writes "use Lwt_list"...)
Denommus has joined #ocaml
ygrek has joined #ocaml
leafac has quit [Ping timeout: 255 seconds]
nullcat_ has joined #ocaml
oscar_toro has quit [Ping timeout: 276 seconds]
oscar_toro has joined #ocaml
Guest63092 has joined #ocaml
mcclurmc has joined #ocaml
mcclurmc_ has quit [Ping timeout: 265 seconds]
idegen has quit [Quit: Leaving.]
c74d has quit [Remote host closed the connection]
c74d has joined #ocaml
sdothum has quit [Quit: ZNC - 1.6.0 - http://znc.in]
Guest63092 has quit [Ping timeout: 258 seconds]
wraithm has quit [Quit: leaving]
chambart has quit [Ping timeout: 265 seconds]
<struktured> is there a builtin function like the following ? "let always x = fun _ -> x" (I know it's trivial but seems common enough to have anyhow)
Bhavya has joined #ocaml
<struktured> companion_cube: nice, you have it at least: https://github.com/c-cube/ocaml-containers/blob/master/src/core/CCFun.mli#L51
inf-gropeoid is now known as pyon
pyon is now known as inf-gropeoid
mcclurmc has quit [Remote host closed the connection]
AndChat|618624 has joined #ocaml
TSMI has quit [Ping timeout: 276 seconds]
<blech_> struktured, that's not a bad idea. Personally I try to avoid preprocessors when possible so I would like to leave that as a last resort but thanks, that probably would work
hilquias has quit [Ping timeout: 246 seconds]
<IbnFirnas> does anyone know if nested recursive modules are possible to define?
hilquias has joined #ocaml
tsumetai` has quit [Quit: Leaving]
clog has quit [Ping timeout: 246 seconds]
MercurialAlchemi has joined #ocaml
<IbnFirnas> along the lines of this: http://pastebin.com/raw.php?i=yVWwh8K3
tsumetai has joined #ocaml
ygrek has quit [Ping timeout: 244 seconds]
nullcat__ has joined #ocaml
nullcat_ has quit [Ping timeout: 272 seconds]
<flux> nice, I thought module rec A : sig type t = int end = A itself would be impossible, but apparently it's OK
<flux> ibnfirnas, but I'm confident there's a way to accomplish that, somehow 8-)
<nullcat__> this doc generator is much better, anyone has experience with it? https://raw.githubusercontent.com/jordwalke/CommonML/master/img/CommonMLDoc.png
<nullcat__> i just want the doc generation part in his thing though
nullcat__ has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
Bhavya has quit [Ping timeout: 256 seconds]
ggole has joined #ocaml
Bhavya has joined #ocaml
TSMI has joined #ocaml
AndChat|618624 has quit [Read error: Connection reset by peer]
slash^ has joined #ocaml
TSMI has quit [Ping timeout: 246 seconds]
<l1x> Log.Global.set_output [Log.Output.stdout;];;
<l1x> this fails
nullcat has joined #ocaml
<l1x> what is the right way to configure the log level with core?
<l1x> it is barely documented
inf-gropeoid has quit [Ping timeout: 256 seconds]
matason has joined #ocaml
wwilly has joined #ocaml
rgrinberg has quit [Ping timeout: 258 seconds]
c74d is now known as Guest53397
c74d3 has joined #ocaml
Guest53397 has quit [Ping timeout: 256 seconds]
matason has quit [Ping timeout: 258 seconds]
avsm has joined #ocaml
clog has joined #ocaml
MercurialAlchemi has quit [Remote host closed the connection]
MercurialAlchemi has joined #ocaml
avsm has quit [Quit: Leaving.]
kushal has joined #ocaml
mcclurmc has joined #ocaml
c74d3 is now known as c74d
mengu has joined #ocaml
mengu has joined #ocaml
mcclurmc has quit [Ping timeout: 264 seconds]
Simn has joined #ocaml
orbitz_ has quit [Quit: Reconnecting]
orbitz has joined #ocaml
psy_ has quit [Ping timeout: 265 seconds]
Cyanure has joined #ocaml
pii4 has joined #ocaml
matason has joined #ocaml
matason has quit []
bobry has joined #ocaml
rgrinberg has joined #ocaml
<flux> re mainlinglist: "- New configure option "-no-naked-pointers" to improve performance by avoiding page table tests during block darkening and the marking phase of the major GC. In this mode, all out-of-heap pointers must point at things that look like OCaml values: in particular they must have a valid header. The colour of said headers should be black. (Mark Shinwell, reviews by Damien Doligez and Xavier Leroy)"
<flux> aren't naked pointers used oftentimes by C bindings?
<flux> I suppose that's bad then?
rgrinberg has quit [Ping timeout: 272 seconds]
<ggole> Presumably that is why it is an option
<ggole> Seems like it could get you into trouble though
<ggole> You'd have to know whether any of your dependencies were using such C bindings
<flux> I wonder how much does it give performance benefits
<flux> maybe if you have particularly GC-heavy app?
<flux> I suppose C bindings could be fixed to use custom allocations and putting the pointer there?
<flux> in fact the GC should also have a debug mode for finding if an application uses such pointers..
<ggole> Changing the way libraries allocate is not necessarily a simple thing to do
<flux> it's been some time since I've done C bindings.. but isn't it a matter of just wrapping the pointer with another block?
<ggole> C libraries might also return pointers that do not point to the beginning of a C allocation, eg, to something inside an array
<ggole> Wrapping the pointer itself might work...
Gama11 has joined #ocaml
siddharthv is now known as siddharthv_away
leowzukw has joined #ocaml
Bhavya has quit [Ping timeout: 264 seconds]
<companion_cube> struktured: what do you mean? CCFun.const has existed for a long time ;)
Bhavya has joined #ocaml
Bhavya has quit [Read error: Connection reset by peer]
<companion_cube> maybe it still works with opaque blocks?
<companion_cube> flux, ggole: if opaque blocks can still contain naked pointers, it should be fine; just wrap C stuff in a ocaml record/variant
octachron has joined #ocaml
<ggole> In other words, rewrite the binding.
<companion_cube> well that might be already the case
rgrinberg has joined #ocaml
<ggole> So if there's no problem, there's no problem. But if there's a problem there's a problem. :)
<ggole> The question in my mind is how easy it is to determine whether you can safely use this feature.
<companion_cube> right
rgrinberg has quit [Ping timeout: 245 seconds]
ollehar has joined #ocaml
<flux> if it crashes.. ;)
<companion_cube> call Gc.compact() a lot
<companion_cube> :D
Cyanure has quit [Remote host closed the connection]
<flux> yep, that's the way ;)
<nullcat> someone wants to answer my question about js-of-ocaml? http://stackoverflow.com/questions/30434644/pretty-print-in-js-of-ocaml
<apache2> is it possible to do something like `match boat with Yellow (Submarine b | Raft b) ->`?
freling has joined #ocaml
<companion_cube> apache2: yes, if both subpatterns define the same set of variables, with compatible types
<apache2> companion_cube: how about (Yellow | Blue) in the example above?
<companion_cube> nullcat: no idea, depends on how "COmpiler.Pretty_print.to_buffer" is defined
<companion_cube> maybe there's an alternative function with "_human" or "_pretty" or "_nice" or something like this, that formats better
<apache2> Ie (Yellow | Blue) (Foo x | Bar x)
<companion_cube> apache2: no, this is not possible
<apache2> Ok. thank you
<nullcat> don't know how to use them...
<companion_cube> however: | Yellow (Foo x | Bar x) | Blue (Foo x | Bar x) -> ... is possible
Haudegen has quit [Ping timeout: 276 seconds]
<companion_cube> nullcat: try calling set_compact <printer> false
<companion_cube> "compact" is usually associated with not very readable, but efficient, printers
<nullcat> makes no difference, sadly...
<companion_cube> :/
<nullcat> to_buffer sets compact to false by default
<nullcat> and changing it to true makes the output even worse
<companion_cube> :D
<companion_cube> maybe it doesn't know how many columns it can use
ingsoc has joined #ocaml
<apache2> companion_cube: ok, thanks :)
hilquias has quit [Ping timeout: 258 seconds]
QuanticPotato has joined #ocaml
Haudegen has joined #ocaml
astocko has joined #ocaml
astocko has quit [Read error: Connection reset by peer]
kushal has quit [Ping timeout: 272 seconds]
rgrinberg has joined #ocaml
mengu has quit [Remote host closed the connection]
rgrinberg has quit [Ping timeout: 276 seconds]
lordkryss has joined #ocaml
milosn has quit [Quit: leaving]
xificurC has quit [Quit: WeeChat 1.2]
Kakadu has joined #ocaml
djellemah has joined #ocaml
mengu has joined #ocaml
ollehar has quit [Ping timeout: 272 seconds]
Haudegen has quit [Ping timeout: 272 seconds]
asQuirreL has joined #ocaml
mengu has quit [Remote host closed the connection]
sgnb` has joined #ocaml
QuanticPotato has quit [Ping timeout: 255 seconds]
sgnb has quit [Remote host closed the connection]
rgrinberg has joined #ocaml
leafac has joined #ocaml
rgrinberg has quit [Ping timeout: 264 seconds]
sdothum has joined #ocaml
Haudegen has joined #ocaml
rand000 has joined #ocaml
Hannibal_Smith has joined #ocaml
BitPuffin|osx has joined #ocaml
sdothum has quit [Quit: ZNC - 1.6.0 - http://znc.in]
sdothum has joined #ocaml
<companion_cube> PR#6468: toplevel now supports backtraces if invoked with OCAMLRUNPARAM=b <--- oh, nice change in 4.03
bobry has quit [Quit: Connection closed for inactivity]
_andre has joined #ocaml
mengu has joined #ocaml
QuanticPotato has joined #ocaml
Haudegen has quit [Ping timeout: 272 seconds]
<ggole> Yeah, looking forward to that.
rgrinberg has joined #ocaml
rgrinberg has quit [Ping timeout: 276 seconds]
<flux> nice
<flux> that's going to make it much nicer for newcomers in particular
<companion_cube> also, .()<- operators
<flux> but no .!%<{ }>%!-operators?-(
<flux> maybe with ocaml-implicits we could even get rid of the different subscription operators :P
<companion_cube> hmm makes me think that removing the special float array case was not included
<companion_cube> sad
Haudegen has joined #ocaml
<ggole> Man, exhaustiveness checking for GADTs is really thoroughly broken :/
sgnb` has quit [Remote host closed the connection]
<flux> can it be fixed?
<ggole> That's a question for the maintainers
sgnb has joined #ocaml
<ggole> I've already got a few bug reports in on the matter, so hopefully it'll be thought about
<flux> I understand GADTs and exhaustiveness checks could even have some theoretical challenges?-o
<ggole> That's possible. I'm not familiar enough with the problem to say.
<companion_cube> flux: +1, I read this too
<companion_cube> ggole: does it require impossible cases, or does it miss possible cases?
<ggole> It accepts a case that is impossible to pass to the function as typed
<companion_cube> so you need assert false, is that it?
<flux> I think he accidentally added a case that can never be matched
<flux> not that the compiler required one?
<ggole> This function is typed int expr -> int
<ggole> But the last case returns a bool!
<ggole> (It doesn't actually ever return a bool because it can't be reached, but still, definitely off.)
<ggole> The "real fix" is to use the let rec eval : type a . a expr -> a = ... form
<ggole> Which requires that the type variable be polymorphic as I intended.
<ggole> (And that makes the case reachable.)
<bernardofpc> ouch
<bernardofpc> so the first form induces the GADT type to be a single one, and not generalized, right ?
<ggole> Seems so, yeah
<ggole> Which is not so bad in itself, but the missing exhaustiveness is quite confusing
<flux> regarding inline records: will they work with GADTs as well?
<ggole> They will, I was asking Drup about this
<ggole> I incorrectly believed they didn't, but I was just confused about the syntax
freling has quit [Quit: Leaving.]
<octachron> flux: if you are willing to argue the case of .!%<{..}>%! with the maintainers, I will gladly write the corresponding patch :p
<flux> octachron, well funky operators would make OCaml look more appealing to newcomers?
<bernardofpc> not sure
<bernardofpc> already newcomers have the ; vs ;; clash
<bernardofpc> (which is simple but takes time to incorporate)
<ggole> bernardofpc: actually, it's a bit stranger than that... if you reduce the eval to just the Lt case, it still gets int expr -> int O_o
<ggole> I think this is because the return type is unified with the inner calls to eval.
<bernardofpc> ggole: weird
<ggole> Yeah, not the most intuitive thing.
<bernardofpc> with the first (type a) syntax ?
<ggole> Yeah. With the second it's fine.
<octachron> flux: the appeal to ascii-artists newcomers that don't want to feel constrained in their artistic freedom?
<bernardofpc> ggole: and it gets an "unexaustive pattern"
<companion_cube> flux: they have camlp4 if they want
<bernardofpc> is there not a simple syntax (sugar?) for defining a gadt function with a \forall and many arguments ?
<companion_cube> let rec f: type a b c. ..... = fun .... -> .....
<octachron> ggole: I think it is a problem of higher order rank polymorphism. Without (forall a.) annotation eval can only be first rank polymorphic so its type is determined at call time
<bernardofpc> something like """ let rec eval (level : int) \forall a (e : a level expr) : a = match e with ...
<ggole> octachron: sure, but that's not really the problem: I'm happy with the idea that I have to provide certain annotations for polymorphism.
<ggole> The issue is that the exhaustiveness check isn't really exhaustive.
Hannibal_Smith has quit [Quit: Leaving]
badkins has joined #ocaml
<octachron> Well, the match pattern is still exhaustive in your example, even if redundant.
Hannibal_Smith has joined #ocaml
<ggole> All right, the redundancy check
<companion_cube> I assume the type checker prefers to be over-conservative when it checks exhaustiveness
leafac has quit [Ping timeout: 245 seconds]
<struktured> companion_cube: I just discovered CCFun yesterday, when looking for const
<companion_cube> \o/
<companion_cube> it exists because I dislike putting even more stuff in pervasives
Gama11 has quit [Quit: No Ping reply in 180 seconds.]
Gama11 has joined #ocaml
rgrinberg has joined #ocaml
<struktured> companion_cube: it's a good name for the module
rgrinberg has quit [Ping timeout: 246 seconds]
<companion_cube> I like fun names
Hannibal_Smith has quit [Quit: Leaving]
idegen has joined #ocaml
<vbmithr_> do you use exceptions or stuff like this -> http://erratique.ch/software/rresult to handle your errors in programs ?
leafac has joined #ocaml
<vbmithr_> exceptions are the only way to do control flow things
<vbmithr_> I've got the feeling that it's old school to use exceptions for errors, everybody seems to have error type nowadayg
<ggole> Depends on the error, really
struktured has quit [Ping timeout: 265 seconds]
Cyanure has joined #ocaml
<vbmithr_> mmh, yes
<vbmithr_> I parse json from a web page
<companion_cube> exceptions very locally can be very useful
<vbmithr_> and sometimes the server returns trash
<companion_cube> if you expose errors in an API, I think an error type is better
<companion_cube> because it shows in the signature
<vbmithr_> so it raises an exception somewhere in my program
<vbmithr_> yeah.
<vbmithr_> I think I like having in mind all the possibilities that can happen
<vbmithr_> good argument companion_cube, you want to know what can happen…
<ggole> Passing errors around through N layers is often annoying if you can just catch them in the outermost.
<ggole> Of course, nothing will remind you to do that.
<companion_cube> sure, it's a tradeoff
<vbmithr_> yeah, true.
<companion_cube> also, I like val foo : a -> b or_error val foo_exn : a -> b
<companion_cube> this way you get to choose
<ggole> Yeah
<vbmithr_> yep, so both have advantages/disadvantages
<companion_cube> and even if you use foo_exn, the prefix reminds you that it can raise
<ggole> This is one of the conventions from Core that I really like
<companion_cube> yep
<companion_cube> also, Foo_intf for modules is pretty nice
<ggole> Instead of S?
<companion_cube> not the same thing
<companion_cube> when you have a larg-ish S in foo.ml and foo.mli
<companion_cube> put it in foo_intf.mli, and alias to it in both foo.ml and foo.mli
<ggole> Oh, that. Right.
asQuirreL has quit [Ping timeout: 256 seconds]
MercurialAlchemi has quit [Ping timeout: 256 seconds]
leafac has quit [Quit: Leaving.]
MercurialAlchemi has joined #ocaml
asQuirreL has joined #ocaml
thomasga has joined #ocaml
slash^1 has joined #ocaml
<companion_cube> I wonder how costly is each call to Random.State.self_init, in practice
slash^2 has joined #ocaml
slash^ has quit [Ping timeout: 252 seconds]
<adrien_znc> you wouldn't try to to do that call more than once anyway, right?
slash^1 has quit [Ping timeout: 252 seconds]
rgrinberg has joined #ocaml
rgrinberg has quit [Ping timeout: 256 seconds]
<companion_cube> hmmm actually it's ok... I think
<octachron> companion_cube: Reading 12 bytes of data from /dev/urandom ( as Random.State.self_init does ) doesn't sound extremely slow
<companion_cube> but /dev/urandom can be costly, I think
<adrien_znc> no
<adrien_znc> let's see
<adrien_znc> 4k reads:
<adrien_znc> 4194304 bytes (4.2 MB) copied, 0.391687 s, 10.7 MB/s
<adrien_znc> how much do you need?
<companion_cube> heh
<adrien_znc> nicoo: your turn ^
<nicoo> adrien_znc: Wat?\
<companion_cube> gah, Uuidm doesn't provide pretty-printers?
<adrien_znc> nicoo: companion_cube is saying that /dev/urandom is costly :P
<nicoo> Well, the costly part is actually doing the syscall, so a small read is (proportionnaly) costlier than a large one. But you should only need to init your RNG once at application startup, so why should C³ care ?
<companion_cube> adrien_znc: I thought so
<nicoo> companion_cube: SO TELL ME, WHY DO YOU CARE? ;_;
<adrien_znc> :)
<companion_cube> never mind
<adrien_znc> I could have typed all that long sentence but all I had to do was to poke nicoo \o/
<adrien_znc> :D
<companion_cube> 14998229/s <--- ok, uuidm is not that costly
rgrinberg has joined #ocaml
<companion_cube> (number of unique random IDs created per second)
<nicoo> companion_cube: If you want moar performance, be my guest and call getentropy() (on platforms where it is supported)
<ggole> Unroll those loops!
<companion_cube> oh right, that would make a good benchmark for flambda
<companion_cube> and it made me peek at UUID, which are cool
<MercurialAlchemi> uuids are cool, but queries with on tables with uuids as primary key you need to type manually, less so :)
<companion_cube> copy/paste ?
<companion_cube> :D
<MercurialAlchemi> companion_cube: yeah, ugh
<flux> best to handle primary keys as strings in your app
<flux> then you can switch to uuids when you have done enough ad-hoc queries during development ;-)
* MercurialAlchemi throws a ball of string at flux
<MercurialAlchemi> string-typist!
<flux> might just as well be a string, you're not going to perform arithmetics on them.
<flux> there's one reasonable solution in the comments: use both
<flux> though I guess it's a bit redundant
<MercurialAlchemi> from the comments "well, they were using MongoDB, so not really a database"
<MercurialAlchemi> I wouldn't want to use two keys
<MercurialAlchemi> too confusing
<companion_cube> anyway, I find uuid cools, not necessarily only for databases
<MercurialAlchemi> I'd be interested to have some numbers when it comes to performance
<flux> uuids will sound a relatively good idea when you have multiple databases you want to join at some point :)
<companion_cube> well you see, 1.5M uuid generated in 1s
<MercurialAlchemi> question is, if you want to use this in a distributed setup, how long before you get a collision?
<companion_cube> flux: well, small probability of collision
<companion_cube> much better than autoincrement
<flux> I understand it's negligible
<MercurialAlchemi> guy in the comments was saying "at work we use both: a sequential primary key (oracle sequence): because it is still faster than UUID when you have multiple joins AND an alternate uuid key that we expose to the outside world"
<flux> with 2^46 RFC UUIDs there's a probability of 4e-10 of a collision
<companion_cube> 2^46 is already a huge number of primay keys, isn't it?
<flux> yep. but I suppose you still want to prepare for pk conflicts just for sake of completeness. regenerating the key when the insert gives you a key constraint should fix it.
<flux> hopefully with some mechanism easy to deploy to all inserts
QuanticPotato has quit [Ping timeout: 264 seconds]
<flux> in fact.. maybe postgresql could learn to do this by itself in future ;-)
<flux> at least if the db is the one that creates the uuid, that might not be applicaple in all cases
<companion_cube> flux: according to the blogpost you can still enforce uniqueness constraint
<companion_cube> but then, yes, renaming would be tough
<companion_cube> (in case of a merge with collision)
<flux> sure, of course you enforce uniqueness constraint
<flux> well, not super tough, given ON UPDATE CASCADE?
A1977494 has joined #ocaml
QuanticPotato has joined #ocaml
<flux> ..but if you don't have indices to make that happen it could be very slow..
<companion_cube> of course, you need to index by primary key
<flux> but there are other tables that refer to the table with a foreign key, so you need an index on that fk as well
<flux> whereas normally you might not need it
<flux> in fact, while developing such a system, you should use a random integer from 1 to 10000. to shake out the conflict resolving bugs ;)
MercurialAlchemi has quit [Ping timeout: 272 seconds]
MercurialAlchemi has joined #ocaml
milosn has joined #ocaml
Khady has quit [Remote host closed the connection]
Khady has joined #ocaml
zpe has joined #ocaml
QuanticPotato has quit [Ping timeout: 240 seconds]
QuanticPotato has joined #ocaml
xificurC has joined #ocaml
willy_ has joined #ocaml
wwilly has quit [Ping timeout: 264 seconds]
zpe has quit [Remote host closed the connection]
rand000 has quit [Ping timeout: 265 seconds]
slash^ has joined #ocaml
lordkryss has quit [Quit: Connection closed for inactivity]
slash^2 has quit [Ping timeout: 252 seconds]
mengu has quit []
shinnya has joined #ocaml
freling has joined #ocaml
gabemc has joined #ocaml
rand000 has joined #ocaml
rand000 has quit [Client Quit]
octachron has quit [Quit: Leaving]
kushal has joined #ocaml
Haudegen has quit [Ping timeout: 240 seconds]
tane has joined #ocaml
kushal has quit [Ping timeout: 256 seconds]
rgrinberg has quit [Ping timeout: 256 seconds]
milosn has quit [Read error: Connection reset by peer]
milosn has joined #ocaml
rgrinberg has joined #ocaml
darkf has quit [Quit: Leaving]
QuanticPotato has quit [Ping timeout: 272 seconds]
QuanticPotato has joined #ocaml
Haudegen has joined #ocaml
Unhammer has quit [Quit: WeeChat 1.1.1]
Denommus has quit [Ping timeout: 264 seconds]
QuanticPotato has quit [Ping timeout: 250 seconds]
<Drup> nullcat: by pure curiosity, why are you interested in pretty-printing javascript ? :)
<companion_cube> to debug calls to eval(), probably
<companion_cube> :>
Hannibal_Smith has joined #ocaml
<apache2> is there an equivalent of 'type .. = ... and .. = ..' for let-bindings of fucntions?
<apache2> (or, mutually recursive functions)
<apache2> oh, 'let rec ... = ... and ... = ...' worked. I had an extra 'rec' in front of the second.
shinnya has quit [Ping timeout: 272 seconds]
rand000 has joined #ocaml
ygrek has joined #ocaml
freling has quit [Quit: Leaving.]
BitPuffin|osx has quit [Ping timeout: 246 seconds]
<adrien> I'm looking for someone who's using the cygwin port of ocaml
<adrien> not the windows one running from cygwin
<adrien> I'd just like to know if it actually works
<adrien> so ask your friends too
leowzukw has quit [Quit: leaving]
rgrinberg has quit [Ping timeout: 258 seconds]
<blech_> Question for the group: I've got a validation pipeline set up that I'd like to be extensible by users of my API. I've got a couple of thoughts so far and I'm not sure what would be the recommended approach. 1 - functorize the validation module to allow people to inject other validation systems in. 2 - allow an optional parameter for the validation function that is a function (M a -> M a) where M is a validation status monad of
<blech_> some sort. The user's rule would get chained onto the end of the current chain and finally be broken down to return the result of the validation.
hilquias has joined #ocaml
hilquias has quit [Changing host]
hilquias has joined #ocaml
<ggole> The quick'n'dirty way would be to have a list ref of user validation functions
<ggole> I assume you want to collect all the validation failures rather than just bailing at the first sign of trouble?
hilquias has left #ocaml ["ERC Version 5.3 (IRC client for Emacs)"]
contempt has quit [Remote host closed the connection]
Anarchos has joined #ocaml
asQuirreL has quit [Ping timeout: 265 seconds]
shinnya has joined #ocaml
<blech_> ggole, correct
<ggole> Seems easier to just collect a list and have the user's function not care about chaining or anything like that (if possible)
<ggole> Particularly since you're likely to want to do things like catch any exception raised by the validation functions
lobo has joined #ocaml
Denommus has joined #ocaml
inf-gropeoid has joined #ocaml
badkins has quit []
<blech_> in the continued spirit of noob questions
<blech_> is it worth it to define a submodule for utility functions?
<blech_> as in I don't want to take a dependency to core or batteries but I need some string utilities so I create a StringExt module
<Drup> just use stringext and stop rewriting them
<blech_> fair enough
<ggole> Dependencies aren't so bad these days
badkins has joined #ocaml
cmtptr has quit [Quit: leaving]
tumdum has joined #ocaml
rgrinberg has joined #ocaml
cmtptr has joined #ocaml
tumdum has quit [Client Quit]
tumdum has joined #ocaml
rgrinberg has quit [Ping timeout: 244 seconds]
<nullcat> Drup: because I need to demo in class... just want to display something nice
rgrinberg has joined #ocaml
matason has joined #ocaml
gabemc has quit [Ping timeout: 255 seconds]
thomasga has quit [Quit: Leaving.]
ggole has quit [Ping timeout: 272 seconds]
thomasga has joined #ocaml
A19774941 has joined #ocaml
sepp2k has joined #ocaml
A1977494 has quit [Ping timeout: 264 seconds]
asQuirreL has joined #ocaml
tmtwd has quit [Remote host closed the connection]
matason has quit []
slash^ has quit [Ping timeout: 252 seconds]
slash^ has joined #ocaml
tmtwd has joined #ocaml
jbrown has quit [Remote host closed the connection]
A1977494 has joined #ocaml
A19774941 has quit [Ping timeout: 244 seconds]
Algebr has joined #ocaml
nullcat has quit [Ping timeout: 246 seconds]
<Algebr> I'm trying out the ctypes library but where can't seem to find a way to make an enum. One of the tests included in ctypes source is test-enum and in that directory there is an enum function but I can't seem to find it defined...and it doesn't exist at the Ctypes.enum expected place..
nojb has joined #ocaml
TheLemonMan has joined #ocaml
badkins has quit [Read error: Connection reset by peer]
<Algebr> Oh, I guess such a thing exists but hasn't been merged yet? https://github.com/ocamllabs/ocaml-ctypes/pull/296
<Drup> and it's a bit more complicated to use
jbrown has joined #ocaml
<Algebr> so how does one do enums now via ctypes?
Denommus` has joined #ocaml
Denommus has quit [Ping timeout: 264 seconds]
<Drup> well, read the PR, it's explained
<Drup> otherwise, treat them as ints
Denommus` is now known as Denommus
badkins has joined #ocaml
<Algebr> I see that its explained, but enums aren't available right now in the latest version of ctypes available via opam...so I should just use ints at the moment?
Hannibal_Smith has quit [Quit: Leaving]
<companion_cube> I like the part where functions with an impure body still have a chance to be inferred as pure
hay207 has joined #ocaml
adarqui has joined #ocaml
MercurialAlchemi has quit [Remote host closed the connection]
MercurialAlchemi has joined #ocaml
struktured has joined #ocaml
rand000 has quit [Ping timeout: 246 seconds]
nojb has quit [Quit: nojb]
Hannibal_Smith has joined #ocaml
slash^ has quit [Read error: Connection reset by peer]
nojb has joined #ocaml
kakadu_ has joined #ocaml
nojb has quit [Quit: nojb]
swgillespie has joined #ocaml
nullcat_ has joined #ocaml
rand000 has joined #ocaml
<rgrinberg> Drup: are there any good js_of_ocaml canvas examples?
<companion_cube> there is a graphics-like binding
<companion_cube> :p
nojb has joined #ocaml
<rgrinberg> companion_cube: yeah that's graphics implemented on top of canvas right?
nojb_ has joined #ocaml
nojb has quit [Ping timeout: 252 seconds]
<companion_cube> I think so
<companion_cube> I used it twice
contempt has joined #ocaml
<companion_cube> (hmm, once)
badkins has quit []
nojb_ has quit [Ping timeout: 252 seconds]
<Drup> yes
<Drup> it works just as fine as you can expect it
tumdum has quit [Ping timeout: 246 seconds]
contempt has quit [Read error: Connection reset by peer]
contempt has joined #ocaml
<Algebr> anyone off the top of their head know how to declare a variadic argument in ctypes?
<rgrinberg> Drup: is it possible to do it without graphics_js though? just pure canvas
<rgrinberg> ideally i just want a blank page with a canvas
<rgrinberg> (showing this to a friend who doesn't much ocaml but knows canvas really well)
<tane> is there not some kind of FFI for JS, which can be used to easily wrap all the necessary functions/types?
<Drup> well, sure, graphics_js is implemented in term of usual canvas stuff ..
rock_neurotiko has joined #ocaml
rock_neurotiko has left #ocaml [#ocaml]
mort___ has joined #ocaml
<nullcat_> is UK on holiday now?..
<rgrinberg> nullcat_: US is
<companion_cube> why so?
<companion_cube> is it a religious thing?
<struktured> memorial day, veteran related
<nullcat_> U.S is having Memorial Day
<companion_cube> ok
<struktured> more ocaml for me, is how I see it
<nullcat_> well, no one answers my issues in no-crypto, Mindy in ocamllab went to vacation. avsm went to greece... that's why I am wondering if UK is having holiday..
BitPuffin|osx has joined #ocaml
<nullcat_> never mind..
<companion_cube> similarly, opam-repo PRs are not merged
<struktured> the horror
<companion_cube> nah, that's fine ^^
<rgrinberg> nullcat_: time to read sources...
<struktured> its a slow time of year, in general.
<rgrinberg> nullcat_: in europe you get a lot of vacations
<rgrinberg> not like in NA
<nullcat_> ...that's good
<rgrinberg> but here we get way more food to eat
A1977494 has left #ocaml [#ocaml]
<nullcat_> although u.s is having holiday, in my lab 3/6 PhDs come to work today...
<nullcat_> (* I am not PhD *)
<struktured> well even in US most people work to osme degree all the time
<rgrinberg> :'(
<struktured> workaholicking is quite I call it
<struktured> *quite/what
<struktured> is it List.fold_right, in stdlib, that is unsafe for large # of iterations?
<nullcat_> rgrinberg: I'd like to fix some problems in otter today... it's still about design. I'd like to fix this messy piece of code. https://github.com/marklrh/otter/blob/master/lib/api.ml#L147
<rgrinberg> nullcat_: yeah i've checked it out. i'll give some feedback later
<rgrinberg> it's definitely bad
* rgrinberg messing around with js_of_ocaml currently :/
<nullcat_> it's too bad I can barely look at it
<companion_cube> NA?
<vbmithr_> good evening dwellers of my screen
<rgrinberg> companion_cube: North America
<vbmithr_> how is it going ?
<companion_cube> oh I see
<rgrinberg> vbmithr_: you broke iocaml for everyone :(
<companion_cube> struktured: indeed, List.fold_right is not tailrec
<rgrinberg> or rather, did not choose to fix it
<companion_cube> CCList.fold_right should be, though
<vbmithr_> haha :)
<struktured> companion_cube: yep thought so, I am using it by accident in a few spots
<vbmithr_> I might fix it then
<rgrinberg> vbmithr_: it was my first instance of opam hell ^_^
<rgrinberg> needing both a newer and older version of tls :P
<vbmithr_> ah shit
<vbmithr_> But it's much better now
<vbmithr_> I looked at my code and I was very ashamed of the thing to be honestm
<vbmithr_> Conduit was a good way to go, for my TLS woes
<struktured> vbmithr_: you should blog about your conduit experiences
<struktured> vbmithr_: after you fix the tls dep issue...
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
<vbmithr_> lol, there isn't much to say
mort___ has quit [Quit: Leaving.]
<Drup> rgrinberg: the raw API calls are here: http://ocsigen.org/js_of_ocaml/2.5/api/Dom_html#2_Canvasobject
<Drup> you can also use vg to draw on a canvas, I think
<Drup> what do you want to do exactly ?
<rgrinberg> Drup: teach a friend some OCaml for a little js_of_ocaml thing we'll work on
<rgrinberg> he knows FP though
<Drup> and you don't want to make him use graphics_js ?
<rgrinberg> Drup: not particularly.. also i don't know any graphics either ^_^
<rgrinberg> btw i found what i wanted
<rgrinberg> although i don't think it should compiile anymore
<rgrinberg> the api changed, it doesn't take tuples everywhere
<Drup> I doubt it has
<Drup> rgrinberg: graphics is easy to use really
<Drup> you'll need a small overlay anyway, raw API calls sucks
Algebr has quit [Ping timeout: 250 seconds]
<rgrinberg> Drup: so it does work. I'm a little confused though, the docs say that all the calls are uncurriefied
<rgrinberg> e.g. lineTo : float -> float -> unit Js.meth
<rgrinberg> but cubes.ml calls it like c##lineTo (w, 2. *. h);
<Drup> that's the syntax of the jsoo camlp4 extension :/
fraggle-boate_ has joined #ocaml
fraggle-boate__ has joined #ocaml
chambart has joined #ocaml
Nahra has joined #ocaml
fraggle-boate has quit [Ping timeout: 272 seconds]
fraggle-boate_ has quit [Ping timeout: 250 seconds]
<rgrinberg> :P
<Drup> wat
nullcat__ has joined #ocaml
nullcat_ has quit [Read error: Connection reset by peer]
freling has joined #ocaml
thomasga has quit [Quit: Leaving.]
ygrek has quit [Ping timeout: 246 seconds]
mort___ has joined #ocaml
mort___ has quit [Client Quit]
<Drup> ah, well, yes, obviously.
<Drup> heh
<Drup> it will only builds on ocaml trunk, and our CI is certainly not running on that
<Drup> sorry, you will have to look at the .mli
<Drup> if you do make doc locally in js_of_ocaml, will everything enables, it will do the right thing
thomasga has joined #ocaml
mcclurmc has joined #ocaml
<rgrinberg> Drup: how come https://ocsigen.org/js_of_ocaml/api/Lwt_js_events doesn't have all events
<rgrinberg> like resize
<rgrinberg> nvm onresize is there ^_^
_andre has quit [Quit: leaving]
<Drup> if one is missing, just PR/bug-report it
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
MercurialAlchemi has quit [Ping timeout: 276 seconds]
Anarchos has joined #ocaml
<rgrinberg> Drup: i'm doing Lwt.ignore_result (Lwt_js_events.onresizes (fun _ev x -> print_endline "xxx"; x))
<rgrinberg> and it seems to work fine
<rgrinberg> on the first resize
<rgrinberg> but then it stops
ygrek has joined #ocaml
<Drup> (it's probably not the issue, but Lwt.async is more suited)
<rgrinberg> the signature isn't making sense to me, what's the 2nd param of type unit Lwt.t for?
<Drup> ahah, I got what you are doing
<Drup> yeah, don't do that :D
<Drup> returns Lwt.return_unit
<Drup> read the documentation of seq_loop
<rgrinberg> Drup: ok but what's it do?
<rgrinberg> ah ok
<rgrinberg> Drup: i still don't understand tbh
<rgrinberg> but hey it's working :P
swgillespie has joined #ocaml
<Drup> let handler = Lwt_js_events.onresizes (fun _ev x -> print_endline "xxx"; Lwt.return_unit)
<Drup> the first argument, x, is "handler"
<rgrinberg> *second argument?
<Drup> second argument, yes
<Drup> this way, you can cancel it from within the handling function.
<Drup> is it ok ?
<rgrinberg> yeah but why does it returning it cancel it
<Drup> it doesn't cancel it
<Drup> it's a seq loop, it waits for the handling function to returns before handling the next events
<Drup> or, "handler" never finish ...
hay207 has quit [Ping timeout: 240 seconds]
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
<rgrinberg> Drup: oh ok that makes sense
mcc has joined #ocaml
ollehar has joined #ocaml
<rgrinberg> Drup: quick question how do i turn int Js.optdef to an int?
<rgrinberg> sorry for that...
swgillespie has joined #ocaml
<Drup> Js.Optdef.to_option
<Drup> (or get, and you provide the default)
<rgrinberg> Drup: thanks :)
axiles has joined #ocaml
<l1x> hi
<l1x> is it possible to only import certain things from batteries and certain other things from core and not collide with types?
<Drup> everything is namespaced in both cases, what's the issue ?
<Drup> just don't open the big modules, Batteries and Core
<Drup> (it's weird to use both, though)
lobo has quit [Quit: leaving]
<l1x> the types collide
<Drup> ?
<l1x> List.count is only in core not in batteries
<l1x> open batteries makes List mean Batteries.List
<l1x> unless you explicitly alias it to the other
<Drup> yeah, then don't open, that's what I said
<tane> l1x, "don't open"
<l1x> tane: do not use open?
<Drup> (and that's not the types, that's the modules ;)
<companion_cube> what is List.count?
<tane> that's what he said, yes
<l1x> Drup: ok :)
<tane> anyway, good night :)
<Drup> companion_cube: 'a list -> ('a -> bool) -> int
<l1x> module Logger = BatLogger
<companion_cube> oh
tane has quit [Quit: Verlassend]
<l1x> this is the way to use something properly?
<companion_cube> sounds like a micro optimization
<companion_cube> :>
<l1x> amazing it works :)
<companion_cube> (I'd probably use sequence)
<Drup> companion_cube: I can see the usefulness, but again, it's not list anyways :p
<Drup> s/not/on/
<Drup> l1x: are you using core just because of List.count ?
asQuirreL has quit [Ping timeout: 256 seconds]
<l1x> Drup, no, because I need List :)
<rgrinberg> Drup: i love some of the js_of_ocaml type errors. Massive dumps :P
<rgrinberg> luckily my friend is a C++ programmer
<rgrinberg> he's used to this punishment
<Drup> rgrinberg: beh, just use tyxml already
<Drup> l1x: I'm not sure I understand your answer, List is already in the stdlib/batteries :|
<l1x> well these things are blurry to me yet :)
Cyanure has quit [Remote host closed the connection]
asQuirreL has joined #ocaml
<Drup> ok. You'll learn soon enough, I guess. :p
gabemc has joined #ocaml
<Drup> rgrinberg: take some time to look at the last patches on ocsigenserver cohttp :p
robink has quit [Ping timeout: 244 seconds]
MrScout_ has joined #ocaml
ingsoc has quit [Quit: Leaving.]
TheLemonMan has quit [Quit: "It's now safe to turn off your computer."]
robink_ has joined #ocaml
Algebr has joined #ocaml
Kakadu has quit [Ping timeout: 246 seconds]
<rgrinberg> Drup: the last 3 commits? I've checked them out. Look good
<rgrinberg> I wonder how many warninings we have left...
<Drup> none
<Drup> but that's in another branch
asQuirreL has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
<dora-molly> rgrinberg: I am testing the code in your issue, I don't even have completion on js objects in merlin
Anarchos has quit [Quit: O vont da kousk emaon !!]
<rgrinberg> dora-molly: hmm i do
asQuirreL has joined #ocaml
<dora-molly> weird
<rgrinberg> dora-molly: actually, never mind it's a little finnicky. Doesn't pop up for me anymore
<dora-molly> ok, I prefer
<rgrinberg> dora-molly: definitely seems broken
sepp2k has quit [Quit: Leaving.]
<l1x> wow everything works, after I moved to module X = Y.Z.Q
<l1x> so open just includes everything from that module?
<l1x> while module just imports the submodule? or what is the terminology for Re2.Std.Re2 for example
<Drup> it doesn't include really, but yes, everything is in the scope
<Drup> (because there is also include, which does something different)
<Drup> and "module" ... create a module ? :)
<tobiasBora> Hello !
mcclurmc has quit [Remote host closed the connection]
rand000 has quit [Quit: leaving]
<rgrinberg> tobiasBora: Hi!
<nullcat__> hi!
<dora-molly> ho
<tobiasBora> I am getting crazy with Makefile, is it possible to use ocamlbuild to define Makefile-like commands ?
<Drup> oasis does that for you
<tobiasBora> Drup: My project is too complex for oasis...
<tobiasBora> And I'm pretty sure that writing a "from scratch" script in ocaml to compile my program would be more efficient that using Makefile...
<rgrinberg> tobiasBora: no such thing. but perhaps your _oasis file will grow larger than your project
<tobiasBora> rgrinberg: I want to use it to build a website with ocsigen and _oasis isn't usable for that stuff...
<tobiasBora> Well I think I'm going to write my own Make-like ^^
<tobiasBora> Make-like program*
<rgrinberg> tobiasBora: why don't you use ocamlbuild?
Simn has quit [Quit: Leaving]
<Leonidas> can someone explain how to read the deflate RFC? I'm looking at my hexeditor and scratching my head how the deflate blocks are represented
<Leonidas> my program and me, we both agree that the data is invalid, yet zlib decompresses it %)
<tobiasBora> rgrinberg: Well ocamlbuild can build some basics parts of my website, but after I want to put together several parts of my website and I don't know if it's possible to do that with ocamlbuild...
<tobiasBora> Is it possible to run random code with ocamlbuild ?
freling has quit [Quit: Leaving.]
<rgrinberg> tobiasBora: it's possible to run ocaml code and shell commands with ocamlbuild
<dora-molly> rgrinberg: issue reporting fixed (ugly fix :D), completion still being tackled
<Drup> dora-molly: btw, how do you handle it ?
<tobiasBora> rgrinberg: I can't find how to do that in this documentation : https://nicolaspouillard.fr/ocamlbuild/ocamlbuild-user-guide.html They seems to say "use shell scripts/make to do the whole stuff".
<rgrinberg> dora-molly: you didn't push the commit yet, right?
<rgrinberg> dora-molly: confirming that go to definition is working better for me. Hasn't failed yet :)
ollehar has quit [Remote host closed the connection]
<tobiasBora> rgrinberg: You are talking about plugins right ?
<dora-molly> rgrinberg: do completion work for you when prefix is not empty ?
<dora-molly> (completion "" fails but completing "ge" on date give you the list of get… methods)
Hannibal_Smith has quit [Quit: Leaving]
Gama11 has quit [Remote host closed the connection]
<rgrinberg> dora-molly: hmm neither completion works for me
<rgrinberg> empty prefix or not
<rgrinberg> > You are talking about plugins right ?
<rgrinberg> what do you mean by this?
<rgrinberg> i'll just say again that i did manage the proper method comepletion to show up a couple of times. but it seems like i've ran out of luck
kakadu_ has quit [Remote host closed the connection]
nullcat__ has quit [Ping timeout: 256 seconds]
<tobiasBora> rgrinberg: something like that : https://ocaml.org/learn/tutorials/ocamlbuild/Making_plugins.html
asQuirreL has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
Algebr has quit [Remote host closed the connection]
thomasga has quit [Quit: Leaving.]
nullcat has joined #ocaml
Anarchos has joined #ocaml
nullcat has quit [Read error: Connection reset by peer]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
madroach has quit [Ping timeout: 264 seconds]
madroach has joined #ocaml
gabemc has quit [Ping timeout: 256 seconds]
<dora-molly> rgrinberg: pfff, got it, it's quite tricky >_<, it will take me one more hour to fix it, but I take a break
darryn has joined #ocaml
<darryn> Hello
<darryn> exit
<darryn> lol
darryn has quit [Quit: leaving]
rgrinberg has quit [Ping timeout: 256 seconds]
<tobiasBora> Anyone knows how I can use ocamlbuild with eliom files ?
<tobiasBora> I just tried something like ocamlbuild -use-ocamlfind -plugin-tags "package(eliom.ocamlbuild)" kernel.cmo
<tobiasBora> (and I have the myocamlbuild.ml proposed here : https://ocsigen.org/eliom/manual/workflow-compilation#h5o-3)
<tobiasBora> and the solver only look for .ml files instead of .eliom...