ChanServ changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | http://www.ocaml.org | OCaml 4.01.0 announce at http://bit.ly/1851A3R | Logs at http://irclog.whitequark.org/ocaml
Algebr has quit [Ping timeout: 250 seconds]
johnnydiabetic has joined #ocaml
johnnydiabetic has quit [Ping timeout: 240 seconds]
<dmbaturin> Is there a way to see if compiler recognized a function as tail recursive?
<whitequark> apart from disassembly, no
<whitequark> generally, if the call is in tail position and has less than um
<whitequark> sixteen arguments or so
<whitequark> it's guaranteed to be a tail call
<def`> hmm, annots store the fact that a specific point is in tail-position
<def`> (tail recursion is not the right "unit" in ocaml, tail-call and tail-positions are)
philtor_ has joined #ocaml
zpe has joined #ocaml
<Drup> def`: could it be allowed to lint that using merlin ?
<def`> Drup: not without either approximation or big changes in the workflow of merlin
<Drup> ok
<def`> tail-call are computed in the intermediate language, not in the frontend
<def`> but since it's mostly syntactic, it's quite straightforward to implement an approximation working in >90% of the cases
<Drup> well, you can add that to the TODO-List--of-things-that-would-be-nice-but-that-you-will-never-actually-implement :D
<def`> Drup: this one could be made in ~2h… as of proof of concept, but then there will be a lot of associated maintenance :)
<def`> maybe, later…
<whitequark> def`: fix sublime plugin already
<whitequark> ;p
<def`> oops :)
<Drup> 2h hour to make a demo, 8h to make it work :p
zpe has quit [Ping timeout: 264 seconds]
<def`> Drup: then duplicate, implement 90% similar code but still different for 4.01, then 4.00… it costs in the end :)
<dmbaturin> Now I'm confused. Where do I find the details about tail call elimination in ocaml?
<whitequark> in ocamlc sources ;D
<Drup> dmbaturin: I'm afraid it's a bit implementation-defined
<def`> dmbaturin: it's just syntactic, so it's quite easy to lookup
<def`> the only part implementation-defined concerns the arity of the function called
<def`> if you compile your file with ocamlc -c -annot
<def`> it will produce a .annot file, in which you can lookup the word "tail" which will contain, for each position in the source, whether it is tail or not
<dmbaturin> So "tail" for a position means the frontend thinks it's a tail call?
lordkryss has quit [Quit: Connection closed for inactivity]
philtor_ has quit [Ping timeout: 245 seconds]
eikke__ has quit [Ping timeout: 245 seconds]
travisbrady has quit [Quit: travisbrady]
travisbrady has joined #ocaml
ygrek has joined #ocaml
BitPuffin has quit [Ping timeout: 255 seconds]
huza has joined #ocaml
zpe has joined #ocaml
travisbrady has quit [Quit: travisbrady]
zpe has quit [Ping timeout: 245 seconds]
<dmbaturin> def`: Tried on a dummy example, fact n = if n == 0 then 1 else (fact (n-1))*n doesn't have any tails in the annot file, canonical tail recursive version does. My stack is probably safe. :)
mcclurmc has quit [Remote host closed the connection]
lusory has quit [Ping timeout: 240 seconds]
mcclurmc has joined #ocaml
lusory has joined #ocaml
Algebr has joined #ocaml
q66_ has quit [Quit: Leaving]
travisbrady has joined #ocaml
mcclurmc has quit [Ping timeout: 250 seconds]
tobiasBora has quit [Quit: Konversation terminated!]
englishm has joined #ocaml
travisbrady has quit [Quit: travisbrady]
rgrinberg has quit [Quit: Leaving.]
samrat has joined #ocaml
rgrinberg has joined #ocaml
root2 has joined #ocaml
ygrek has quit [Ping timeout: 256 seconds]
huza has quit [Ping timeout: 250 seconds]
samrat has quit [Quit: Computer has gone to sleep.]
Algebr has quit [Read error: No route to host]
zpe has joined #ocaml
root2 is now known as huza
zpe has quit [Ping timeout: 255 seconds]
ygrek has joined #ocaml
samrat has joined #ocaml
oriba has quit [Quit: oriba]
hausdorff has joined #ocaml
huza has quit [Read error: Connection reset by peer]
huza has joined #ocaml
huza has quit [Client Quit]
huza has joined #ocaml
zpe has joined #ocaml
samrat has quit [Quit: Computer has gone to sleep.]
zpe has quit [Ping timeout: 255 seconds]
samrat has joined #ocaml
koderok has joined #ocaml
jao has quit [Ping timeout: 250 seconds]
hausdorff has quit [Remote host closed the connection]
hausdorff has joined #ocaml
hausdorff has quit [Read error: Connection reset by peer]
hausdorff has joined #ocaml
englishm has quit [Remote host closed the connection]
studybot has quit [Remote host closed the connection]
englishm has joined #ocaml
studybot has joined #ocaml
hausdorff has quit [Ping timeout: 264 seconds]
studybot has quit [Ping timeout: 264 seconds]
rgrinberg has quit [Quit: Leaving.]
zpe has joined #ocaml
rgrinberg has joined #ocaml
zpe has quit [Ping timeout: 240 seconds]
badon has joined #ocaml
samrat has quit [Quit: Computer has gone to sleep.]
siddharthv_away is now known as siddharthv
root_empire has joined #ocaml
root_empire has quit [Read error: Connection reset by peer]
axiles has joined #ocaml
yacks has joined #ocaml
huza has quit [Ping timeout: 250 seconds]
zpe has joined #ocaml
samrat has joined #ocaml
arj has joined #ocaml
zpe has quit [Ping timeout: 240 seconds]
Hannibal_Smith has joined #ocaml
Simn has joined #ocaml
studybot has joined #ocaml
Nahra has quit [Remote host closed the connection]
studybot has quit [Ping timeout: 264 seconds]
testcocoon has quit [Ping timeout: 260 seconds]
nickmeharry has quit [Ping timeout: 272 seconds]
nickmeharry has joined #ocaml
andy_____ has quit [Ping timeout: 256 seconds]
j0sh has quit [Ping timeout: 256 seconds]
j0sh has joined #ocaml
andy___ has joined #ocaml
andy___ is now known as Guest54942
ygrek has quit [Ping timeout: 255 seconds]
zpe has joined #ocaml
testcocoon has joined #ocaml
zpe has quit [Ping timeout: 255 seconds]
WraithM has joined #ocaml
tac has quit [Quit: Leaving]
shinnya has quit [Ping timeout: 264 seconds]
hhugo has joined #ocaml
zpe has joined #ocaml
sgnb has joined #ocaml
zpe has quit [Ping timeout: 260 seconds]
pyon has quit [Quit: Fiat justitia ruat caelum.]
yacks has quit [Quit: Leaving]
lordkryss has joined #ocaml
AltGr has joined #ocaml
rgrinberg has quit [Quit: Leaving.]
ygrek has joined #ocaml
tac has joined #ocaml
sepp2k has joined #ocaml
rgrinberg has joined #ocaml
tac has quit [Ping timeout: 244 seconds]
adrien_oww has joined #ocaml
eikke__ has joined #ocaml
tane has joined #ocaml
_0xAX has joined #ocaml
zpe has joined #ocaml
gasche has joined #ocaml
WraithM has quit [Quit: leaving]
koderok has quit [Quit: koderok]
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
zpe has quit [Read error: Connection reset by peer]
zpe has joined #ocaml
samrat has quit [Quit: Computer has gone to sleep.]
BitPuffin has joined #ocaml
cdidd has quit [Ping timeout: 250 seconds]
<whitequark> using ppx_deriving in the wild
samrat has joined #ocaml
<companion_cube> whitequark: looks like you want a @printer_const "<Subst.t>" or some similar shortcut
<whitequark> it seems so
<whitequark> [@abstract], I guess
shinnya has joined #ocaml
sagotch has joined #ocaml
<companion_cube> it's less obvious that @abstract is about printing
<companion_cube> anyway ppx_deriving looks great overall
<whitequark> companion_cube: it could be useful not just for printing
<whitequark> for Eq as well?
<whitequark> hm, no, not [@abstract]. [@opaque]
<companion_cube> well, I don't think you should assume that printing and Eq should have the same set of opaque types
<companion_cube> something could be irrelevant for printing, but relevant for equality
<whitequark> you could definitely have separate sets if you want
<whitequark> [@show.opaque] [@eq.opaque]
<companion_cube> better, yes
<companion_cube> although anyway you'd have to give an argument to [@show.opaque "<yolo>"]
skchrko has joined #ocaml
adrien_oww has quit [Quit: leaving]
Kakadu has joined #ocaml
adrien_oww has joined #ocaml
adrien_oww has quit [Client Quit]
adrien_oww has joined #ocaml
siddharthv is now known as siddharthv_away
<whitequark> huh? it'd just print "<opaque>" or skip the comparison
thomasga has joined #ocaml
<companion_cube> then it's not exactly what you needed in the example you pasted above
<whitequark> why not?
<whitequark> I don't really care what is printed there, I just put something
yacks has joined #ocaml
<whitequark> that happened to be the type name
rgrinberg has quit [Quit: Leaving.]
<companion_cube> well you choosed different names for different opaque fields
<whitequark> well, it could print the type, or something
<whitequark> I think <opaque> is fine after all
dsheets has quit [Ping timeout: 240 seconds]
koderok has joined #ocaml
dsheets has joined #ocaml
divyanshu has joined #ocaml
cdidd has joined #ocaml
fold has quit [Ping timeout: 250 seconds]
ggole has joined #ocaml
siddharthv_away is now known as siddharthv
hausdorff has joined #ocaml
hausdorff has quit [Remote host closed the connection]
hausdorff has joined #ocaml
locallycompact has joined #ocaml
rom1504 has quit [Quit: Reconnecting]
rom1504 has joined #ocaml
<Drup> whitequark: nice
pgomes has joined #ocaml
maattdd has joined #ocaml
siddharthv is now known as siddharthv_away
studybot has joined #ocaml
siddharthv_away is now known as siddharthv
sagotch has quit [Ping timeout: 240 seconds]
rand000 has joined #ocaml
eikke__ has quit [Ping timeout: 240 seconds]
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
kvelicka has joined #ocaml
George__ has joined #ocaml
Reventlov has quit [Quit: leaving]
Reventlov has joined #ocaml
koderok has quit [Quit: koderok]
Reventlov is now known as Guest99776
sagotch has joined #ocaml
Guest99776 is now known as Reventlov
Reventlov has quit [Changing host]
Reventlov has joined #ocaml
zpe has quit [Ping timeout: 245 seconds]
maattdd has quit [Ping timeout: 250 seconds]
agarwal1975 has quit [Quit: agarwal1975]
tane has quit [Quit: Verlassend]
locallycompact has quit [Remote host closed the connection]
locallycompact has joined #ocaml
BitPuffin has quit [Ping timeout: 264 seconds]
maattdd has joined #ocaml
pgomes has quit [Quit: http://www.kiwiirc.com/ - A hand crafted IRC client]
<whitequark> I have a problem
rand000 has quit [Ping timeout: 245 seconds]
<whitequark> it can basically described by "asprintf has hidden state"
<whitequark> I don't understand how, but it does
pgomes has joined #ocaml
rand000 has joined #ocaml
<def`> whitequark: are you doing partial application and reusing the function ?
SethTisue has joined #ocaml
<whitequark> curiously, no
<whitequark> I used to, and I had even more hidden state
agarwal1975 has joined #ocaml
<whitequark> def`: please look at this failure: https://travis-ci.org/whitequark/ppx_deriving#L304
<def`> I am afk, I can take a look in one hour
<whitequark> it's not even the same function! it's completely syntactically different asprintf invocations
<def`> But I would say that string printing functions from Format shares the same str_formatter str_buf
<whitequark> if I reorder lines 27 and 28 in that file, then the one on line 28 still has the linebreak
<def`> we use this to avoid global state in merlin
badon has quit [Ping timeout: 244 seconds]
<whitequark> def`: but this is the exact code from Format.asprintf
englishm has quit [Ping timeout: 256 seconds]
pminten has joined #ocaml
badon has joined #ocaml
Reventlov has quit [Quit: leaving]
Reventlov has joined #ocaml
BitPuffin has joined #ocaml
SethTisue has quit [Quit: SethTisue]
Reventlov is now known as Guest84030
Guest84030 has quit [Client Quit]
reventlo1 has joined #ocaml
reventlo1 is now known as Reventlov
<whitequark> def`: also reusing your code produces no difference
darkf has quit [Quit: Leaving]
_`_ has quit [Remote host closed the connection]
_`_ has joined #ocaml
<whitequark> def`: oh, nevermind, there is no hidden state
<whitequark> just some weird kind of behavior
maattdd has quit [Ping timeout: 250 seconds]
siddharthv is now known as siddharthv_away
koderok has joined #ocaml
ygrek has quit [Ping timeout: 245 seconds]
<dmbaturin> "Warning 25: bad style, all clauses in this pattern-matching are guarded." Why is this bad?
eikke__ has joined #ocaml
<companion_cube> because the compiler has no way to check whether the pattern is exhaustive
<companion_cube> and exhaustive patterns are good
<dmbaturin> Ah, well, makes sense.
Reventlov has quit [Quit: leaving]
Reventlov has joined #ocaml
koderok_ has joined #ocaml
divyansh_ has joined #ocaml
_2can_ has joined #ocaml
bernardo1pc has joined #ocaml
Valda has joined #ocaml
andy___ has joined #ocaml
samrat_ has joined #ocaml
eikke___ has joined #ocaml
nickmeha1ry has joined #ocaml
andy___ is now known as Guest38299
maufred_ has joined #ocaml
jpdeplaix` has joined #ocaml
_andre has joined #ocaml
Youri has joined #ocaml
<companion_cube> nice
eikke__ has quit [*.net *.split]
koderok has quit [*.net *.split]
divyanshu has quit [*.net *.split]
samrat has quit [*.net *.split]
Guest54942 has quit [*.net *.split]
nickmeharry has quit [*.net *.split]
jbrown has quit [*.net *.split]
bernardofpc has quit [*.net *.split]
seliopou has quit [*.net *.split]
_2can has quit [*.net *.split]
jpdeplaix has quit [*.net *.split]
Valdo has quit [*.net *.split]
maufred has quit [*.net *.split]
Youri_ has quit [*.net *.split]
mfp has quit [*.net *.split]
macron has quit [*.net *.split]
Valda is now known as Valdo
divyansh_ is now known as divyanshu
samrat_ is now known as samrat
koderok_ is now known as koderok
Reventlov has quit [Quit: leaving]
Reventlov has joined #ocaml
macron has joined #ocaml
jbrown has joined #ocaml
tane has joined #ocaml
pminten has quit [Quit: Leaving]
mfp has joined #ocaml
<whitequark> fffuuuuu, so much global data in ocamlc
<whitequark> why?!
<companion_cube> :D
<tane> what do you mean by that?
<whitequark> tane: the ocaml compiler uses a lot of global variables
<whitequark> often in the most inexplicable places
<tane> ah yeah
_2can_ is now known as _2can
<tane> i read the concurrent ocaml thingy's webpage some days ago
<tane> their main problem is in the same area i remember
<tane> on the emitted- and standard library code
<whitequark> no, that's a completely different thing
<tane> why?
<whitequark> the compiler itself isn't and doesn't need to be concurrent
<companion_cube> ans shouldn't be
<companion_cube> and*
<companion_cube> the compiler's style isn't that nice to me: lots of open, few comments :(
<whitequark> it's horrendous
<whitequark> though not for those reasons, for me
<whitequark> for me, it's because the few comments are in french, there is too much global mutable data, and most of the interesting invariants are completely undocumented
<whitequark> companion_cube: also try: ocaml $ git grep Weak
englishm has joined #ocaml
<def`> re
<whitequark> def`: already figured it out
<def`> whitequark: did you solve your problem?
<def`> ok
<whitequark> I didn't open a box and the default box acts weird
<def`> :P
<companion_cube> whitequark: I don't see the problem with Weak
<companion_cube> agreed on the invariants: smart constructors and comments in english would help
<companion_cube> and no fracking open
maattdd has joined #ocaml
<whitequark> open is fine, all the fields and constructors are prefixed anywa
<dmbaturin> Do the maintainers accept style-related patches? :)
badon has quit [Ping timeout: 255 seconds]
pgomes has left #ocaml [#ocaml]
samrat has quit [Quit: Computer has gone to sleep.]
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
<companion_cube> whitequark: I find this style very ugly
<companion_cube> I'd take M.Var rather than opem M;; M_var any day
<ggole> Module qualification of field names can be a bit clunky though
<companion_cube> not worse than prefixed field names
<companion_cube> using modules explicitely allows you to choose the prefix (by renaming the module)
<companion_cube> module T = Term ;; ......
<companion_cube> also I think records should have accessors whenever possible
<whitequark> companion_cube: I think ocamlc code predates first-class modules though
<whitequark> as for accessors, how are you going to match using accessors?
<companion_cube> ah, right
<companion_cube> matching is a specific case, but qualified names still work
<companion_cube> the point of using qualified names is that you need less context to understand where things come from
<whitequark> I don't agree that this is a problem in practice with compiler-libs
<companion_cube> really? even with the 8 open statements at the beginning of the file?
<whitequark> нуы
<whitequark> yes
<companion_cube> ;/
<companion_cube> :/
<companion_cube> also, smart constructors
badon has joined #ocaml
<whitequark> documentation is needed too
<whitequark> I want to know what the hell I'm matching over
<whitequark> look at Types.row_field for example
<whitequark> and try to tell how would [`A | `B of int] look
Reventlov has quit [Quit: leaving]
Reventlov has joined #ocaml
<companion_cube> it must be like Coq, they wrote most of the code ages ago and it was never refactored to have cleaner code
<companion_cube> which is understandable because it's a big effort
<whitequark> well, Alain undertook a truly heroic effort to make Parsetree usable
<whitequark> but everything below is just sheer horror
<companion_cube> it would be extremely interesting to have an alternative OCaml compiler (down to, say, dlambda or something like this)
<whitequark> I dunno, what would that achieve?
<companion_cube> cleaner code, a compiler that is easier to modify/understand/debug?
<whitequark> and some man-decades of effort
<whitequark> it's not ... hard to modify, it's merely unpleasant
<asmanur> ask def`
<companion_cube> whitequark: well I heard the typechecker was actually hard to modify
kvelicka has quit [Quit: Leaving.]
<def`> (there is no first-class module involved :P, and yes, ocamlc code is by no mean representative of ocaml code :P)
<whitequark> oh, right
<ggole> Few old codebases are beautiful.
<def`> code of the typechecker is a bit strange. Individual parts are straightforward, in the sense that they just get things done. There is few complicated control flow, a bit too much hidden state, but what is really surprising
<def`> there is no abstraction (encapsulation) at all
<def`> if something can be represented as an int, even if it isn't semantically, it's just an int that get stored. Also a lot of treatement are just copy-pasted, there is really factorization.
divyanshu has quit [Quit: Computer has gone to sleep.]
divyanshu has joined #ocaml
seliopou has joined #ocaml
<companion_cube> there is really factorization? or did you mean the opposite?
<def`> NO*
<companion_cube> ok
<adrien> ;p
<companion_cube> so, for instance, "why" (a software verification platform) has been rewritten from scratch twice since its beginning, because the authors think it's good to start from clean foundations from time to time
<companion_cube> using the experience acquired from the previous version
samrat has joined #ocaml
Gonzih has joined #ocaml
<def`> companion_cube: it makes sense. It's also unclear wether experience from previous version apply in the case of the typechecker, as it would be tempting to switch to another algorithm
<companion_cube> maybe so
<companion_cube> but still, writing a new typechecker with all current extensions baked in from the start would be good
reventlo1 has joined #ocaml
reventlo1 has quit [Client Quit]
<companion_cube> i.e. a typechecker designed to cope with subtyping and GADT from the beginning
<def`> maybe… It would mainly be painful
kvelicka has joined #ocaml
<companion_cube> but wouldn't the result be better than the current typechecker?
<def`> It could, it could not. Who knows without any code?
hausdorf_ has joined #ocaml
<companion_cube> yes, sure
nickmeharry has joined #ocaml
shinnya has quit [Ping timeout: 240 seconds]
hausdorff has quit [Ping timeout: 240 seconds]
vincom2 has quit [Ping timeout: 240 seconds]
Youri has quit [Ping timeout: 240 seconds]
Guest38299 has quit [Ping timeout: 240 seconds]
nickmeha1ry has quit [Ping timeout: 240 seconds]
Youri has joined #ocaml
mfp has quit [Ping timeout: 240 seconds]
maufred_ has quit [Ping timeout: 240 seconds]
skchrko has quit [Ping timeout: 240 seconds]
axiles has quit [Ping timeout: 240 seconds]
ivan\ has quit [Ping timeout: 245 seconds]
andy has joined #ocaml
ivan\ has joined #ocaml
skchrko has joined #ocaml
mfp has joined #ocaml
axiles has joined #ocaml
maattdd has quit [Ping timeout: 255 seconds]
shinnya has joined #ocaml
maufred has joined #ocaml
vincom2 has joined #ocaml
pyon has joined #ocaml
divyanshu has quit [Quit: Computer has gone to sleep.]
testcocoon has quit [Quit: Coyote finally caught me]
arj has quit [Quit: Leaving.]
testcocoon has joined #ocaml
<whitequark> oooooo, I figured out how to make pry.ml work on unpatched 4.02
<whitequark> you don't want to know how
<def`> pry ?
<whitequark> my toplevel/debugger thing
<ggole> Oh?
<def`> It seems quite minimalistic at the moment:)
<whitequark> I want a debugger which can execute arbitrary expressions in current context
<whitequark> and none of this "time travel" shite
<ggole> Heh
<ggole> Civilized backtraces would be good too
<whitequark> whatcha mean by "civilized"?
<ggole> Um, mostly "better than what we have"
<whitequark> what don't you like in bytecode backtraceS?
<ggole> At the moment if you make a mistake and test some code in the toplevel, you get something thoroughly unhelpful like "exception: Not_found"
<whitequark> ah, yes, sure, I even have an open PR for that
sepp2k has quit [Quit: Konversation terminated!]
<def`> Hmm, I am a bit worried by the use of exceptions both as an error mechanism and non-local control flow one.
<ggole> It's quite annoying to go form a bytecode backtrace to source, too, although that's probably mostly a matter of editor automation.
<def`> It would be nice to have less expressive but typechecked exceptions for non-local control flow (not producing backtraces), and real errors producing backtraces.
* companion_cube sits and quietly watches whitequark re-build the whole OCaml ecosystem by himself
<rks`> def`: "less expressive"?
maattdd has joined #ocaml
nlucaroni has joined #ocaml
<def`> I saw there was some changes in the exception API in 4.02, but backtraces are not yet completely separated from exceptions (it makes sense to request a backtrace from an arbitrary point, for debug purpose)
divyanshu has joined #ocaml
<ggole> Hmm, you could get much of the effect with a primitive that printed out a backtrace and then exited
<whitequark> def`: there's "raise_notrace" or something like that
<whitequark> not typechecked though
<ggole> I don't think that would help with the unhelpful Not_found problem though
<def`> whitequark: yeah it's not really about performance, just distinguishing two unrelated things expressed with a similar mechanism
<ggole> I guess most of those should be options
<def`> rks`: yes? Exceptions rebinding, generation, … exceptions names are much more complex than what a type-system can express easily
<rks`> right
<def`> rks`: having a more static subset that can be typechecked would make sense (especially, preventing name escapes)
maattdd has quit [Ping timeout: 264 seconds]
koderok has quit [Quit: koderok]
tristero has quit [Ping timeout: 255 seconds]
hausdorf_ has quit [Remote host closed the connection]
kvelicka has quit [Quit: Leaving.]
samrat has quit [Quit: Computer has gone to sleep.]
sagotch has quit [Remote host closed the connection]
zpe has joined #ocaml
maattdd has joined #ocaml
kvelicka has joined #ocaml
yomimono has joined #ocaml
_0xAX has quit [Remote host closed the connection]
travisbrady has joined #ocaml
slash^ has joined #ocaml
zz_flazz is now known as flazz
samrat has joined #ocaml
hausdorff has joined #ocaml
tane has quit [Quit: Verlassend]
Hannibal_Smith has quit [Quit: Sto andando via]
ygrek has joined #ocaml
maattdd has quit [Ping timeout: 244 seconds]
skchrko has quit [Quit: Leaving]
philtor_ has joined #ocaml
leowzukw has joined #ocaml
BitPuffin has quit [Ping timeout: 255 seconds]
maattdd has joined #ocaml
eikke___ has quit [Ping timeout: 245 seconds]
yomimono has quit [Ping timeout: 255 seconds]
DreamLinuxer has quit [Quit: leaving]
Gonzih has quit [Remote host closed the connection]
sgnb has quit [Read error: Connection reset by peer]
elfring has joined #ocaml
maattdd has quit [Ping timeout: 244 seconds]
yomimono has joined #ocaml
mcclurmc has joined #ocaml
<whitequark> [✔] Abuse insufficient quoting in ocamlc to work around insufficient flexibility in ocamlc
lambdahands has joined #ocaml
tobiasBora has joined #ocaml
eikke__ has joined #ocaml
lambdahands has quit [Quit: leaving]
fold has joined #ocaml
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
rgrinberg has joined #ocaml
rgrinberg has joined #ocaml
tane has joined #ocaml
<jerith> Is it possible to have two modules that reference each other's types?
kvelicka has quit [Quit: Leaving.]
<tane> maybe that can help
<jerith> Thanks.
zpe has quit [Ping timeout: 250 seconds]
tac_ has joined #ocaml
<ggole> modules can mutually recur, but it's a bit clunky and there are some restrictions
travisbrady has quit [Quit: travisbrady]
jwatzman|work has joined #ocaml
travisbrady has joined #ocaml
ollehar has joined #ocaml
ollehar has quit [Client Quit]
jjwatt has joined #ocaml
mcclurmc_ has joined #ocaml
mcclurmc has quit [Read error: Connection reset by peer]
maattdd has joined #ocaml
milosn has quit [Read error: No route to host]
milosn_ has joined #ocaml
philtor_ has quit [Ping timeout: 255 seconds]
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
<Leonidas> oh, does anyone use Ohm? http://ohm-framework.com/?
samrat has quit [Quit: Computer has gone to sleep.]
samrat has joined #ocaml
maattdd has quit [Ping timeout: 250 seconds]
pyon has quit [Quit: Fiat justitia ruat caelum.]
hausdorff has quit [Remote host closed the connection]
koderok has joined #ocaml
<whitequark> it seems very dated
Kakadu has quit [Quit: Page closed]
<whitequark> apache2, ocaml 3.12, doesn't use even lwt.syntax (!)
<whitequark> some questionable design decisions like resetting itself via database
<Leonidas> so, better use eliom?
dsheets has quit [Ping timeout: 240 seconds]
<Leonidas> it is on the first page of google if you look for 'ocaml web framework' :-)
<whitequark> oh, it also uses couchdb
<whitequark> burn it with fire
<whitequark> it seems to be a port of something between rails and node to ocaml
<whitequark> it could be *okay* if done well, but I would not say that it is done well
<companion_cube> what's wrong with not using lwt.syntax?
<whitequark> I'd say use eliom, yes
zpe has joined #ocaml
<whitequark> companion_cube: they reinvent it, poorly
<companion_cube> oh.
<whitequark> and add a bunch more syntax extensions with *very* questionable design
troutwine_away is now known as troutwine
_0xAX has joined #ocaml
kvelicka has joined #ocaml
<Leonidas> could be worse. Others use MongoDB which in my experience was always quite terrible
<whitequark> MongoDB is the worst
<whitequark> have you seen http://www.mongodb-is-web-scale.com/ ?
<Leonidas> no. *clicky*
<Leonidas> whitequark: the problem is, some people really like to use meteor which supports any database (as long as it is mongodb), so my enthusiasm for that platform can hardly be ever put in words ;-)
ygrek has quit [Ping timeout: 240 seconds]
<whitequark> if someplace where I worked considered using mongo, I would consider resigning immediately
hausdorff has joined #ocaml
shinnya has quit [Ping timeout: 255 seconds]
hhugo has quit [Quit: Leaving.]
travisbrady has quit [Quit: travisbrady]
samrat has quit [Quit: Computer has gone to sleep.]
locallycompact has quit [Ping timeout: 250 seconds]
<def`> my experience with mongo was extremely bad, it created as much problem as it solved. yet I don't what would be a good alternative (there are too many, that's the problem), but I don't care as I don't have to deal with dataset at the moment
<def`> I don't know*
<whitequark> def`: couchdb is bad, elasticsearch is bad, redis is bad (it works ok as a cache/pubsub)
<whitequark> cassandra is ok afaik
q66 has joined #ocaml
<whitequark> our ops guy plain out refuses to deploy mongo, because it's such a pain
<whitequark> "eats all the RAM, slows down and randomly segfaults"
<whitequark> def`: oh btw, check out postgres' latest schemaless features
<whitequark> you basically have a database with implicit schema like mongo, but it a) actually works b) can have indexes
George__ has quit [Ping timeout: 246 seconds]
<def`> I would have chosen postgres actually… Safe default when I don't know the alternatives
<whitequark> yep
<def`> but I'll take a look at cassandra (it is somewhat associated to Java in my mind, maybe I am wrong)
<whitequark> it's in Java
<whitequark> Java isn't bad as long as you don't run untrusted code on it :]
<def`> then postgres, unless there already is java in the system :)
<whitequark> they have somewhat different use cases
<def`> sure
<whitequark> e.g. cassandra is much better at sharding than postgres
<def`> I didn't had to deal with such big environment yet
octachron has joined #ocaml
<def`> but mongodb was so bad that we had to learn how to scale out even with a small dataset =]
<whitequark> should've used text files
lordkryss has quit [Quit: Connection closed for inactivity]
<def`> you're correct, grep would probably have been faster.
travisbrady has joined #ocaml
maattdd has joined #ocaml
tobiasBora has quit [Quit: Konversation terminated!]
englishm has quit [Remote host closed the connection]
englishm has joined #ocaml
maattdd has quit [Ping timeout: 255 seconds]
samrat has joined #ocaml
elfring has quit [Quit: Konversation terminated!]
kvelicka has quit [Quit: Leaving.]
thomasga has quit [Quit: Leaving.]
_0xAX has quit [Remote host closed the connection]
Kakadu has joined #ocaml
samrat has quit [Quit: Computer has gone to sleep.]
englishm has quit [Remote host closed the connection]
englishm_ has joined #ocaml
pootler has joined #ocaml
rgrinberg has quit [Quit: Leaving.]
ygu_ has quit [Read error: Connection reset by peer]
albino has joined #ocaml
<albino> anyone know where the best place is to ask questions about the tutorial found here? http://try.ocamlpro.com/
<def`> here, unless you're french in which case #ocaml-fr has locale specific support
<albino> Okay, I'm on lesson 2 and it has me doing "print_int 3", which I expect to print out "3", but when I do it I get this: - : unit = <uknown constructor>
Anarchos has joined #ocaml
rgrinberg has joined #ocaml
Kakadu has quit [Quit: Konversation terminated!]
<def`> albino: wow, they uploaded a wrong version of the system, this should be reported
philtor has joined #ocaml
<albino> def`: where should I report it?
<def`> albino: "Submit a bug report" at the bottom of the page
<def`> if you have a github account
<albino> def`: haha, should have seen that
<albino> I don't
<albino> I was sort of hoping someone here knew someone that was involved with it
<def`> otherwise I can do it
<albino> def`: do you mind?
testcocoon has quit [Quit: Coyote finally caught me]
<def`> I'll do it, nevermind, just ignore this print_int problem
<albino> def`: thanks
flazz is now known as zz_flazz
<albino> print_string also fails with the same problem
<gperetin> albino sry to jump in, but which browser do you use?
<gperetin> I'm asking because it blows up on load in Safari
<def`> gperetin: reproduced with firefox 31
<albino> gperetin: Firefox 29.0 on ubuntu
<gperetin> ah thx
<ggole> Yeah, same here
testcocoon has joined #ocaml
Kakadu has joined #ocaml
<albino> oh this thing hasn't had a commit since Nov 21, 2013
<albino> I wonder how quickly it will get fixed
lordkryss has joined #ocaml
typedlambda has quit [Ping timeout: 250 seconds]
typedlambda has joined #ocaml
<def`> the easiest is probably to just try on your computer with opam
jave has quit [Quit: ZNC - http://znc.in]
rand000 has quit [Quit: leaving]
englishm_ has quit [Remote host closed the connection]
englishm has joined #ocaml
yomimono has quit [Ping timeout: 250 seconds]
SethTisue has joined #ocaml
araujo has quit [Ping timeout: 256 seconds]
ygu has joined #ocaml
Simn has quit [Ping timeout: 240 seconds]
lambdahands has joined #ocaml
hhugo has joined #ocaml
yomimono has joined #ocaml
divyanshu has quit [Quit: Computer has gone to sleep.]
zz_flazz is now known as flazz
<gperetin> what do people usually use for quickly looking up docs on a module/function? eg. if I wanted to look up signature and params for Unix_error exception
SethTisue has quit [Quit: SethTisue]
<Kakadu> I use qocamlbrowser
<Kakadu> also you can do it in toplevel
<def`> lookup doc in toplevl ?!
<Kakadu> signature
<Kakadu> anyway
<Kakadu> is opam-doc already usable?
<def`> not yet
koderok has quit [Ping timeout: 264 seconds]
slash^ has quit [Quit: Leaving.]
englishm has quit [Remote host closed the connection]
divyanshu has joined #ocaml
<Drup> (19:15:22) Leonidas: it is on the first page of google if you look for 'ocaml web framework' :-) <--- Really ?!
<Drup> eliom should be properly indexed, the job must have been done very poorly if a never released never used software rank better for you
<gperetin> thanks!
<Drup> (ocsigen is before with me, but that's not really surprising)
englishm_ has joined #ocaml
SethTisue has joined #ocaml
<Drup> gperetin: I use ocp-browser, which is packaged with ocp-index
tac_ has quit [Quit: Leaving]
tac_ has joined #ocaml
<Leonidas> Drup: 1st hit is Ocsigen, second is OCaml and the Web tutorial, 3rd is Ohm, fourth is Ocsigen wikipedia page, fifth is eliom github repository, the rest is more or less useless.
<rgrinberg> die ohm, die.
<Drup> rgrinberg: was it born one day ?
<Drup> Leonidas: okay, that's better
<Leonidas> hahaha, I want an '#ocaml approved' badge for projects :-D
<Drup> (I still don't understand why it's here, but well)
<rgrinberg> Leonidas: link above is more or less an approximation of that
<gperetin> Drup thanks! I'm waiting for the doc command to be implemented :)
<Leonidas> oh, right, I remember awesome-ocaml. Just forgot about it.
<gperetin> basically, I was looking for something like this https://hackage.haskell.org/package/haskell-docs
<gperetin> or what help(module) does in python
Simn has joined #ocaml
<Drup> albino, gperetin : you can use this toplevel too : http://ocsigen.github.io/js_of_ocaml/#version=4.01.0
<Drup> it should be more up-to-date and more featureful
<gperetin> Drup same problem :)
<rgrinberg> Drup: i've been absent from #ocaml lately. any news on 4.02?
<Drup> rgrinberg: not really
<Drup> gperetin: hum, can you do a detailed bug report in https://github.com/ocsigen/js_of_ocaml/issues ?
<Leonidas> rgrinberg: opium looks neat
* jerith puts "syntax = lwt" in .ocp-indent for his project and is suddenly happier.
<gperetin> I think def` already reported an issue somewhere, if he didn't I can put something in here
<rgrinberg> Leonidas: it works and you can get started with it easily*. That's all I will say about it ;)
jave has joined #ocaml
<rgrinberg> * familiarity with async might be necessary
<Drup> why the * ? :D
<Drup> ahah :p
<rgrinberg> i'm making an lwt port though..
<rgrinberg> it's extremely boring work so that's why it's taking a while
<Drup> (my opinion on opium is that it's a sign eliom tutorials are not good enough)
<Anarchos> the best way to integrate an ocaml application with a (maybe distant) toplevel, is it to marshal strings through a channel ?
<Leonidas> rgrinberg: Yeah, I need something that will not make Ruby programmers run away screaming :-)
<rgrinberg> Drup: (and them pesky async people)
<Drup> rgrinberg: indeed
<Drup> rgrinberg: but you don't disagree, afair ? :p
<rgrinberg> indeed
<Drup> :)
<Drup> Leonidas: but whitequark will convert all ruby programmers to eliom in beginning of September anyway :D
<rgrinberg> been programming a lot in ruby lately. i'll say that ruby has 1 big advantage over ocaml in the commercial world
<rgrinberg> it's good at creating more work for other ruby programmers
<jerith> Ruby makes me sad.
_andre has quit [Quit: leaving]
Reventlov has quit [Quit: leaving]
Reventlov has joined #ocaml
travisbrady has quit [Quit: travisbrady]
hhugo has quit [Quit: Leaving.]
<Leonidas> jerith: nodejs makes me even more sad
rgrinberg has quit [Quit: Leaving.]
<Leonidas> Drup: how so?
<jerith> Leonidas: Likewise.
travisbrady has joined #ocaml
rgrinberg has joined #ocaml
Reventlov has quit [Client Quit]
Thooms has joined #ocaml
shinnya has joined #ocaml
<Drup> bleurg
hausdorff has quit [Remote host closed the connection]
<Leonidas> Drup: it'd be cool if https://ocsigen.org/install stressed opam more
<Leonidas> something like: "hey, you can install ocsigen by typing this simple line" (and a list of dependencies below)
<Drup> yeah ...
<Drup> there are lot's of stuff like this in the ocsigen doc
divyanshu has quit [Quit: Textual IRC Client: www.textualapp.com]
<Leonidas> yes, maybe I'll try to help some time.
<Leonidas> that's one thing the node folks got right
<Drup> Leonidas: they have slightly more manpower :(
<Leonidas> yes they do, but they focus on giving easy instructions, like "just type npm install whateverstupidpackagewithstupidname" so people dive right in
<Leonidas> opam is doing a *great* job to emulate this which is neat.
ggole has quit []
malo has joined #ocaml
<Leonidas> (don't want to bash ocsigen, I'm sure it is a great software, but I can see why people are a bit lost)
<Drup> I agree with you
<Drup> and the website is a bit of a pain to edit, which doesn't help
Reventlov has joined #ocaml
<Leonidas> yeah, some users are dead. like eigenclass.org
<Leonidas> cumulus looks nice. like a Hacker News which doesn't look like it escaped from the nineties.
<Drup> :D
<Drup> Leonidas: beware, basically all the developers are on this channel
<Leonidas> :-) Actually, that is something that is pretty awesome in smaller PL communities.
<gperetin> where does the "auxiliary library Misc" mentioned in Ocaml Unix book come from?
<Drup> which book ?
<gperetin> just at the top, they mention using Misc library which has try_finalize and some other convenient methods
<nlucaroni> That library is created through the work in the book.
<gperetin> oh :D
<nlucaroni> You'll have to maintain it yourself. I'm not sure if anyone has compiled the complete codebase to use externally.
<gperetin> no problem, thanks! I was reading first chapter and decided to install it now since I'm gonna need it, didn't bother reading further :/
<nlucaroni> there is a darcs repo of the code.
<nlucaroni> (i guess in case you want to cheat ;) )
<gperetin> nah, I'm going on my own :)
travisbrady has quit [Quit: travisbrady]
fraggle_laptop has quit [Ping timeout: 264 seconds]
octachron has quit [Quit: Page closed]
jrw has joined #ocaml
hausdorff has joined #ocaml
axiles has quit [Remote host closed the connection]
AltGr has left #ocaml [#ocaml]
Simn has quit [Quit: Leaving]
ollehar has joined #ocaml
ollehar has quit [Client Quit]
araujo has joined #ocaml
typedlambda has quit [Ping timeout: 250 seconds]
zpe has quit [Remote host closed the connection]
typedlambda has joined #ocaml
zpe has joined #ocaml
zpe has quit [Ping timeout: 260 seconds]
eikke__ has quit [Ping timeout: 240 seconds]
kvelicka has joined #ocaml
oriba has joined #ocaml
tane has quit [Quit: Verlassend]
Algebr has joined #ocaml
<Algebr> I've seen that in a .mly, for the production rules matching, one can do TOKEN1 TOKEN2 {Foo($1, $2)} or a = TOKEN1; b = TOKEN2 { Foo(a, b) }. Is there a difference?
studybot has quit [Remote host closed the connection]
<companion_cube> the latter is only possible with menhir
<companion_cube> but it's generally considered more readable
studybot has joined #ocaml
hausdorff has quit [Remote host closed the connection]
kvelicka has quit [Quit: Leaving.]
hausdorff has joined #ocaml
eikke__ has joined #ocaml
<Algebr> I'm not understanding the purpose of menhir's separated_list
troydm has quit [Quit: What is hope? That all of your wishes and all of your dreams come true? (C) Rau Le Creuset]
<Algebr> Is it just saying split a list on a token?
yomimono has quit [Ping timeout: 240 seconds]
philtor has quit [Ping timeout: 245 seconds]
<companion_cube> yes, but it's more convenient than writing a rule by yourself
travisbrady has joined #ocaml
<Algebr> But what is it giving back?
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
<companion_cube> separated_list(token,rule) returns a list of x if rule returns a x
Nahra has joined #ocaml
tobiasBora has joined #ocaml
<tobiasBora> Hello !
<Kakadu> how are you doing?
<tobiasBora> I'm having a strange problem (which is only visible under Windows, but present anyway), a file isn't closed and I can't delete it after.
<tobiasBora> I use somewhere this code : BatFile.lines_of myfile |> BatEnum.find f
<tobiasBora> Should the file be close right after this code ?
<tobiasBora> The doc says ""line_of name reads the contents of file name as an enumeration of lines. The file is automatically closed once the last line has been reached or the enumeration is garbage-collected.""
<tobiasBora> But I'm not sure when the enumeration is really "garbage-collected"
<companion_cube> I suppose that if you find a line, the last line is never read so you'd have to wait for the enumeration to be garbage collected
Kakadu has quit [Quit: Konversation terminated!]
<tobiasBora> companion_cube: And it can be garbage collected a long time after or it's just after the line ? (Because even me I can see that the enumeration won't be able to be collected, so maybe the compilateur see it)
<tobiasBora> And is there a good way to force the whole enumeration ?
<tobiasBora> Because it's too bad to have a such great function if I can't use it...
<companion_cube> it can be collected a long time after
<tobiasBora> Of thank you.
<tobiasBora> And is there a quick turn around for that ?
<companion_cube> none I'm aware of, I don't use batteries
Algebr has quit [Remote host closed the connection]
<tobiasBora> Ok thank you. Do you use any other "framework" ?
<Drup> (he NIHed his own :D)
jao has quit [Ping timeout: 255 seconds]
zpe has joined #ocaml
<companion_cube> ;)
<tobiasBora> Can I see it :D
<companion_cube> well seriously, the problem of IO iterators isn't easy
<companion_cube> https://github.com/c-cube/ocaml-containers/blob/master/core/CCIO.mli I have this stub for IO, but it's far from complete
troydm has joined #ocaml
<tobiasBora> I love that !
lambdahands has quit [Ping timeout: 250 seconds]
typedlambda has quit [Ping timeout: 250 seconds]
hausdorff has quit [Remote host closed the connection]
typedlambda has joined #ocaml
BitPuffin has joined #ocaml
Thooms has quit [Ping timeout: 240 seconds]
philtor_ has joined #ocaml
englishm_ has quit [Remote host closed the connection]
englishm has joined #ocaml
englishm has quit [Ping timeout: 255 seconds]
agarwal1975 has quit [Quit: agarwal1975]
lambdahands has joined #ocaml
zpe has quit [Remote host closed the connection]
darkf has joined #ocaml
zpe has joined #ocaml
zpe has quit [Ping timeout: 264 seconds]
eikke__ has quit [Ping timeout: 260 seconds]
rwmjones has quit [Ping timeout: 250 seconds]
agarwal1975 has joined #ocaml
troutwine is now known as troutwine_away
travisbrady has quit [Quit: travisbrady]
rwmjones has joined #ocaml
flazz is now known as zz_flazz
pyon has joined #ocaml
thomasga has joined #ocaml
madroach has quit [Ping timeout: 250 seconds]
madroach has joined #ocaml
Submarine has quit [Remote host closed the connection]
troutwine_away is now known as troutwine
NoNNaN has quit [Remote host closed the connection]
NoNNaN has joined #ocaml
thomasga has quit [Quit: Leaving.]
travisbrady has joined #ocaml
manizzle has joined #ocaml
bjorkintosh has quit [Ping timeout: 256 seconds]
lambdahands has quit [Quit: leaving]
bjorkintosh has joined #ocaml