flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 4.00.1 http://bit.ly/UHeZyT | http://www.ocaml.org | Public logs at http://tunes.org/~nef/logs/ocaml/
Neros has joined #ocaml
dsheets has quit [Ping timeout: 245 seconds]
avsm has quit [Quit: Leaving.]
darkf has joined #ocaml
oriba has quit [Quit: oriba]
ygrek has joined #ocaml
Neros has quit [Ping timeout: 268 seconds]
Neros has joined #ocaml
madroach has quit [Ping timeout: 264 seconds]
madroach has joined #ocaml
dtg has quit [Read error: Connection reset by peer]
dtg has joined #ocaml
osa1 has quit [Ping timeout: 245 seconds]
mfp has quit [Ping timeout: 240 seconds]
bkpt has quit [Quit: Leaving]
Nahra has quit [Ping timeout: 264 seconds]
travisbrady has joined #ocaml
zRecursive has joined #ocaml
<zRecursive> i forgot how to use "+,-,*,/" for float ?
Nahra has joined #ocaml
Nahra has quit [Changing host]
Nahra has joined #ocaml
<zRecursive> seems Float. {1.2 + 1.3} ?
q66 has quit [Quit: Leaving]
ygrek has quit [Ping timeout: 268 seconds]
Neros has quit [Ping timeout: 260 seconds]
Neros has joined #ocaml
ygrek has joined #ocaml
milosn_ has joined #ocaml
gereedy has quit [Ping timeout: 240 seconds]
levi has quit [Ping timeout: 240 seconds]
gereedy has joined #ocaml
milosn has quit [Read error: Connection reset by peer]
weie has quit [Read error: Connection reset by peer]
weie has joined #ocaml
Xom_ has joined #ocaml
Xom has quit [Ping timeout: 268 seconds]
Xom_ is now known as Xom
travisbrady has quit [Quit: travisbrady]
ben_zen has joined #ocaml
shinnya has quit [Ping timeout: 245 seconds]
tlockney has quit [Excess Flood]
tlockney has joined #ocaml
ggole has joined #ocaml
pkrnj has joined #ocaml
gasche has quit [Ping timeout: 264 seconds]
gasche has joined #ocaml
technomancy has joined #ocaml
<technomancy> how do I get a list of the values of a given function called N times?
tlockney has quit [Excess Flood]
tlockney has joined #ocaml
<ggole> let rec repeat f n = if n <= 0 then [] else f ()::repeat f (n - 1)
<technomancy> gotcha; so no built-in for that
<technomancy> thanks
<ggole> There might be something in core or batteries: the default stdlib is pretty bare bones.
<technomancy> indeed
tlockney has quit [Excess Flood]
<technomancy> I'm actually going through the new oreilly book, so core is fine, but this works too
tlockney has joined #ocaml
ben_zen has quit [Ping timeout: 268 seconds]
<technomancy> is there something wrong with these auto-generated docs?
ben_zen has joined #ocaml
<ggole> The documentation generator doesn't follow includes. You'll have to click through yourself.
levi` has joined #ocaml
<technomancy> ah, gotcha
<ggole> Maybe there should be an annotation to pull included material into a documentation page.
<technomancy> so... I've done `opam install core`, but `open Core.Std` fails in the toplevel
<ggole> That's a search path problem iirc: there's a little dance you do in .ocamlinit to make it work
<ggole> Uh, one moment
<ggole> let () = try Topdirs.dir_directory (Sys.getenv "OCAML_TOPLEVEL_PATH") with Not_found -> ()
<technomancy> my toplevel is definitely coming from an opam-managed install
tlockney has quit [Excess Flood]
<technomancy> that's already there =\
<ggole> Hmm
<ggole> (Well, that's good: the opam guys were supposed to fix it. Guess they did.)
<technomancy> ls $OCAML_TOPLEVEL_PATH # -> topfind
<technomancy> just one file
tlockney has joined #ocaml
<technomancy> core is one level up
<technomancy> as is everything else
<ggole> Let me fiddle around a bit and see what I can find.
<ggole> (I don't actually use core or batteries in my project, so I haven't run into this.)
<technomancy> ~/.opam/4.01.0dev+trunk/lib/toplevel is the dir with one file
<technomancy> topfind looks like it could be a shim designed to get me access to other things
<technomancy> but it's not working
tlockney has quit [Excess Flood]
<ggole> So it looks like you start the toplevel, #use "topfind" and then #require "..." to load a package
<ggole> (For actual use you would automate this with .ocamlinit, naturally.)
<ggole> Does any of that not work?
tlockney has joined #ocaml
<technomancy> I see now there's a directive in the book that I was missing
<technomancy> well, missing because I tried it and it didn't work
<ggole> Looks like something bad in your .ocamlinit
<technomancy> http://p.hagelb.org/.ocamlinit.html <- comes straight from the book =\
<ggole> Hmm :/
<technomancy> oh hum
<technomancy> works with utop
<technomancy> just not ocaml(1)
<technomancy> weird
<ggole> Try commenting out the bottom three lines
<ggole> And do the #requires by hand
<ggole> See where it goes bad
<technomancy> it's ok; I can stick with utop
<technomancy> some hand-wavy magic is allowable at this point; I'll circle back and make sense of it once some code gets written =)
<ggole> Fair enough.
tlockney has quit [Excess Flood]
tlockney has joined #ocaml
pkrnj has quit [Quit: Textual IRC Client: www.textualapp.com]
<ggole> Oh yeah, and you'll still get "unbound constructor" if you just name a module (due to the way the syntax works).
<ggole> Something like module X = Core.Std might be better
tlockney has quit [Excess Flood]
tlockney has joined #ocaml
<technomancy> can you curry =?
<technomancy> oh I see; I was missing the "open"
<ggole> If you mean partially apply, ((=) 1)
<ggole> There are no sections though
<ggole> So that's the first argument, not the rightmost argument
<technomancy> nice; thanks
levi` is now known as levi
<zRecursive> how to upgrade 3.12 to 4.0.x in freebsd ?
introom has joined #ocaml
<technomancy> I've got a list of [x;y] positions and want to build an index of which positions map to what values... what are my options?
<technomancy> associative list?
<ggole> That, Hashtbl or Map
<technomancy> looks like hash tables are mutable; don't want that
<ggole> Map then
<technomancy> cool
<technomancy> a vector of vectors would be fine too if it could be inserted into efficiently, but that's a tal order
<technomancy> tall
manud has quit [Quit: manud]
zpe has joined #ocaml
zpe has quit [Ping timeout: 240 seconds]
ggole has quit [Ping timeout: 240 seconds]
<levi> Is there a convenient way to tell opam to just build and install what's in the current directory? Or do I have to set up a local repository?
Nahra has quit [Quit: leaving]
ollehar has joined #ocaml
ulfdoz has joined #ocaml
ygrek has quit [Ping timeout: 246 seconds]
introom has quit [Remote host closed the connection]
ggole has joined #ocaml
<orbitz> levi: if you've pinned a package to your dir, you mean?
<levi> I mean, I have a package I've downloaded into a directory and built manually, but I'd like to have it installed with the rest of the opam libraries.
<orbitz> an opam package?
<levi> Yes. I have been away from ocaml for a while, so I am not very familiar with these recent tools.
<levi> I am trying to install it from a local directory instead of directly from its source because it has a minor incompatibility with my system that I had to fix.
zpe has joined #ocaml
<orbitz> levi: I'd just make an opam repository, add it to your list of repos and you can do opam install
ulfdoz has quit [Ping timeout: 246 seconds]
<levi> OK. Kind of a pain, but I'll manage. Thanks.
<orbitz> levi: or just modify your OCAMLPATH to point into the directory you just built and you don't have to d oanything
<orbitz> or just submit the package to opam so everyone can benefit :)
<levi> It's not my package, or I would. :)
djcoin has joined #ocaml
<orbitz> levi: What do you mean? It's alread yin opam but you didn't write it?
<levi> It's not in the public opam repository, but it's in someone else's repository.
<orbitz> is the package itself public?
<orbitz> i mean, what hte package installs
<orbitz> if it's all open, I don't think there is any social or legal reason you can't repackage it
zpe has quit [Ping timeout: 248 seconds]
<levi> I'm sure it'll get released when it's ready.
<zRecursive> Can i use opam to upgrade 3.12 to 4.0.x ?
<levi> I think you can use it to install 4.0.x.
<zRecursive> levi: thx, i am studying to use opam now
<orbitz> zRecursive: It won't upgrade your system, just the one you use iva opam
<orbitz> via
<zRecursive> orbitz: do you mean i need to install 4.0.x manually ?
* zRecursive maybe i can wait for the newest ocaml into freebsd ports
<gasche> zRecursive: OPAM cannot be built from a versino of OCaml older than 4.00
<gasche> so either you get a binary distribution of it, or you have to install a 4.00 on your system beforehand
<gasche> it would have been better for OPAM devs to support 3.12 as well, but well they didn't
<gasche> levi: note that you can have local OPAM packages, and in the packaging information you can store a patch to be applied against the upstream source
<gasche> if you want to keep this manually-changed package around long-term, that would be a better option
<orbitz> zRecursive: I mean that opam does not interact with your system at large, it installed things locally so installing a version of ocaml doesnot change it for your entire system
<zRecursive> gasche: ok
<zRecursive> orbitz: yeah
<zRecursive> opam --version => 1.1.0
<gasche> in practice most OPAM packages are probably just installing libraries through ocamlfind, so a non-OPAM-packaging that also uses ocamlfind should be compatible
<gasche> but then you'll have to handle reinstallation yourself when the OPAM repo changes
<zRecursive> "opam list => Installed packages for system:\n base-bigarray ...", opam indeed works with my ocaml 3.12
<gasche> zRecursive: "opam switch show" will give you "system"
<gasche> the opam switch is configured to point to your OCaml "system" install, the one that was there before OPAM
<zRecursive> yeah
testcocoon has quit [Quit: Coyote finally caught me]
<zRecursive> opam switch show => system
<gasche> if you want to install a 4.00, without touching your system, you can install it as a different switch
<gasche> (each switch is an independent installation of an OCaml version and any librairies packaged for that version in OPAM)
<zRecursive> gasche: install 4.0.x manually ?
<gasche> you don't need to
<zRecursive> oh
<gasche> I *think* "opam switch 4.00.1" will do the installation by itself
zpe has joined #ocaml
<gasche> hm
<gasche> that would probably be "opam switch install 4.00.1", in fact
<zRecursive> using root
<zRecursive> ?
<zRecursive> can i install using ordinary user account ?
<zRecursive> i want to install 4.00.1 into ~/ocaml
<orbitz> everything an opam can be done as a nonroot user
<orbitz> opam does not install thigns in ~/ocaml
<zRecursive> great
<gasche> read the manual :-'
<orbitz> by default at least
hkBst has joined #ocaml
<orbitz> Why do you need it in ~/ocaml?
<zRecursive> ls ~/ocaml/bin/ => opam opam-mk-repo now
<orbitz> I'm not sure what you're showing me with that line
<zRecursive> whereis ocaml => ocaml: /usr/local/bin/ocaml /usr/local/man/man1/ocaml.1.gz /usr/ports/lang/ocaml
<zRecursive> it is 3.12
ollehar has quit [Ping timeout: 240 seconds]
<orbitz> I still don't know what you're trying to tell me
<zRecursive> orbitz: now i am using 3.12, and i want install 4.0.1 into ~/ocaml
<orbitz> Why does it need to be in ~/ocaml?
ygrek has joined #ocaml
<zRecursive> i donot want it disturb 3.12
<gasche> but ~/.opam/... would be fine as well, right?
<zRecursive> sure
<gasche> well
<orbitz> zRecursive: You can isntall in many places that won' tdistrubte 3.12
<gasche> at some point zRecursive I think you should go read the OPAM documentation
<zRecursive> i will
<gasche> instead of having us re-hash it to you in a badly worded way over an IRC channel
<zRecursive> heh
<gasche> the short line is that by default, "opam switch install 4.00.1" will install the new version in ~/.opam
<gasche> (but you may have explicitly configured it to do otherwise)
zpe has quit [Ping timeout: 240 seconds]
<zRecursive> switching now, thx
<zRecursive> awesome, it is VERY fast
* zRecursive wish our old ocaml projects will work under 4.00.1 ...
cago has joined #ocaml
fmardini has joined #ocaml
introom has joined #ocaml
introom has quit [Ping timeout: 260 seconds]
<adrien_oww> morning
ben_zen has quit [Quit: leaving]
mcclurmc has joined #ocaml
zpe has joined #ocaml
Xom has quit [Ping timeout: 248 seconds]
zpe has quit [Ping timeout: 240 seconds]
Simn has joined #ocaml
dsheets has joined #ocaml
zpe has joined #ocaml
MarcWeber has quit [Ping timeout: 245 seconds]
testcocoon has joined #ocaml
MarcWeber has joined #ocaml
ttamttam has joined #ocaml
zRecursive has left #ocaml []
zRecursive has joined #ocaml
yezariaely has joined #ocaml
<zRecursive> After `opam switch install 4.00.1` and `opam config env`, ocaml reports: Cannot find file topfind. Unknown directive `require'. (there is #require "str";; in ~/.ocamlinit)
ttamttam has quit [Quit: ttamttam]
<zRecursive> seems i need to install topfind ?
thomasga has joined #ocaml
<zRecursive> but i donot know its package name
<gasche> zRecursive: opam install ocamlfind
<gasche> (topfind is part of ocamlfind/findlib, but you're right the name is not easy to guess)
<zRecursive> gasche: thanks
quelu_ has quit [Ping timeout: 260 seconds]
quelu has joined #ocaml
<zRecursive> gasche: do i need to put the output of `opam config env` into ~/.bashrc ?
<zRecursive> it is ok now, thx
zRecursive has left #ocaml []
<yezariaely> I want to work with the BatResult monad and I am missing the >> operator. Where can I find it? additionally, I'd like to have a mapM (map lifted to monads) is this available somewhere?
Xom has joined #ocaml
<gasche> yezariaely: map over what?
quelu has quit [Ping timeout: 245 seconds]
<gasche> BatEnum has a WithMonad functor that produces "sequence" (probably the mapM you're looking for) and "fold_monad"
<yezariaely> I have a function f : t -> (a',b') BatResult.t and now I have a lst : t list and want to apply map f lst. The result should however be an error, if there is one error.
<gasche> other Batteries module are not that well-furnished
<yezariaely> gasche: sounds correct.
<yezariaely> I will have a look
<yezariaely> ehm correct is the wrong word. "good" is better.
<gasche> if you want to contribute WithMonad functors for other datastructures, that could be a good idea
<yezariaely> is Core better wrt. monads?
<gasche> (and we could extend the range or supported monadic-lifted operations)
<gasche> I don't know
<yezariaely> yeah, maybe but time is a problem as with anyone ;)
<ousado> yezariaely: are you aware of wmeyers omonad?
<yezariaely> ousado: yes I am but never tried it. Does it work with Batteries.BatResult?
<gasche> omonad, in its present shape, is a Bad Idea
sgnb has quit [Read error: Connection reset by peer]
sgnb has joined #ocaml
<gasche> there is no way to make -ppx writers that do not disturb the existing syntax of the language
<gasche> so it should be considered a prototype/experiment only, and not actually used
<gasche> pa_monad are better choices if you want long-term monadic syntax extension
<ousado> gasche: disturb the syntax of the language?
<yezariaely> gasche: is the >> operator defined anywhere in Batteries
<gasche> yezariaely: I don't think so
<yezariaely> :(
<gasche> ousado: omonad gives a new meaning to a syntactically valid OCaml expression
<gasche> whereas pa_monad extends the language to allow previously undefined constructs
<gasche> yezariaely: patches welcome :]
<yezariaely> sure ;-) well, let's see I have holidays in two weeks. Maybe I can do something.
sgnb has quit [Remote host closed the connection]
sgnb has joined #ocaml
Anarchos has joined #ocaml
Kakadu has joined #ocaml
ggole has quit [Ping timeout: 256 seconds]
zpe has quit [Ping timeout: 246 seconds]
Xom has quit [Quit: ChatZilla 0.9.90.1 [Firefox 22.0/20130618035212]]
rossberg has joined #ocaml
<whitequark> gasche: I've been thinking about various RTTI techniques (not necessarily as an application to my SSA thingy), and it turns out that there are three possibilities, and they nicely correspond between OCaml and C-langs
zpe has joined #ocaml
<whitequark> the first one is to make a class method return a string with a class name, then, in match expression which aims to do narrowing, simply compare this string within a guard clause.
<whitequark> this is exactly how C++'s dynamic_cast<> typically works
<whitequark> (no wonder it's slow as hell)
<whitequark> the advantage is that there is a true open-world model which supports any kind of dynamic linking. the disadvantage is mainly speed.
mort___ has joined #ocaml
<whitequark> the second one is to declare a sum type with a variant for every possible subclass, and add a method #repr, which returns a value of that type
ggole has joined #ocaml
<whitequark> this roughly corresponds to what LLVM's homegrown RTTI does--except LLVM's implementation is able to handle deep inheritance trees by exploiting the fact that C++ enums are ordered
<whitequark> and in OCaml that would, I think, require a distinct sum type for each intermediate class
<whitequark> at least if you'd want to take advantage of exhaustiveness checking
mcclurmc has quit [Ping timeout: 256 seconds]
<whitequark> the third way would be to implement a technique similar to dynamic linking: place initialization code besides each class which would build a lookup structure, then again use guards in match clauses to perform queries to that structure
<whitequark> this one is most complex, but it potentially offers efficiency and an open-world model
<whitequark> gasche: by the way, how do GADTs simplify the task compared to regular ADTs?
avsm has joined #ocaml
quelu has joined #ocaml
pango has quit [Remote host closed the connection]
mcclurmc has joined #ocaml
mfp has joined #ocaml
osa1 has joined #ocaml
mort___ has quit [Quit: Leaving.]
Snark has joined #ocaml
mort___ has joined #ocaml
<gasche> whitequark: GADTs allow to transfer equalities between types
<gasche> if you have a blurb type 'a value that contains everything
<gasche> and you want to do what you call RTTI on it
<gasche> with ADTs, you would have a
<gasche> type 'a rtti_value = Int of int | Float of float | ... | Bar of narrowed_value_in_the_bar_case
<gasche> and have a function (inspect : 'a value -> 'a rtti_value)
<gasche> match inspect foo with Bar foo_refined -> ...
<gasche> so in the branch, foo_refined is *assumed* to be equivalent to foo, and it has the refined type (statically)
<gasche> with GADTs you could do things a bit differently
<gasche> type 'a rtti_tag = Int : int rtti_tag | ... | Bar : narrowed_value_in_the_bar_case rtti_tag
<gasche> when you match on a (a rtti_tag), in the Int case, you learn the type equality (a = int)
<gasche> so code would look like
<gasche> match inspect_tag foo with Bar -> ...
<gasche> and in this branch, locally, `foo` itself has type narrowed_value_in_the_bar_case
q66 has joined #ocaml
<gasche> whitequark: so I'd say that with GADTs, you can refine typing information without changing the dynamic value you're looking at
<gasche> (hm, forget the 'a parameter on rtti_value, it's useless)
<gasche> if you are fine with changing the dynamic value as a first step, it is better to use simpler type-system features of course
<gasche> GADTs give painful error messages
<whitequark> interesting
osa1 has quit [Ping timeout: 240 seconds]
osa1 has joined #ocaml
tane has joined #ocaml
Kakadu has quit []
Kakadu has joined #ocaml
Simn has quit [Read error: Connection reset by peer]
dsheets has quit [Ping timeout: 248 seconds]
fmardini has quit [Ping timeout: 256 seconds]
ttamttam has joined #ocaml
amirmc has joined #ocaml
fmardini has joined #ocaml
ttamttam has quit [Client Quit]
dsheets has joined #ocaml
Neros has quit [Ping timeout: 268 seconds]
Neros has joined #ocaml
<kerneis> gasche: ocamlbuild --helps tells among other things
<kerneis> -no-stdlib Don't ignore stdlib modules
<kerneis> is it really "Don't ignore"?
<kerneis> it seems counter-intuitive
Neros has quit [Ping timeout: 260 seconds]
tane has quit [Quit: Verlassend]
osa1 has quit [Remote host closed the connection]
osa1 has joined #ocaml
_andre has joined #ocaml
ygrek has quit [Ping timeout: 245 seconds]
beckerb has joined #ocaml
amirmc has quit [Quit: Leaving.]
Anarchos has quit [Quit: Vision[0.9.7-H-130604]: i've been blurred!]
amirmc has joined #ocaml
yezariaely has quit [Quit: Leaving.]
skchrko has joined #ocaml
osa1 has quit [Ping timeout: 245 seconds]
osa1 has joined #ocaml
ollehar has joined #ocaml
introom has joined #ocaml
amirmc has quit [Quit: Leaving.]
yezariaely has joined #ocaml
<kerneis> okay, now another ocamlbuild question
<kerneis> is there simple way to convince ocamlbuild to include someexternallib.cmo inside mylib.cma, using ocamlfind?
<kerneis> if I just put Someexternallib inside mylib.mllib, it fails to find it
<kerneis> (which is arguably a bug, or maybe not)
<adrien_oww> "include"?
<kerneis> include cannot point above your root directory
<kerneis> this is another "feature"
<kerneis> root = where myocamlbuild.ml is
<kerneis> yes, I could use symbolic links, but this is really overkill
<kerneis> ln -s $(ocamlfind query someexternalib) local_copy
<kerneis> and ocamlbuild would should about hygien violations
<kerneis> shout*
<kerneis> oh wait wait wait
<kerneis> in fact, I want to include someexternallib.cma, not someexternallib.cmo
<kerneis> so ocaml_lib should be able to help
<avsm> or create an ocamlfind package for that
<kerneis> avsm: there *is* an ocamlfind package for that
<avsm> ocamlbuild -use-ocamlfind ?
<kerneis> it finds the libray, but does not bundle it in the .cma automatically
<kerneis> and if it is in a .mllib, it does not help (fails to find it)
<avsm> You want a cma to contain another cma?
<kerneis> yep
<avsm> i didnt think you could do that (can't using C archives either)
<avsm> ar rc foo.a bar.a wont work
<kerneis> because I'm writing plugins, and I would like it to be self contained
<kerneis> so that my user does not need to bother loading all the dependencies first
<kerneis> (although ocamlfind helps with that)
<avsm> i dont think trying to wrap them in an .mllib is the right answer there
<kerneis> agreed
<kerneis> it
<kerneis> was just one of my guesses
<kerneis> avsm: in fact, my real goal is to do it for cmxs
<kerneis> because bloody library writers do not provide .cmxs all the time
<avsm> yeah. that's a bummer :-)
<kerneis> so, bundling an external .cmxa into my cmxs
<adrien_oww> easier to kick them until they do it
<kerneis> it works, but I need to convince ocamlbuild to make it look reasonably easy
<avsm> (or, as a maintainer on openbsd/sparc64, if they *do* include cmxs, then i need to patch it away on bytecode only arches)
<kerneis> (another issue, yeah; would be great if you could update ocaml-autoconf macros to support that use case easily)
<kerneis> (I would be so grateful)
<kerneis> please, juste provide me a macro testing if dynlink.cmxa is available
* kerneis throws feature requests all over the place
ygrek has joined #ocaml
xenocons has quit [Ping timeout: 264 seconds]
xenocons has joined #ocaml
<introom> let x = 1 in x + 1, let y = 2 in y + 1, 4;; will evaluates to int * (int * int), why not int * int * int?
<kerneis> introom: because the second let introduces some sequencing I guess
<introom> yeah, in (y+1, 4) actually.
<kerneis> oh, it has nothing to do with sequencing, it's just precedence in fact
<kerneis> I'm a bit dumb
<kerneis> (let x = 1 in x), (let y = 2 in y), 4 ;;
<introom> so , has higher precedence than in ?
<kerneis> looks like so
* introom dunno what sequencing is .
<kerneis> sequencing would have to do with the order of execution
<introom> got it.
<kerneis> let has the lowest precedence
<introom> really? ',' should be lower than 'let'
<kerneis> well, look at the table in my previous link
<kerneis> given your example, I think I disagree
<kerneis> you definitely want to be able to write let x = 3 in x, x
<kerneis> without the extra parentheses
<kerneis> would lead to horrible bugs otherwise
<kerneis> imagine:
<kerneis> let f x = let x = x*2 in x, x
<kerneis> f 3 would return (6, 3)
cdidd has quit [Ping timeout: 246 seconds]
cdidd has joined #ocaml
<introom> kerneis: yeah. let's precedence means the clause "let xx in"'s precedence, that makes sense.
<gasche> kerneis: beware that while including .cma in .cma is allowed, this won't work for .cmxa
<gasche> (or at least something something in the native case)
<gasche> I prefer to avoid compilation options that don't work both in byte and native modes
<gasche> hm
Drup has joined #ocaml
<kerneis> gasche: cmxa in cmxs works though
<kerneis> at least in my test-case
<kerneis> maybe i'm just lucky
<kerneis> btw, does anybody agree that there is an issue with the help message here: "ocamlbuild --help|grep stdlib" or is it just me being confused?
<gasche> I have no idea what -no-stdlib does
<gasche> so
<gasche> looking at the sources, kerneis
<gasche> the message is right but confusing
<gasche> when computing the dependencies of a module through ocamldep, ocamlbuild will filter out what's part of stdlib
cdidd has quit [Remote host closed the connection]
<kerneis> oh, yes
<gasche> if you want to build in an environment where no stdlib is available (and you would pass -nostdlib to the OCaml compiler), you would want modules having those names to also appear in the dependencies, hence "don't ignore them"
<kerneis> so the option name is in fact misleading
<kerneis> hmm, ok
cdidd has joined #ocaml
<gasche> I think the name is correct
<gasche> but the description could have to be improved; not sure how, though
<kerneis> in fact, it's completely correct, but really counter-intuitive
<gasche> it's probably not worth bothering with given how arcane it is
<kerneis> because the case is not so common probably
cdidd has quit [Remote host closed the connection]
<gasche> so
<gasche> I think the reason why those need to be filtered out
<gasche> is that you don't explicitly pass stdlib.cma to the OCaml compiler, it is added in an ad-hoc way there
<gasche> if ocamlbuild passed stdlib.cma, the usual archive-handling mechanism would handle that
<thizanne> I suggest something like « Don't deal differently with with stdlib modules »
<thizanne> -with
<gasche> (and ocamlc would have to be called with -nostdlib I suppose, but probably this flag does other stuff as well and it wouldn't work)
<gasche> hi thizanne :)
<thizanne> hi gasche
<gasche> maybe "Do not assume the stdlib is available"?
<gasche> I think most users would be left wondering what "deal differently" means
<gasche> ("deal differently" is not worse than "ignore", but still bewildering)
<thizanne> I did not dare to change the message that much :)
<gasche> I vote for keeping the message as it is and concentrating on more pressing issues on ocamlbuild
<gasche> btw. kerneis I thought more about your patch
<gasche> (though I'd accept the killer message and it's easy to provide a patch for that)
<gasche> I'll write on the bugtracker
<kerneis> ack
cdidd has joined #ocaml
amirmc has joined #ocaml
ygrek has quit [Ping timeout: 245 seconds]
<kerneis> to conclude my previous issue, I confirm that using ocaml_lib in myocamlbuild.ml + tag use_someexternallib works perfectly
<kerneis> probably no need to change anything
<kerneis> oh but Findlib is available in myocamlbuild.ml!
<kerneis> even cleaner then
<introom> is there a way to project the element of a tuple ? given the tuple contains elements of different type?
<thizanne> if it is a 2-tuple, you have fst and snd, if not, you need to write your projection yourself
<kerneis> introom: only fst and snd for pairs
<gasche> 15:33 < kerneis> oh but Findlib is available in myocamlbuild.ml!
cdidd has quit [Quit: Leaving]
<gasche> I'm surprised, where does that come from?
cdidd has joined #ocaml
<gasche> I suspect you are hitting ocamlbuild's Findlib module, which is not Gerd's code
<kerneis> yeah
<gasche> but merely a reimplementation of some parts of it for the old -no-ocamlfind world
<introom> yeah. I am thinking about how to write it because a function must return a value of the same type.
<kerneis> just got a compilation error
<kerneis> :-(
<kerneis> introom: it will be polymorphic, no problem, or I didn't get your point
<gasche> note that in PR#5680 I discuss ways to make arbitrary ocamlfind packages available to myocamlbuild.ml
<gasche> (maybe he wants int -> n-th element ?)
<kerneis> that is impossible indeed
<kerneis> gasche: yes, I'm following PR#5680
<introom> let (x, y, z) have different type https://gist.github.com/introom/6164490
<kerneis> gasche: for this simple case, (Findlib.query name).Findlib.location is equivalent to Gerd's Findlib.package_directory
<kerneis> and better than calling "ocamlfind" yourself I guess
<gasche> I'm not sure how long this half-baked Findlib support will remain in ocamlbuild
<gasche> I'd rather pay the external call if I were you
<kerneis> ok
<gasche> but then I hope we'll get a solution for modularity soon
<kerneis> :-)
<gasche> I answered on the .mllib bug
<kerneis> seen
<kerneis> does mantis support reply by email?
<gasche> I don't know
<kerneis> given the nouser@inria.fr, I guess not
<gasche> (so that you can yell at me and then pretend your email account was cracked ? ;)
<kerneis> no, so that I can answer without opening my browser
<introom> kerneis: my question is given a tuple: (a, b, c, d, ...) and an index n, how to get the nth element ?
<gasche> you can't do that in a type-safe way
<gasche> unless your index is statically known
<gasche> in which case it shouldn't be written as an integer per se
<gasche> you can define
<introom> if gasche already known?
<gasche> let's say
<gasche> get1_3 : ('a * 'b * 'c) -> 'a
<gasche> geti_j for any reasonable (i,j)
<gasche> and then if you know statically (when writing the code) that (n = 3) and the tuple has type (l = 5), instead of your imaginary "get n", write get$n_$l if you want
<gasche> Batteries provides such accessors for small values of i and j
<gasche> it's not *obviously* better than let (_a,_b,c,_d) = foo in ... c ...
<introom> so if I have (3, "23", 2) and I want to get the last val, which is 2, I have to find some battery?
<introom> or directly write let _, _, last = (3, "23", 2), that seems too trivial.
hkBst has quit [Quit: Konversation terminated!]
cdidd has quit [Quit: Leaving]
<ggole> If you access particular fields enough that it becomes an issue, you should be using a record.
<gasche> (or define an accessor function, but yes records are better long-term)
<ggole> I don't see any objection to static integer tuple accessors myself, but since OCaml doesn't have those, just use what works.
<gasche> ggole: a single index doens't work well if your types are not implicitly pairs right-nested
<introom> I used to write python, the slice thing really makes my life comfortable...
<gasche> you can do the same in OCaml, using lists or arrays
<gasche> all elements are forced to have the same type... as in python
<ggole> Eh? Indexing is exactly the accessor that you would write yourself
<gasche> (type "blurb you don't know anything about")
<ggole> Except you don't have to bother writing it yourself.
travisbrady has joined #ocaml
<gasche> ggole: but you have to choose the tuple shape
<gasche> (right-nested or left-nested of course)
adrien_oww has quit [Remote host closed the connection]
<ggole> I'm not sure what you mean by nesting: you'd have to do something about inference?
cdidd has joined #ocaml
<ggole> I guess that would mean another hack like '_a, so maybe it is actually problematic
<ggole> I was thinking "ATS has those", but of course ATS doesn't have that problem
<whitequark> I want to do something like: "class foo = object(self) val lst = [self] end"
<whitequark> but...
<whitequark> Error: The instance variable self
<whitequark> cannot be accessed from the definition of another instance variable
<whitequark> why is that so?
<yezariaely> I want to use bisect in combination with the OcamlMakefile but I have problems integrating that.
<yezariaely> I want to have the following calls: ocamlfind ocamlc -package batteries,oUnit,bisect -c -dtypes -g -pp "camlp4o str.cma $BI/bisect_pp.cmo" test.ml
<yezariaely> Anyone knows how to achieve this?
<yezariaely> The variable PPFLAGS seems to be wrong.
zshi has joined #ocaml
<zshi> 1
<kerneis> whitequark: you need to change val to method
<whitequark> kerneis: I guess I stripped too much
<whitequark> my original code looks like: val args = List.map (fun ty -> new argument(self, ty)) args_ty
<whitequark> so I don't want to create new arguments each time I execute the method #args
<whitequark> I guess the only way to do it is lazy initialization?
zshi has quit [Quit: Lost terminal]
ollehar has quit [Remote host closed the connection]
ollehar has joined #ocaml
<kerneis> probably
<kerneis> I don't the reason of this restriction
<gasche> well
<kerneis> but probably the reason why recursion is disabled by default
<gasche> I suppose values are initialized first, and then "self" starts making sense
<whitequark> gasche: interesting
<gasche> you don't want to talk about non-fully-complete "self" or you'll shoot yourself in the foot just as C++
<whitequark> that makes sense indeed
<kerneis> it looks like this is a more general warning about not being able to reference an instance variable from another one though
<kerneis> class foo = object(self) val lst = 1 val lst2 = lst end ;;
<kerneis> fails just the same
<whitequark> maybe the order of initialization is not well-defined ?
<kerneis> yes, that's my guess
<kerneis> and you could initialize with side-effects
<introom> let f x =x;; List.iter f [1;2;3];; and it fails, why?
cdidd has quit [Ping timeout: 240 seconds]
<kerneis> raaaaaaah, I hate "make inconsistent assupmtions" at the very end of compiling OCaml
<kerneis> I don't know what to delete, and I don't want to start from scratch…
<whitequark> uh, I think I broke ocaml
<whitequark> Fatal error: exception Assert_failure("typing/ctype.ml", 359, 6)
<rks`> whitequark: o/
<kerneis> :-D
<Drup> kerneis: most of the time, the good way is a brutal clean and recompile ...
<kerneis> I just did that
<kerneis> but my disk is slow
<whitequark> kerneis: compile on tmpfs.
<orbitz> git clean -xdf !
<whitequark> hm, I can easily reproduce that.
quelu has quit [Read error: Operation timed out]
<kerneis> gasche: it WORKS!
<kerneis> option 3, cmo -> mllib
osa1 has quit [Read error: Connection reset by peer]
osa1_ has joined #ocaml
quelu has joined #ocaml
<gasche> kerneis: good news, I was going to try just that
<gasche> did you just test it?
<gasche> (or had you already done something like that?)
cdidd has joined #ocaml
<whitequark> so this somehow breaks the typechecker: https://gist.github.com/whitequark/7ab818d36c799762be52
<kerneis> just tested it
<kerneis> i'm adding corresponding code for mldylib and sending the patch
<gasche> that's very nice, thank you
djcoin has quit [Quit: WeeChat 0.4.0]
<kerneis> what i'm not sure is whether the rule should be "cmx & o -> mldylib" or if "cmx -> mldylib" is enough
<kerneis> (given the fact that the .o will be tested in mldylib -> cmxs anyway)
<kerneis> it probably doesn't make any difference, just a matter of style about when we fail
<gasche> whitequark: this seems to be a bug that wasn't present in older versions of OCaml
<gasche> the file works under 3.12, fails under 4.00.1 and trunk
<gasche> would you file a bug report?
<gasche> (by works I mean "fails with a type error")
<whitequark> gasche: sure. in the meantime, can you please post the type error somewhere?
<whitequark> because I have no idea why is it not well-typed
<gasche> File "test.ml", line 15, characters 43-53:
<gasche> Error: This expression has type < arguments : 'a; .. > * 'b but an expression was expected of type 'c Self type cannot escape its class
fmardini has quit [Ping timeout: 260 seconds]
<gasche> whitequark: the problem is that the class has no way to describe its own type
<gasche> but this type would be needed to describe the type of the method "arguments"
<gasche> you should be able to work around that by adding a type parameter that can talk about this type
<gasche> class ['a] foo = object (self : 'a) ... end
<whitequark> gasche: hmm, strange
<whitequark> why would it need to refer to the type of itself?
<whitequark> method arguments : argument list
<whitequark> argument isn't polymorphic, or at least wasn't intended to be
<gasche> I don't know what "new argument" makes
<whitequark> the argument class is defined at line 19
<whitequark> or are you talking about something else ?
<gasche> oh
<gasche> you are doing polymorphic recursion
<gasche> if you take "func" out of the class .. and .. block and define it in a second step
<gasche> it works
<gasche> (but I suppose you real-world case really need this recursive circle)
<gasche> in absence of type annotations, mutually-recursive functions are typed as monomorphic functions (and later generalized)
<gasche> (because doing otherwise would be undecidable)
<gasche> hm
<gasche> in maybe easier to understand words, I mean
<whitequark> sure, I understood you
osa1_ has quit [Ping timeout: 245 seconds]
<whitequark> on a second look, I do not think I actually need these class types to be defined recursively
<gasche> while it's still trying to understand the type of the whole "class .. and .. and" structure, the type-checker picks fresh unknown types for any of the three; in the "new argument(self,...)" case, the unknown type with "argument" is mixed with the type for "self"; this count as an escape of the self type
<gasche> s/with "argument"/for "argument"/
<gasche> please submit a bugreport anyway
yezariaely has quit [Quit: Leaving.]
<gasche> thanks
ygrek has joined #ocaml
<whitequark> hm, no, I do need recursion there :/
Neros has joined #ocaml
<whitequark> gasche: so. a better demonstration of what I'm trying to achieve: https://gist.github.com/whitequark/44af67d9b852ed57a384
<kerneis> gasche: okay, adding the cmo -> mllib yields unexpected dependencies to be satisfied but I'm ironing it out
<whitequark> gasche: by the way, I've tried adding a type parameter
<whitequark> (class ['a] foo = object (self : 'a) ... end)
<whitequark> it explodes in a different assertion in ctypes.ml :)
<whitequark> (I've updated the gist)
jbrown has quit [Ping timeout: 248 seconds]
<gasche> whitequark: this one works in trunk
<gasche> so it's been fixed since 4.00.1
<gasche> it's the same error as before on "new arguments"
<whitequark> I see
<whitequark> how can I fix this?
<gasche> you need the recursion?
<whitequark> yes
<whitequark> well, without recursion there couldn't be a type for class argument, right?
<whitequark> the inferencer will infer a polytype for it, and then it'll get rejected
<gasche> hm
<gasche> in fact I was wrong, this again fails in trunk
<whitequark> I imagine I can generalize class argument over class func, i.e. replace method parent : func in the signature with method parent : 'a
<whitequark> and thus get rid of recursion
<whitequark> but this doesn't look like a very good solution to me
jbrown has joined #ocaml
<whitequark> gasche: any ideas?
Nahra has joined #ocaml
<gasche> whitequark: I'm trying two different things
alang__ has joined #ocaml
alang_ has quit [Ping timeout: 260 seconds]
cago has left #ocaml []
introom has quit [Remote host closed the connection]
ygrek has quit [Ping timeout: 276 seconds]
<gasche> whitequark: so
<gasche> I think you need polymorhpic recursion, but it's not implemented at the class level in OCaml
<gasche> the workaroudn is to do open recursion instead: instead of calling "new argument" in your func class, parametrize func over an input that will be instantiated with an argument factory later (when you "tie the knot")
<gasche> I believe this corresponds to what is described there: http://pauillac.inria.fr/~remy/cours/appsem/ocaml-objects.html#toc13
<gasche> kerneis: thanks, looking at it
<gasche> kerneis: what do you mean by "thanks to ocamlbuild lazy approach"?
<kerneis> just the fact that it doesn't build what it already has
<kerneis> gasche: probably a poor wording, couldn't think of anything better
<gasche> ok
zpe has quit [Remote host closed the connection]
<kerneis> gasche: ocamlbuild/signatures.mli says about [rule]: "the ~tags argument is deprecated, don't use it", but it's heavily used in ocaml_specific.ml!
* kerneis should stop looking at ocamlbuild's source code
<gasche> yes
travisbrady has quit [Quit: travisbrady]
<gasche> we realized that with avsm a few weeks ago
<gasche> I have a patch from him sitting somewhere to remove all the ~tags from ocaml_specific
<gasche> we were confused as well
<gasche> I'll apply it on trunk
<kerneis> at least that's why I removed it from my newly introduced rules
<gasche> of course, you were right to do so
<gasche> in fact
<gasche> better apply his patch sooner than later, so that you can rebase yours on top of it
<kerneis> after wondering during 10 minutes and *then* reading the doc :-)
<kerneis> or you can apply mine and then avsm's, up to you
<kerneis> I use git so don't mind rebasing
<whitequark> gasche: hm, this is what I ended up with: https://gist.github.com/whitequark/01a96382fedfb3c1b137
<whitequark> it is clear from this that from the argument class, I won't be able to manipulate func-s
<whitequark> (neither could I do within the window-observer example you linked, *on the base class level*)
<gasche> kerneis: as I said on the bugtracker, I won't apply yours right away
avsm has quit [Quit: Leaving.]
<kerneis> ok
<kerneis> oh, didn't get the email
travisbrady has joined #ocaml
<whitequark> gasche: so as long as I only want to store the parent link, it's fine... an actual circular dependency between two classes, with method calls and such, seems to be impossible to type
<gasche> kerneis: if you feel motivated enough (you've surprised me so far), you can add the testsuite stuff
<gasche> wmeyer's testsuite (in testsuite/, no tests/) is a pleasure to use
<kerneis> where does it leave?
<kerneis> ok
<gasche> so far we've added everything in level0.ml
<gasche> at some point we'll need to structure that a bit better, but it's fine for now
<kerneis> not today, but maybe later this week
<gasche> ok
<gasche> otherwise I may do it
<kerneis> if I start working on it, I'll let you know
<kerneis> if I don't say anything, feel free to go ahead
shinnya has joined #ocaml
csakatoku has joined #ocaml
bkpt has joined #ocaml
pango has joined #ocaml
mort___ has quit [Ping timeout: 245 seconds]
<gasche> Anil's patch completely removes the ~tags parameter from the interface
<gasche> I think that for compatibility purposes I'll rather make its use emit a warning -- at least as a first step
<gasche> (I cringe at the idea of all those users having copy-pasted old stuff in their myocamlbuild.ml suddenly getting a compile error)
<gasche> the warning text I'm going for so far is the following
<gasche> "Warning: your ocamlbuild rule %S uses the ~tags parameter, which is deprecated and ignored."
<gasche> any comments on the wording will be appreciated
skchrko has quit [Remote host closed the connection]
amirmc1 has joined #ocaml
amirmc has quit [Ping timeout: 245 seconds]
amirmc1 has quit [Client Quit]
<kerneis> gasche: good
<gasche> I just commited the change to trunk
<gasche> adrien: did I already ask you for a comment on the output_obj_ext.diff patch in http://caml.inria.fr/mantis/view.php?id=6059?
<gasche> (on how inferior the english typography is in presence of URLs)
travisbrady has quit [Quit: travisbrady]
<gasche> hm
<gasche> adrien: forget about it, it looks fine
csakatoku has quit [Remote host closed the connection]
ollehar has quit [Ping timeout: 240 seconds]
zpe has joined #ocaml
zpe has quit [Ping timeout: 245 seconds]
darkf has quit [Quit: Leaving]
amirmc has joined #ocaml
Kakadu has quit [Ping timeout: 240 seconds]
csakatoku has joined #ocaml
amirmc has quit [Ping timeout: 245 seconds]
travisbrady has joined #ocaml
avsm has joined #ocaml
zpe has joined #ocaml
csakatoku has quit [Ping timeout: 264 seconds]
zpe has quit [Ping timeout: 245 seconds]
avsm has quit [Quit: Leaving.]
thomasga has quit [Ping timeout: 268 seconds]
thomasga has joined #ocaml
Yoric1 has joined #ocaml
thomasga has quit [Ping timeout: 245 seconds]
osa1 has joined #ocaml
thomasga has joined #ocaml
amirmc has joined #ocaml
osa1 has quit [Remote host closed the connection]
amirmc has quit [Ping timeout: 240 seconds]
Yoric1 has quit [Ping timeout: 264 seconds]
osa1 has joined #ocaml
zpe has joined #ocaml
<ggole> The typing of GADTs rules out certain kinds of functions on ADTs, is that right?
<gasche> ggole: what do you mean?
<ggole> You can't 'mix' constructors
<ggole> Uh, one moment. I'll make an example.
<ggole> type _ num = | One: int -> one num | Two : int -> two num
<ggole> You can't write a function that permutes a One into a Two, and vice versa
<ggole> (Oops: just pretend there are empty definitions of type one and type two)
<mrvn> you can write a function ('a num, 'b num) -> ('b num, 'a num) and build your ast accordingly.
<ggole> But there's no way to say "this could return any leg of the ADT"
<mrvn> depends on your type
<ggole> Hmm
<mrvn> and there are certainly things the type system can
<mrvn> 't grock
avsm has joined #ocaml
zpe has quit [Ping timeout: 264 seconds]
<gasche> ggole: you can do that using an existential type
<gasche> avsm: on my machine, your testsuite for PrincipalFlag failes
<gasche> because you build two target, I get the error message twice, as opposed to the tests that assume only one error message
<ggole> Oh?
<gasche> ggole: an existential type allows you to say that you don't know what a part of the type is
<ggole> I've read there is a connection, but I won't pretend to understand what it is.
<gasche> so you could type a swap as
<gasche> "I don't know which num I get, and I don't know which one I return"
<gasche> this is less precise than the type-level function you would want to express (you could say that as well but it's even more painful)
<gasche> hm
<ggole> That sounds like the answer to my problem.
<mrvn> gasche: But that is different to I will swap the two types.
<gasche> but you are still right in the sense that you have to add explicit (including at runtime) existential wrapping
<gasche> mrvn: you can do that as well
<gasche> type (a, b) swap_witness = | OT : (one, two) swap_witness | TO : (two, one) swap_witness
<mrvn> gasche: already said that
<gasche> val swap : type a b . a num -> b num * (a, b) swap_witness
<mrvn> ggole: witness types are fun
<gasche> what I had suggested was val swap : some_num -> some_num
<gasche> (less precise but also more widely applicable)
<ggole> Mmm... I see my understanding of GADTs is even more superficial than I thought
<gasche> ggole: you need to define some_num as type some_num = Exists : 'a num -> some_num
<gasche> let swap = function Exists One -> Exists Two | Exists Two -> Exists One
<ggole> OK
<ggole> I'll chew on that for a bit
Drup has quit [Ping timeout: 248 seconds]
mort___ has joined #ocaml
Neros has quit [Read error: Connection reset by peer]
Neros has joined #ocaml
<ggole> Hrm, you really do need the wrapping
<mrvn> if you only use the Exists form then you can just use type onetwo = One | Two
<gasche> mrvn: well you can still give the more precise type to other operations
<gasche> existential allow to give up type information only locally
<mrvn> then you wouldn't using only the Exists form
<gasche> (or "on the outside", I should say)
<gasche> of course
<gasche> ok
<gasche> I see what you mean, sorry
<gasche> hm
<gasche> avsm: I see you were busy doing user support on the mailing-list ^^ I reopened PR#6060 with my problem
Neros_ has joined #ocaml
<avsm> gasche: hrm, it passed for me. perhaps because i didnt have ocamlopt? odd
Neros has quit [Ping timeout: 264 seconds]
zpe has joined #ocaml
mcclurmc has quit [Quit: Leaving.]
Neros__ has joined #ocaml
cdidd has quit [Remote host closed the connection]
avsm has quit [Quit: Leaving.]
Drup has joined #ocaml
Neros_ has quit [Ping timeout: 245 seconds]
dsheets has quit [Ping timeout: 269 seconds]
Neros__ has quit [Read error: Connection reset by peer]
Neros has joined #ocaml
cdidd has joined #ocaml
zpe has quit [Ping timeout: 264 seconds]
Neros_ has joined #ocaml
osa1 has quit [Remote host closed the connection]
osa1 has joined #ocaml
ggole has quit []
Neros has quit [Ping timeout: 264 seconds]
Neros_ has quit [Read error: Connection reset by peer]
Neros has joined #ocaml
smondet has joined #ocaml
pango has quit [Ping timeout: 264 seconds]
Neros_ has joined #ocaml
rgrinberg has left #ocaml []
osa1 has quit [Ping timeout: 240 seconds]
osa1_ has joined #ocaml
zpe has joined #ocaml
osa1_ has quit [Client Quit]
mort___ has quit [Quit: Leaving.]
Neros has quit [Ping timeout: 264 seconds]
zpe has quit [Ping timeout: 264 seconds]
ollehar has joined #ocaml
zpe has joined #ocaml
osa1 has joined #ocaml
zpe has quit [Ping timeout: 246 seconds]
_andre has quit [Quit: leaving]
zRecursive has joined #ocaml
avsm has joined #ocaml
csakatoku has joined #ocaml
zpe has joined #ocaml
csakatoku has quit [Ping timeout: 240 seconds]
osa1 has quit [Remote host closed the connection]
Nahra has quit [Quit: leaving]
zpe has quit [Ping timeout: 264 seconds]
osa1 has joined #ocaml
thomasga has quit [Quit: Leaving.]
thomasga has joined #ocaml
thomasga has quit [Client Quit]
dsheets has joined #ocaml
tlockney has quit [Ping timeout: 260 seconds]
manud has joined #ocaml
tlockney has joined #ocaml
zpe has joined #ocaml
tlockney has quit [Excess Flood]
tlockney has joined #ocaml
Xom has joined #ocaml
zpe has quit [Read error: No route to host]
zpe has joined #ocaml
Neros_ is now known as Neros
beckerb has quit [Ping timeout: 245 seconds]
zpe has quit [Ping timeout: 240 seconds]
csakatoku has joined #ocaml
csakatoku has quit [Ping timeout: 264 seconds]
Snark has quit [Quit: leaving]
travisbrady has quit [Quit: travisbrady]
osa1 has quit [Remote host closed the connection]
osa1 has joined #ocaml
milosn_ has quit [Remote host closed the connection]
milosn has joined #ocaml
<technomancy> I've got a question about this codebase: http://p.hagelb.org/skaro.ml.html
<technomancy> it's a game loop that takes moves on stdin and prints out board state with printf
<technomancy> but nothing actually gets printed until the program exits
<technomancy> how do you force an explicit flush of stdout?
<technomancy> oh, I tried printf-ing ! instead of %!
<technomancy> there we go
<technomancy> I get a lot of non-exhaustive match warnings with that code... is it bad form to match against a list in your arguments like that? (x and y args on line 11, for instance)
zRecursive has left #ocaml []
<xenocons> technomancy: i think (personally) any warnings are bad, especially pattern exhaustiveness, so while some features can be really nice e.g. let [a;b;d] = [1;2;3], the cost on safety is too damn high
<xenocons> i would like a way to be able to disable that warning locally, but that probably has issues too
<xenocons> tbh, i am not sure *why* the compiler can at least try to work out exhaustiveness, most stuff is trivial
<technomancy> xenocons: I guess a record for x/y would be an easy way to avoid that?
<technomancy> is there a built-in point type, or should I make my own?
<xenocons> yeah, but that can look over the top right
<xenocons> good question, not sure in ocaml
<xenocons> maybe check out http://caml.inria.fr/resources/doc/guides/pointers.en.html ? (if thats what you mean by point types)
<flux> xenocons, what stuff is trivial? barring the cases where you can just rewrite it as a tuple match..
<technomancy> flux: oh, so tuples would be better for this due to their fixed length?
<xenocons> flux: if you only have two elements on the righthand side of an expression, compiler should be able to work out that the binding is exhaustive
<xenocons> i probably mis-understand the complexity of it though
<flux> xenocons, sure, but why would you write it that way?
<xenocons> flux: ive only ever used it for receiving argv
<flux> technomancy, for coordinates, certainly
<xenocons> which can be any size i guess
<flux> xenocons, umm so the compiler is warning exactly correctly :-)
<xenocons> so it would be impossible for the compiler to work it out i guess
<xenocons> flux: im still gona argue this
<xenocons> now, what if you could hint the compiler to max allowed length
<flux> well, there was this camlp4 syntax extension called pa_refutable.ml or something
<xenocons> let [a;b] = if x.Length <> 2 then fail else x
<xenocons> or some kinda attribute
<flux> let (a, b) = tuple2_of_list x in ..
<ggherdov> [OT] just in case anybody wants to compete in the ICFP programming contest next w/e, deadline for registration is 90 minutes from now. Look: http://research.microsoft.com/en-us/events/icfpcontest2013/
<flux> (of course, first write tupleX_of_list functions)
<flux> certainly better than adding very fragile analysis into a compiler
<xenocons> interesting refutable.ml
<xenocons> yeah true
<xenocons> maybe a way to disable the warning locally (but this just creates more ugliness)
<xenocons> and something about being able to disable pattern exhaustive warning feels...wrong
<flux> technomancy, it seems btw that you have a bug in the 'move' function?
<flux> technomancy, I assume the first field should be x and the second y..
<flux> a record with field names would probably have lesser of chance to mix it up :)
<technomancy> flux: yep! since my stdout wasn't flushing I didn't get a good feel for how the game was actually going =)
<flux> otherwise your code looks pretty clean
<technomancy> thanks! it's my first ocaml in two years =)
<xenocons> nice, i think there is a nice number of functions
<xenocons> pretty readable i think
<technomancy> xenocons: doesn't hurt that I already wrote this game 4 times in other languages =)
<flux> and small functions like 'allowed' and 'collision' are really the indicator of good functional code :)
<technomancy> flux: shame about not being able to put a ? on the end of the names, but I'll live
<kerneis> ggherdov: I don't understand the deadline stuff this year; it used to be opened until the last minute previous years, wasn't it?
<kerneis> anyway, I registered already
<xenocons> technomancy: yes it also helps that you wrote it scheme
<xenocons> which is always a good way to see a problem refined
<technomancy> the compiler actually doesn't like this much: List.init (width + 1) (Fn.compose (printf " %s ") (get_piece pieces row));
<xenocons> imo
<technomancy> saying it should have type unit... what's going on there?
<flux> technomancy, sprintf?
<xenocons> printf returns unit
<flux> woohoo, compiler caught a bug ;)
<technomancy> flux: no, I want it emitted to stdout
<flux> ah, ok. meh :)
<xenocons> hmm
<flux> well, I'm not familiar with those functions as I don't use core
<xenocons> maybe use sprintf first, then List.iter it to stdout
<flux> but doesn't it tell a more exact error?
<technomancy> flux: not really "Warning 10: this expression should have type unit."
<flux> (I can guess, though, their signatures and what they do)
<flux> ah, ok
<flux> so you probably discard the result
<technomancy> maybe List.init just isn't meant for side-effects?
<flux> that would be right, as it makes a list of unit values
Neros has quit [Read error: Connection reset by peer]
<flux> but if you want to, you can do: ignore (List.init.. )
<flux> or: let () = List.init ... in..
<technomancy> so List.iter would be better here except that I have to construct the range manually
<xenocons> let x = List.init (width + 1) (Fn.compose (sprintf " %s ") (get_piece pieces row)) in List.iter stdout x
Neros has joined #ocaml
<xenocons> also what is Fn.compose?
<flux> well, you could just use a good ol' for-loop :-)
<technomancy> xenocons: it's from core; just does what it says on the tin =)
<flux> or Core possibly has a function for that
<technomancy> simple composition
<xenocons> ah
<flux> I'm pretty certain it has a representation for ranges and those ranges can be iterated
<flux> or if not ranges then enumerations
<technomancy> flux: oh yeah; there's a List.range
<technomancy> but for might be better here because it is imperative
<technomancy> haven't gotten that far in the book yet =)
<flux> book?
<technomancy> the new oreilly one
<technomancy> seems quite good so far
<ggherdov> kerneis: yes it was. I have no idea why this new policy, I am pretty annoyed too
<technomancy> and I've noticed markedly fewer grammatical errors in the compiler messages vs when I tried ocaml a couple years ago =)
<technomancy> and opam is a very welcome improvement over "yeah uh go ahead and grab this library from apt-get or something" =)
<technomancy> FWIW the ocaml version clocks in at the same line count as scheme
<technomancy> I'm sure it could be golfed further though
* technomancy <3 option
<technomancy> is it kind of a sore topic that perl has effectively co-opted the camel as its mascot? it hardly seems fair.
<Qrntz> Perl's is a very specific camel
<Qrntz> OCaml's is more of a schematic camel
<Qrntz> that's how I see it
<flux> they are completely different. ocaml camel has two humps!
<Qrntz> and is only an outline
<flux> seems it was discussed 9 years ago on the mailing list
<Qrntz> nobody dares to look OCaml in the face
<flux> what's the logo on the o'reilly book, btw?
<bitbckt> a bactrian camel.
<bitbckt> Perl is a dromedary.
<technomancy> that works
<Qrntz> for what I see it's vastly different from the Perl one
<technomancy> "two humps good; one hump baaaaaad"
<technomancy> </animal-farm>
<bitbckt> :)
<bitbckt> double the hump, double the fun.
csakatoku has joined #ocaml
csakatoku has quit [Remote host closed the connection]
osa1 has quit [Remote host closed the connection]
osa1 has joined #ocaml