adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml MOOC http://1149.fr/ocaml-mooc | OCaml 4.02.3 announced http://ocaml.org/releases/4.02.html | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
tristero has quit [Quit: tristero]
damason has quit [Remote host closed the connection]
ncthom91 has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
madroach has quit [Ping timeout: 246 seconds]
madroach has joined #ocaml
mfp has quit [Quit: Leaving]
ontologiae_ has joined #ocaml
Algebr has quit [Remote host closed the connection]
damason has joined #ocaml
mangooes has joined #ocaml
ncthom91 has joined #ocaml
ncthom91 has quit [Client Quit]
mangooes has quit [Ping timeout: 260 seconds]
cody` has quit [Quit: Connection closed for inactivity]
systmkor has quit [Ping timeout: 246 seconds]
mangooes has joined #ocaml
mangooes has quit [Ping timeout: 260 seconds]
pierpa has quit [Ping timeout: 260 seconds]
mfp has joined #ocaml
supercircle4 has quit [Quit: Sleep]
rossberg has joined #ocaml
ontologiae_ has quit [Ping timeout: 246 seconds]
nicholasf has joined #ocaml
FreeBirdLjj has joined #ocaml
pw_ has joined #ocaml
<pw_> Hi, I am using utop in emacs. I found that "read_line ();;" does not work as expected in the utop REPL. It does not read standard input, the only thing I can do is to interrupt it by Ctrl-C. Is it possible to read standard input in the REPL? Am I missing anything?
badon has quit [Quit: Leaving]
manizzle has quit [Ping timeout: 260 seconds]
lobo has quit [Quit: sleep]
ncthom91 has joined #ocaml
psy_ has quit [Remote host closed the connection]
nicholasf has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
nicholasf has joined #ocaml
nojb has joined #ocaml
tristero has joined #ocaml
nicholasf has quit [Client Quit]
nicholasf has joined #ocaml
malc_ has joined #ocaml
badon has joined #ocaml
nicholasf has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
malc_ has quit [Ping timeout: 245 seconds]
malc_ has joined #ocaml
nicholasf has joined #ocaml
nicholasf has quit [Ping timeout: 260 seconds]
malc_ has quit [Ping timeout: 260 seconds]
malc_ has joined #ocaml
malc_ has quit [Ping timeout: 245 seconds]
malc_ has joined #ocaml
f[x] has quit [Ping timeout: 246 seconds]
ncthom91 has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
FreeBirdLjj has quit [Ping timeout: 260 seconds]
FreeBird_ has joined #ocaml
pw_ has quit [Remote host closed the connection]
antkong has quit [Quit: antkong]
nojb has quit [Ping timeout: 260 seconds]
BitPuffin|osx has quit [Ping timeout: 246 seconds]
mac10688 has quit [Ping timeout: 246 seconds]
NingaLeaf has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
badon has quit [Quit: Leaving]
badon has joined #ocaml
MercurialAlchemi has joined #ocaml
cyraxjoe has joined #ocaml
larhat1 has quit [Quit: Leaving.]
darkf has joined #ocaml
JacobEdelman has quit [Quit: Connection closed for inactivity]
cody` has joined #ocaml
zpe has joined #ocaml
zpe has quit [Remote host closed the connection]
aaronelkins has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 246 seconds]
badon has quit [Ping timeout: 260 seconds]
badon has joined #ocaml
MercurialAlchemi has joined #ocaml
Mercuria1Alchemi has joined #ocaml
Mercuria1Alchemi has quit [Ping timeout: 260 seconds]
aaronelkins has quit [Quit: aaronelkins]
AlexRussia has quit [Ping timeout: 250 seconds]
Guest414 has quit [Remote host closed the connection]
freehck has joined #ocaml
nojb has joined #ocaml
solrize has joined #ocaml
<solrize> is there a function like foldl1 in ocaml? i don't see it in the list module. basically List.fold_left except uses the hd of the list as the initial value.
ggole has joined #ocaml
<artart78> solrize: I don't think so, but it's pretty trivial to implement with fold_left (also, I think it's often known as 'reduce')
<solrize> artart78, thanks. yes it's called reduce in lisp
<solrize> but the init value in lisp is an optional arg to reduce
<solrize> i just thought i might have missed something in the docs. i'm just starting trying out ocaml (have been using lisp and haskell for a while)
dsheets has joined #ocaml
<flux> I think I relatively rarely use the same type as the folding values as is the type of the element in the list
freehck` has joined #ocaml
freehck has quit [Ping timeout: 245 seconds]
<flux> at least I found a use from my code base: let max_width = adjusted_widths |> List.map snd |> List.map sum |> reduce max
<flux> so looking for extremes is one such case
<freehck`> solrize: let reduce func list = List.fold_left func (List.hd list) (List.tl list);;
freehck` is now known as freehck
<ggole> Lisp's reduce is interesting: in the case of an empty sequence it calls the function with 0 arguments
<solrize> flux, freehck, thanks. i think of reduce func1 (map func2 list) asidiomatic although i guess it makes an intermediate list in lisp and ocaml
<solrize> *as idiomatic
<solrize> ggole, yeah, that behavior of lisp always seemed ugly to me
<ggole> Many lisp functions like + and * return an identity value, so this magically does the right thing (sometimes)
<solrize> right
<solrize> not sure what scheme does
<ggole> Same thing
<freehck> solrize: yes, you should also note in that realization of reduce the case of empty list as ggole mentioned.
<solrize> well i'd expect the ocaml version to throw an error
<freehck> solrize: List.hd will throw an error.
<solrize> right
<freehck> It could be not the error you want to see.
<solrize> hmm well it's a program bug either way
Mercuria1Alchemi has joined #ocaml
<ggole> An alternative is let reduce f = function [] -> None | x::xs -> Some (List.fold_left f x xs)
<ggole> Depending on how willing you are to wrangle options everywhere
<freehck> ggole: I'd raise Invalid_argument in the case of empty list.
<ggole> Is that really much better than List.hd doing it?
ely-se has joined #ocaml
<freehck> But what do we need options here for?
<ggole> To remind the programmer of the potential failure case
<freehck> Oh, nevermind.
<ggole> If you want to throw an exception, OK, although I would prefer that the name of the function indicates that (eg, reduce_exn)
agumonkey has joined #ocaml
<flux> the None case is then simple to convert to an exception or a default value with proper additional functions, ie |> Option.default 42 or |> Option.get
<freehck> flux: Sorry, where's the operator ( |> ) described?
<freehck> Is it batteries?
<solrize> that's function composition ?
<flux> it's a standard operator nowdays isn't it?
<solrize> doesn't seem so
<flux> solrize, how do you figure?
<flux> I use: ocaml -init /dev/null
<flux> and (|>) works
agumonkey_ has joined #ocaml
<MasseR> solrize: which ocaml version?
<flux> but I wonder if it's documented in the ocaml manual
<flux> I'm running 4.02.0 btw
<freehck> flux: don't this run uses .ocamlinit?
<freehck> *doesn't .. use
<solrize> # (|>);;
<solrize> Error: Unbound value |>
agumonkey has quit [Read error: Connection reset by peer]
agumonkey_ is now known as agumonkey
<solrize> that's in 4.00.1
<MasseR> solrize: ocaml version?
<MasseR> Oh
<solrize> hmm
<flux> it's probably introduced in-between then
<freehck> Ah, maybe it's because I'm using 4.01.0
<solrize> yeah could be, i know there's new stuff in recent versions
<freehck> flux: but the question is opened: where's the description of this operator? )
<solrize> oh lol, tried other machine and it's running 3.12
<flux> indeed I cannot find it from the manual. a bug I suppose, or an error in my part :)
<flux> let (|>) x f = f x
<artart78> it seems to exist in ocaml 4.02.3
<artart78> at least it exists for me in toplevel without anything loaded
<freehck> "In OCaml 4.00.0, we optimized these operators by providing native operators"
<freehck> well, solrize, is it really works on ocaml 3.12? )))
Simn has joined #ocaml
<solrize> didn't try :)
Haudegen has quit [Ping timeout: 246 seconds]
<freehck> aah, other machine running 3.12, not mention of this code working on that machine... )
<freehck> gotcha
<freehck> cool: [1;2;3] |> List.map (fun x -> x + 2) |> List.iter (Printf.printf "%d\n%!");;
dsheets has quit [Ping timeout: 260 seconds]
<solrize> that's nice syntax
<solrize> pipeline-like
<flux> now that ocaml is going to have the flambda optimizer, does it obsolete the special compiler magic for |> ?-)
<def`> the special magic was relevant for bytecode compiler
<def`> flambda targets native code compiler which could (very likely, although I didn't check this case specifically) already do this optimisation
sgnb has joined #ocaml
Haudegen has joined #ocaml
<flux> well, optimizing byte code by specializing |> is like carrying water to a well with a bucket?-)
<ggole> Hmm. match Obj.magic 0 with `Foo -> true => true, but match Obj.magic 0 with `Foo -> true | _ -> false => false O_o
<ggole> Of course Obj.magic doesn't give you any guarantees, only suffering and death. Still, I was surprised.
<ggole> My guess is this is an type-driven exhaustiveness optimisation that results in the value of the scrutinee not being inspected at all in the first case.
<flux> I guess in the first case it unifies 'a with [ `Foo ] and whatyousaid
<def`> ggole: yes, the pattern matching compiler is optimizing
<def`> (you can always -dlambda to verify)
<flux> ggole, you should now make use of this new-found knowledge to the benefit of your ocaml programs! Obj.magic matching all the way!
agumonkey has quit [Ping timeout: 260 seconds]
madroach has quit [Read error: Connection reset by peer]
madroach has joined #ocaml
dsheets has joined #ocaml
pierpa has joined #ocaml
Sim_n has joined #ocaml
Simn has quit [Ping timeout: 264 seconds]
ggole has quit [Ping timeout: 246 seconds]
supercircle4 has joined #ocaml
Bahman has joined #ocaml
jonludlam has joined #ocaml
zpe has joined #ocaml
Sim_n is now known as Simn
dr_toboggan has quit [Ping timeout: 245 seconds]
dr_toboggan has joined #ocaml
sepp2k has joined #ocaml
<solrize> is ocamlopt a complicated compiler?
<solrize> like is it managable size, could i read it and make sense of it, which i couldn't do with ghc or gcc?
<malc_> solrize: it's much simpler than either
<solrize> nice
<malc_> solrize: the code generation part that is
<solrize> yeah
<solrize> i heard it uses a fairly fancy type inference algorithm but in principle could use (much slower) algorithm W
<solrize> i have a book about standard ml, can i just read it and then deal with the syntax differences with ocaml?
<solrize> ml for the working programmer
<solrize> harper's book also looks good
<edwin> about the type checker there is some info here: http://okmij.org/ftp/ML/generalization.html "There is more to Hindley-Milner type inference than the Algorithm W [...] This page is to explain and popularize Rémy's algorithm, and to decipher a part of the OCaml type checker."
<edwin> better learn ocaml from an ocaml book, unless of course you already know standard ML
ggVGc has joined #ocaml
ggVGc has quit [Changing host]
ggVGc has joined #ocaml
<pierpa> Modern Compilers in ML, no?
sepp2k has quit [Quit: Leaving.]
<solrize> thanks
<solrize> ok it's real late here, i gotta goto sleep.... gnite
<solrize> thanks again
ely-se has quit [Quit: leaving]
ely-se has joined #ocaml
mort___ has quit [Quit: Leaving.]
david______ has joined #ocaml
david______ has quit [Client Quit]
NingaLeaf has joined #ocaml
Bahman has quit [Quit: Ave atque vale]
NingaLeaf has quit [Ping timeout: 245 seconds]
dsheets has quit [Ping timeout: 246 seconds]
Bahman has joined #ocaml
Guest79936 is now known as infinity0
infinity0 has quit [Changing host]
infinity0 has joined #ocaml
mort___ has joined #ocaml
moei has quit [Quit: Leaving...]
moei has joined #ocaml
DanielRichman has quit [Quit: leaving]
DanielRichman has joined #ocaml
cody` has quit [Quit: Connection closed for inactivity]
l1x has quit []
l1x has joined #ocaml
strmpnk has quit []
strmpnk has joined #ocaml
malc_ has quit [Quit: leaving]
DanielRichman has quit [Quit: leaving]
yomimono has joined #ocaml
dsheets has joined #ocaml
ely-se has quit [Quit: leaving]
Sim_n has joined #ocaml
DanielRichman has joined #ocaml
Simn has quit [Ping timeout: 264 seconds]
FreeBirdLjj has joined #ocaml
ely-se has joined #ocaml
nojb has quit [Quit: nojb]
nojb has joined #ocaml
FreeBird_ has quit [Ping timeout: 260 seconds]
FreeBirdLjj has quit [Ping timeout: 260 seconds]
supercircle4 has quit [Quit: Sleep]
raphaelsss has joined #ocaml
raphaelss has quit [Ping timeout: 246 seconds]
JacobEdelman has joined #ocaml
ely-se has quit [Quit: leaving]
clockish has joined #ocaml
dsheets has quit [Ping timeout: 246 seconds]
Haudegen has quit [Ping timeout: 246 seconds]
zpe has quit [Remote host closed the connection]
Sim_n is now known as Simn
ggole has joined #ocaml
Haudegen has joined #ocaml
Lightsephi has joined #ocaml
<companion_cube> is there a very fast, monotonic time counter somewhere? for profiling purpose
<def`> core
<companion_cube> :(
Sim_n has joined #ocaml
<Drup> there is one done by bunzli too, for mirage
raphaelssss has joined #ocaml
<Enjolras> any binding to posix clock_gettime using CLOK_MONOTONIC_RAW ?
<Enjolras> it's really fast on linux. It's basically the cost of a C call
<Enjolras> (there might be one in extunix, not certain)
<flux> enjolras, probably
dsheets has joined #ocaml
<flux> there are maybe three opam libraries matching for clock, probably one or all of them support it ;)
Simn has quit [Ping timeout: 264 seconds]
<flux> but that's a non-standard clock, is it?
<companion_cube> ok, oclock looks nice for instance
<companion_cube> or mtime
<Enjolras> (_RAW is a linux extension, portable is CLOCK_MONOTONIC, but linux didn't get it right so they had to add the _RAW version)
raphaelsss has quit [Ping timeout: 260 seconds]
BitPuffin has joined #ocaml
simn__ has joined #ocaml
<companion_cube> ok, oclock it is
<companion_cube> thanks
Sim_n has quit [Ping timeout: 264 seconds]
<edwin> Core's documentation shows a comparison between different methods of getting the time:
<edwin> Time.now 37.93ns (gettimeofday)
<edwin> Time_ns.now 28.18ns (clock_gettime)
<edwin> TSC.now 7.14ns (rdtsc)
<flux> I wouldn't say gettimeofday is super slow then, if it takes only 5 times as fast as a single (special) instruction
<flux> ..but for many applications monotonic time itself is of course useful
<edwin> it only has micro-second precision though, clock_gettime gives you ns, depends what you need
<Enjolras> the dumbest part of ocaml's gettieofday is that it has to allocate a float
<companion_cube> that's cool and all, but I'm not depending on Core
<Enjolras> the main drawback of TSC is that it's monotonic but the intervals can change a lot
d0nn1e has quit [Ping timeout: 260 seconds]
zpe has joined #ocaml
<Enjolras> that is, it's monotonic but not really stable and definitly not precise
<edwin> oclock will probably be like Time_ns.now in terms of performance
<Enjolras> there is also the issue of cross cpu synchronisation
<companion_cube> it's a monocore program
<Enjolras> although it does appear with clock_gettime too but at least the kernel tries to compensate
<edwin> helps if you have constant_tsc in /proc/cpuinfo, disable cpufreq scaling and cpuidle
<Enjolras> companion_cube: but is it a mono cpu machine ?
<edwin> or you can just use taskset to restrict program to one core
d0nn1e has joined #ocaml
<edwin> (or at least with cpufreq/cpuidle/core-performance-boosting on I can't get reliable measurements on my machine, so I always turn them off before benchmarking)
ely-se has joined #ocaml
<Enjolras> yeah. TSC is just the cpu clock cycle
profan has joined #ocaml
simn__ is now known as Simn
FreeBirdLjj has joined #ocaml
<def`> you can enable constant rate tsc on modern intels
cody` has joined #ocaml
Lightsephi has quit [Quit: Page closed]
<def`> cat /proc/cpuinfo | grep constant_tsc
<def`> mine is reliable, wouhou
Lightsephi has joined #ocaml
<ggole> Reliable for what? If you run a benchmark and the CPU switches frequency you will have an uneven rate of execution per counter tick.
<ggole> The kernel can also migrate your process to a different CPU, which also requires handling
<ggole> (Unless you've pinned the process as suggested above.)
ontologiae_ has joined #ocaml
raphaelssss has quit [Ping timeout: 260 seconds]
raphaelssss has joined #ocaml
<def`> ggole: on a given core, it is a monotonic clock
<def`> of course the amount of work done between two ticks depend on frequency, but at least, it measures something in sync with our time
dexterph has quit [Ping timeout: 264 seconds]
<def`> monotonic and constant speed* clock
tane has joined #ocaml
dexterph has joined #ocaml
<Enjolras> def`: tsc is already monotonic
<Enjolras> the problem is stable, not monotonic
<Enjolras> since tsc is just the cycle number it's always increasing, unless the cpu is reset or something strange like that
<Enjolras> ah sorry i skiped your errata :)
<flux> is constant_tsc constant also between cores?
<ggole> No, each core has its own counter
<flux> well, you can always pin your process to a core for benchmarking
<Enjolras> flux: this is almost impossible to achieve
AlexRussia has joined #ocaml
Haudegen has quit [Remote host closed the connection]
ncthom91 has joined #ocaml
clockish has quit [Ping timeout: 245 seconds]
clockish has joined #ocaml
Kakadu has joined #ocaml
Bahman has quit [Quit: Ave atque vale]
Bahman has joined #ocaml
ncthom91 has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
<flux> enjolras, really?
<flux> enjolras, oh you meant cross-core monotonic tsc?
BitPuffin is now known as OUT
FreeBirdLjj has quit [Ping timeout: 260 seconds]
NingaLeaf has joined #ocaml
OUT is now known as BitPuffin
<companion_cube> well, getclock should be enough for my purpose
<companion_cube> it's fun starting a debate about stuff I don't really grasp
lobo has joined #ocaml
ir2ivps4 has quit [K-Lined]
orbifx has joined #ocaml
orbifx has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
ely-se has quit [Quit: leaving]
ely-se has joined #ocaml
pw_ has joined #ocaml
<Drup> companion_cube: insert xkcd about wikipedia
<edwin> now that you have a clock you only need a benchmark lib, there are at least 3 of those on opam again :)
<companion_cube> it's not for benchmarking but for profiling inside a big program :)
<companion_cube> I already use `benchmarking` for small benchs
<edwin> ah
<hannes> is there a generic last-recently-used map/table in OCaml? I'd like to have a cache which does not exceed X entries (and don't want to reinvent it if it's already available)
<edwin> hmm there is a clock inside mirage-profile too
<flux> hannes, no. there could be one in some of the libraries that come with data structures. but probably not even there, that's a bit specialized.
ely-se has quit [Quit: leaving]
<edwin> I have one in my code that I wanted to release as a separate lib
<hannes> companion_cube: thx. is this a library in itself, or only available as part of containers?
<companion_cube> it might be a bit heavyweight, you should benchmark it
<companion_cube> it's part of containers
<companion_cube> but the module is totally independent
<edwin> mine is here but not a separate lib http://gitweb.skylable.com/gitweb/?p=libres3.git;a=blob;f=libres3/src/anycache/lRUCache.mli;h=029d59b0779d3534754aefec783211431881b0d3;hb=HEAD http://gitweb.skylable.com/gitweb/?p=libres3.git;a=blob;f=libres3/src/anycache/lRUCacheMonad.mli;h=7e7a5f2253ccb4c95b127f4504e9dc9dc3a004c1;hb=HEAD
<companion_cube> so it should not pull lots of dependencies in the progrma
<companion_cube> (or you can just copy/paste it and start from there, containers is also designed for that)
ncthom91 has joined #ocaml
slash^ has joined #ocaml
<Drup> hannes: told you he would have an idea :]
<hannes> edwin: nice! I actually prefer a Map here...
<hannes> edwin: if this would be a separate opam package, that'd be wonderful
ely-se has joined #ocaml
<edwin> I think I should rather contribute my code to containers, it already has a couple of cache types, mine is LRU/2Q
ontologiae_ has quit [Ping timeout: 245 seconds]
<hannes> ..but containers is imho pretty big... wouldn't it be useful to have a dedicated lru package?
OnkV has joined #ocaml
<companion_cube> edwin: your code looks more advanced than mine ^^
<companion_cube> hannes: erf, I don't consider containers to be big, at least not at linking, but I understand
<companion_cube> the problem is I don't want to maintain 20 packages -_-
<def`> hannes: I wonder what is the appropriate size for a package...
<Drup> I prefer companion_cube's API
<def`> and there is the distinction between findlib packages and opam package
<hannes> def`: imho as small as it can be to be useful on its own
<edwin> companion_cube: I could maybe extend val lru to val lru2q that'd provide my caching algo and otherwise have the same API as yours
<def`> then how do you deal with the fact that you have to maintain 20 packages ?
<hannes> c'est la vie
<def`> :D
<def`> maybe more automation can be done on this side
<companion_cube> but for instance, a "ListUtils" module is not useful enough on its own, you also need a few utils for option, string...
<companion_cube> hannes: I'd have to split into distinct repositories, I guess? then it means duplicating the test, benchmark, etc. infrastructure
<companion_cube> so painful :(
<hannes> companion_cube: why would a ListUtils not be useful in its own
<companion_cube> because it's less useful than a lib with utils for the very very common types
Armael has joined #ocaml
<def`> companion_cube: you can have a single directory but multiple opam files
<def`> oh wait... github generates tarball on a tag basis.
<companion_cube> def`: yeah, it's a possibility. But then the complexity is on the build system (only build the interesting part, etc.)
<companion_cube> oh, right
<def`> too bad sorry for you :)
<companion_cube> I'm happy with containers, thanks, it's not heavy if you only use a few modules :p
<Drup> def`: how is the tarball an issue ?
<def`> or you pull the whole repo each time but compile only a subpart
<Drup> def`: that's what some mirage lib do
<def`> Drup: opam publish <tarball>
<Drup> yeah, that's not an issue
<Drup> opam caches the tarballs anyway
<def`> yes
<edwin> does opam support single source - multiple output packages like debian/rpm?
<Drup> edwin: not exactly
<hannes> hmm, I didn't intend to end up in this discussion and will drop out...
<Drup> hannes: just copy cccache.ml in your app and be done with it
<hannes> Drup: this might be another (bad) solution since I'll need to keep track of updates... I'll just not provide any such thing for now
<companion_cube> so, on my machine, a helloworld.native is 457kB ; using CCCache it weights 557kB
<companion_cube> pretty ok \o/
psy_ has joined #ocaml
<pw_> Hi, how can I provide input to `read_line ();;` inside utop in Emacs?
<Drup> pw_: use it out of emacs
<pw_> Drup: thanks, ehh, does this mean no way to do it in emacs?
<Drup> I don't really know
<pw_> I thought this is a very common scenario, anyway, thanks!
<Drup> (I barely use the toplevel inside emacs ..)
zpe has quit [Remote host closed the connection]
supercircle4 has joined #ocaml
<ggole> pw_: I believe you need to use some comint function
Armael has left #ocaml ["WeeChat 1.3"]
<pw_> Drup: I'm just curious what's your typical workflow then? modify in an editor, switch to terminal, reload, something like this?
<ggole> I think it's comint-send-input
<flux> I use regular toplevel in emacs
<flux> but I also use regular toplevel otherwise.. :)
<flux> except when I remember to use utop
<ggole> Yeah, comint-send-input
<ggole> (This is also with the standard toplevel, I don't really use utop.)
<pw_> that's cool, let me try it!
<Drup> I use utop, just never in emacs
<pw_> hmmm, strange, I got this error: Text is read-only: "You cannot edit the buffer while ocaml is evaluating a phrase", any ideas?
<ggole> When you M-x comint-send-input?
<pw_> after I input: utop[15]> read_line ();;
<ggole> Oh, hmm
<pw_> then I invoked M-x comint-send-input
<pw_> seems the only thing I can do is Ctrl-C, which interrupts it: Interrupted.
<ggole> That's not the case in my emacs, so we have some different code running.
<ggole> Does utop have it's own emacs mode?
<Drup> yes
<pw_> in my case, the buffer has the major-mode of utop
<ggole> Ah, utop.el
<pw_> yes, utop.el
<pw_> use M-x utop, to get such a ocaml REPL.
ely-se has quit [Quit: leaving]
<ggole> Looking at the source, it has logic dedicated to preventing edits... unless there's a variable to control that, you may be out of luck.
<pw_> did you mean the Elisp code? Could you give me a pointer?
<ggole> utop-inhibit-check, perhaps
<pw_> is this one? (defconst utop-non-editable-properties ... )
ely-se has joined #ocaml
k1000_ has quit [Quit: .]
k1000 has joined #ocaml
cartwright has quit [Quit: WeeChat 1.3]
<Enjolras> flux: sorry i read "cross cpu". cross core is still ok
yomimono has quit [Ping timeout: 246 seconds]
ely-se has quit [Quit: leaving]
dsheets has quit [Remote host closed the connection]
NingaLeaf has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
NingaLeaf has joined #ocaml
zpe has joined #ocaml
<madroach> Hi, I think I've encountered a bug when using {expr with field = x} notation. The relevant code section is here: http://pastebin.com/S0eL1nAT The whole project here: http://gmerlin.de/ocaml-zlib.tgz
<madroach> Is this a real bug or am I overlooking something?
struk|desk has joined #ocaml
<j0sh> is there a way to simulate dependent types without doing something crazy like chained constructors (church encoding?)... applicative functors sorta do the trick, but they're incompatible with first-class modules, as far as i can tell (unpacking a value into a module then applying that module to a functor results in a fresh type, even if the same value is unpacked multiple times)
<ggole> madroach: do you get the same thing with full explicit record construction?
<madroach> ggole: I'll try.
<madroach> ggole: no, with explicit record construction the bug doesn't trigger.
zpe has quit [Remote host closed the connection]
<ggole> O_o
<ggole> Certainly sounds like a bug.
Anarchos has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 260 seconds]
ontologiae_ has joined #ocaml
tane has quit [Quit: Verlassend]
native_killer has joined #ocaml
jonludlam has quit [Ping timeout: 260 seconds]
sz0 has joined #ocaml
jwatzman|work has joined #ocaml
nojb has quit [Ping timeout: 245 seconds]
nojb has joined #ocaml
^elyse^ has joined #ocaml
Kakadu has quit [Quit: Page closed]
tane has joined #ocaml
Anarchos has quit [Ping timeout: 246 seconds]
lostman has joined #ocaml
mort___ has quit [Ping timeout: 260 seconds]
jeroud has quit [Ping timeout: 264 seconds]
octachron has joined #ocaml
jeroud has joined #ocaml
OnkV has quit [Ping timeout: 246 seconds]
systmkor has joined #ocaml
Anarchos has joined #ocaml
Algebr has joined #ocaml
Kakadu has joined #ocaml
f[x] has joined #ocaml
Haudegen has joined #ocaml
supercircle4 has quit [Quit: Sleep]
darkf has quit [Quit: Leaving]
mort___ has joined #ocaml
agarwal1975 has joined #ocaml
Anarchos has quit [Remote host closed the connection]
Anarchos has joined #ocaml
agarwal1975 has quit [Client Quit]
BitPuffin has quit [Ping timeout: 246 seconds]
smerdyakow has joined #ocaml
nojb has quit [Ping timeout: 245 seconds]
ontologiae_ has quit [Ping timeout: 245 seconds]
mort___ has quit [Quit: Leaving.]
slash^ has quit [Read error: Connection reset by peer]
smerdyakow has quit [Ping timeout: 246 seconds]
mort___ has joined #ocaml
caisah has joined #ocaml
Bahman has quit [Quit: Ave atque vale]
ollehar has joined #ocaml
sbrouf has joined #ocaml
<sbrouf> hello
<sbrouf> I am getting lost in the ocaml compilation process
<sbrouf> is there a good ressource explaining how to set up a project, and compile with external libraries (batteries), as well as linking local cma ?
<sbrouf> or real example of a project I could take inspiration from ?
<sbrouf> so oasis is the way to go ?
<sbrouf> thanks mr Drup
<Drup> It's simpler
<sbrouf> ok
mort___ has quit [Quit: Leaving.]
mort___ has joined #ocaml
<Maelan> i use make :p
Snark has joined #ocaml
ggole has quit []
mort___ has quit [Quit: Leaving.]
yomimono has joined #ocaml
native_killer has quit [Quit: Leaving]
meiji11 has joined #ocaml
<flux> OCamlMakefile is nice, haven't used it for a while, though
<adrien> agreed: make alone is a bad thing but with ocamlmakefile it's efficient
<adrien> (make alone means no proper ocamlfind support)
<flux> also proper dealing of dependencies with make is quite annoying
<flux> as in: .cmo depends on .ml. but if there is .cmi (which depends on .mli), then it depends on it as well
<flux> or did ocamldep handle all that?
<flux> and then the .cmx dependencies
rwmjones is now known as rwmjones|holiday
<adrien> :)
<flux> I forgot to mention .cmi can also depend on .ml if there is no .mli
smerdyakow has joined #ocaml
<flux> and both .cmo and .cmi may be generated at the same time, or separately depending on if there is .mli or not
<flux> or is this wrong infact..
<flux> I don't actually recall ocamlc -c producing two files, but how did the inter-module interface system then work :)
<flux> well, I must have been just inattentive because it indeed does create both
<sbrouf> ok so now I know i don't want to have to mess with this myself !
<adrien> :)
<Maelan> flux, i spent days setting up a makefile that handles all this
<Maelan> and now i copy-paste it and change the 2 first lines :p
iosys has joined #ocaml
<Maelan> actually i did not finished it if i remember correctly, i may still have incorrect dependencies for .cmx (i did the same than for .cmo, then i heard that it was wrong because you could’nt separate modules because of inlining needs)
<flux> maelan, OCamlMakefile ;)
<flux> it's designed to be include'd from your Makefile, so you don't need to modify it
<Drup> Maelan: why did you even tried ?
<flux> but, of course, it's always nicer to have your own!
<Drup> genuine question, I don't understand
<flux> well, I guess make was a very familiar tool to Maelan, how else could he have done it ;)
<Drup> flux: and ? what's the point ?
<adrien> most people tend to start with make
<adrien> foo: a.ml b.ml
<Maelan> and recently i used c stubs for the first time and had to patch my makefile dirtyly :p
<adrien> \tocamlopt -o foo a.ml b.ml
<adrien> Maelan: well, look at ocamlmakefile: it handles that well :)
<Drup> adrien: but ocamlbuild is already simpler and better than that.
<flux> drup, and one is more likely choose to use a familiar tool rather than an unfamiliar
<Maelan> yes, i heard about ocamlmakefile just after
<Drup> flux: well, you are still reinventing something that exists, only it's going to suck more
<adrien> Drup: people use what they already know :P
<adrien> (trolldi! \o/)
<flux> and then you choose to use ocamlbuild. and you realize you want to pass in some linker flags. and then the problems start, "what is this myocamlbuild.ml?" :P
<adrien> -lflags :D
<adrien> -lflags -cclib,-lrt
<Drup> flux: what adrien said, if you want to troll, pick one that actually doesn't work :D
<flux> and then you need a driver script and get a horrible feeling of inelegancy
<adrien> I actually have the following in some code:
<adrien> $(if $(WITH_ICON),-lflags $(WITH_ICON:=.o)) \
<adrien> -lflags yypkg/win.o \
<Drup> flux: and how much does that happen to beginners ? at least the basic ocaml build rules are correct
iosys has quit [Ping timeout: 245 seconds]
<flux> I use ocamlbuild, but I will most certainly copy paste my old myocamlbuild as a base for a new one when I need to do that
<flux> with make I can just write it off my head
<flux> well, maybe it's just because I've still use make more, but ocamlbuild is just a more complicated tool to use.
<Drup> flux: and your makefile is going to be correct ?
<Drup> (I doubt it)
<flux> not for ocaml, of course
<flux> with C it's pretty simple to get right
<Drup> but we are not talking about C
systmkor has quit [Ping timeout: 246 seconds]
<Maelan> Drup, because i knew make, because make is kind of universally available, because i wanted to understand better the OCaml compilation process with all those files dangling, because i felt to lazy to learn to use a new tool, because i did not know which one to choose since it appeared to exist several (ocamlbuild, oasis, omake…)
<Maelan> right, the “lazy” part was not that relevant after all
<Maelan> incidentally, i had bad feedbacks about ocamlbuild
iosys has joined #ocaml
<Drup> I like hating on ocamlbuild as much as the other person, but reinventing a custom makefile is just asking for pain :/
<flux> no pain, no gain!
<flux> and I imagine in this case the gain was knowledge :)
<edwin> now that you know of the existence of ocaml-makefile you could try it on some of your old custom makefile based projects and see if the result is any simpler/better
<flux> I don't think it's bad to learn the reasons why the tools we use now are better than what was before.
<Maelan> (and all those weird files in projects using oasis/ocamlbuild/whatever-strange-tool are disturbing me, sound like a mess ^^)
NingaLeaf has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<Maelan> i promise i’ll learn a proper tool some day
tane has quit [Ping timeout: 260 seconds]
tane has joined #ocaml
^elyse^ has quit [Quit: Leaving]
^elyse^ has joined #ocaml
systmkor has joined #ocaml
freehck has quit [Remote host closed the connection]
f[x] has quit [Ping timeout: 260 seconds]
ollehar has quit [Read error: Connection reset by peer]
ollehar1 has joined #ocaml
yaewa has joined #ocaml
ollehar1 is now known as ollehar
moei has quit [Ping timeout: 260 seconds]
BitPuffin|osx has joined #ocaml
octachron has quit [Quit: Leaving]
smerdyakow has quit [Ping timeout: 260 seconds]
smerdyakow has joined #ocaml
ollehar has quit [Ping timeout: 264 seconds]
f[x] has joined #ocaml
ollehar has joined #ocaml
ncthom91 has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
<Algebr> Maelan sbrouf: I wrote a blog post that might help getting you up to speed on building ocaml stuff http://hyegar.com/blog/2015/10/19/so-you're-learning-ocaml/
yomimono has quit [Quit: Leaving]
ncthom91 has joined #ocaml
<sbrouf> Algebr, one thing I don't get is, does opam install the ocaml compiler (when doing switch 4.02.3) , or does it need to be installed separately ?
<Algebr> it installs it for you and keeps like namespace of packages that you want to keep associated with just that switch
ncthom91 has quit [Client Quit]
<Algebr> so I have multiple switches, one for packages that I want only for the compiler for my js_of_ocaml coding and another for general purpose coding, etc.
<sbrouf> so I can fully remove the package from my distro repository ?
<Algebr> something like libfoo-ocaml?
<sbrouf> i mean ocaml
<Algebr> I usually only use opam for all my ocaml stuff and avoid the system's (brew/apt-get) package manager
<Algebr> for ocaml stuff
<sbrouf> ok thank you ! and nice blog post, i will be usefull to me !
<Algebr> yay
Mercuria1Alchemi has quit [Ping timeout: 260 seconds]
<Maelan> thanks Algebr !
jeffmo has quit [Quit: jeffmo]
<fds> Algebr: Yes, that blog post was interesting. I still get quite confused with OCaml 'infrastructure stuff' like oasis.
<Algebr> its painful but honestly just takes about 5 minutes of effort to get a new project off the ground. I made sure that you can copy paste stuff and hit the ground mostly running
<Algebr> from that blog post
<Maelan> Algebr, when building an executable, does oasis infer module dependencies like for libraries?
<Maelan> because i do not see this in your template _oasis
<sbrouf> you can add a line like BuildDepends: batteries
<Algebr> BuildDepends: is for packages that you need, but for the modules that your executable needs then it figures it out, just need to provide that MainIs field
<sbrouf> oh ok
<Algebr> yes, this is much nicer than makefile style ml_src := foo.ml bar.ml compiled_code := foo.cmo bar.cmo etc.
<Maelan> oh, i want this Algebr :p
<Algebr> I also thought that becuase I wanted to learn the lower level details of compiling ocaml.....but once the projects get bigger then teh compiling becomes a painpoint with make
smerdyakow has quit [Ping timeout: 246 seconds]
<Maelan> i thought that the OCaml world was quite hostile to automatically computing module dependencies, because of side effects in loaded modules
<Maelan> at least this is the reason i heard to justify why this was not possible with ocamlbuild
<Drup> Maelan: on the contrary, it's quite easy, since everything is clearly stated inside the file
<Algebr> yes
<Maelan> so i thought it was the same for oasis
<Drup> Maelan: huh, it's precisely one of ocamlbuild strong point
<Drup> you never need to give the ordering
<Drup> Algebr: if you have improvements to the ocaml.org tutorial on oasis, please contribute them :)
<Maelan> Drup, i mean, inferring dependencies is easy, but because modules can do things on their own when they are loaded, their order should be left to the programmer
<Drup> if you have side effects dependency that do not appear in link dependency, well you deserve everything you are getting (and it's trivial to add a link dependency)
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
<Algebr> Drup: it helped me but I really just wanted a one stop shop blog post for OCaml jargon, dev step up, getting things to work post.
<Algebr> I have like 4 more blog posts to write but there's never enough time in day....
<Maelan> ok Drup, that is good news :-)
Denommus has quit [Quit: going home]
yaewa has quit [Quit: Leaving...]
moei has joined #ocaml
supercircle4 has joined #ocaml
Kakadu has quit [Remote host closed the connection]
sbrouf has quit [Ping timeout: 260 seconds]
sbrouf has joined #ocaml
<fds> Man, I set up Merlin in Emacs yesterday and it's great.
sbrouf has quit [Ping timeout: 260 seconds]
larhat1 has joined #ocaml
Kakadu has joined #ocaml
smerdyakow has joined #ocaml
smerdyakow has quit [Ping timeout: 260 seconds]
Kakadu has quit [Remote host closed the connection]
badon has quit [Ping timeout: 245 seconds]
caisah has quit [Remote host closed the connection]
<Algebr> its pretty dope
tane has quit [Quit: Verlassend]