adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | Upcoming OCaml MOOC: https://huit.re/ocamlmooc | OCaml 4.03.0 release notes: http://ocaml.org/releases/4.03.html | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
wu_ng has quit [Ping timeout: 244 seconds]
wu_ng has joined #ocaml
nicholasf has joined #ocaml
al-damiri has quit [Quit: Connection closed for inactivity]
crass has joined #ocaml
<bruce_r> Lwt question: I have a list, and I want for each element x in this list call f x, sleep 3 seconds, and then keep going on the rest of the list.
<bruce_r> I started with this:
<bruce_r> List.map (fun x -> let () = f x in Lwt_unix.sleep 3.) [1;2;3;4;5;6;7;8;9;10]
<bruce_r> but it obviously doesn't work
<bruce_r> How do I make the next elements wait on the previous ones?
<bruce_r> Hmm, maybe a List.fold together with Lwt.map
al-damiri has joined #ocaml
pseudo-sue has quit [Ping timeout: 276 seconds]
<bruce_r> OK that worked, thanks guys :)
<bruce_r> It feels like there should be an easier way to do this:
<bruce_r> List.fold_left (fun y x -> Lwt.bind y (fun () -> ux x; Lwt_unix.sleep 3.)) (Lwt.return ()) [1;2;3;4;5;6;7;8;9;10]
Heasummn has joined #ocaml
<mfp> bruce_r: Lwt_list.iter_s (fun x -> f x; Lwt_unix.sleep 3) l
rgrinberg has quit [Ping timeout: 265 seconds]
pyon has quit [Quit: brb]
pyon has joined #ocaml
pseudo-sue has joined #ocaml
fraggle_ has quit [Ping timeout: 248 seconds]
fraggle_ has joined #ocaml
pseudo-sue has quit [Ping timeout: 265 seconds]
<Bluddy[m]> compiler question: anyone know how middle_end/closure_conversion.ml is opening lambda.ml? It's using constructors from lambda.ml but with no open.
pseudo-sue has joined #ocaml
Reshi has joined #ocaml
Orion3k has quit [Ping timeout: 240 seconds]
shinnya has quit [Ping timeout: 240 seconds]
crass has quit [Ping timeout: 244 seconds]
Orion3k has joined #ocaml
Reshi has quit [Quit: WeeChat 1.5]
bruce_r has quit [Remote host closed the connection]
rgrinberg has joined #ocaml
phase_ has joined #ocaml
pierpa has quit [Ping timeout: 240 seconds]
bruce_r has joined #ocaml
pseudo-sue has quit [Ping timeout: 265 seconds]
struk|desk2 has quit [Remote host closed the connection]
abeaumont_ has quit [Ping timeout: 265 seconds]
beaumonta has joined #ocaml
sdothum has quit [Quit: ZNC - 1.6.0 - http://znc.in]
crass has joined #ocaml
fraggle_ has quit [Ping timeout: 248 seconds]
crass has quit [Ping timeout: 250 seconds]
Heasummn has quit [Quit: Leaving]
fraggle_ has joined #ocaml
al-damiri has quit [Quit: Connection closed for inactivity]
fraggle_ has quit [Ping timeout: 265 seconds]
MercurialAlchemi has joined #ocaml
fraggle_ has joined #ocaml
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 250 seconds]
darkf has quit [Ping timeout: 250 seconds]
MercurialAlchemi has quit [Ping timeout: 240 seconds]
dlbeer has quit [Quit: leaving]
Algebr` has quit [Read error: Connection reset by peer]
Denommus has quit [Ping timeout: 244 seconds]
phase_ has quit [Remote host closed the connection]
octachron has joined #ocaml
<octachron> Bluddy[m], Lambda is not openened, the code in closure_conversion.ml is relying on constructor resolution, that does not require the corresponding type to be in scope only known
<octachron> e.g ` module M = struct type t = A end;; let x : M.t = A;;`
rgrinberg has quit [Ping timeout: 260 seconds]
tmtwd has quit [Ping timeout: 276 seconds]
copy` has quit [Quit: Connection closed for inactivity]
tmtwd has joined #ocaml
FreeBirdLjj has joined #ocaml
MercurialAlchemi has joined #ocaml
jackweirdy has joined #ocaml
rbocquet has quit [Ping timeout: 248 seconds]
chelfi has quit [Ping timeout: 250 seconds]
rom1504 has quit [Ping timeout: 250 seconds]
chelfi has joined #ocaml
rbocquet has joined #ocaml
cantstanya has quit [Ping timeout: 265 seconds]
octachron has quit [Quit: Leaving]
cantstanya has joined #ocaml
rom1504 has joined #ocaml
jackweirdy has quit [Quit: Textual IRC Client: www.textualapp.com]
darkf has joined #ocaml
Simn has joined #ocaml
tmtwd has quit [Ping timeout: 250 seconds]
bruce_r has quit [Ping timeout: 265 seconds]
valexey has quit [Ping timeout: 250 seconds]
FreeBirdLjj has quit [Remote host closed the connection]
valexey has joined #ocaml
FreeBirdLjj has joined #ocaml
kolko has quit [Quit: ZNC - http://znc.in]
kolko has joined #ocaml
Algebr` has joined #ocaml
nichola__ has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
nicholasf has quit [Ping timeout: 265 seconds]
zpe_ has quit [Remote host closed the connection]
zpe has joined #ocaml
adi___ has quit [Ping timeout: 265 seconds]
FreeBirdLjj has joined #ocaml
adi___ has joined #ocaml
nicholasf has joined #ocaml
Algebr` has quit [Remote host closed the connection]
Algebr` has joined #ocaml
nichola__ has quit [Ping timeout: 244 seconds]
FreeBirdLjj has quit [Remote host closed the connection]
pyon has quit [Quit: Fix config.]
pyon has joined #ocaml
Sorella has quit [Quit: Connection closed for inactivity]
kamog has quit [Quit: Konversation terminated!]
tmtwd has joined #ocaml
freusque has joined #ocaml
d0nn1e has quit [Ping timeout: 244 seconds]
ontologiae has joined #ocaml
d0nn1e has joined #ocaml
jstolarek has joined #ocaml
FreeBirdLjj has joined #ocaml
jstolarek has quit [Ping timeout: 240 seconds]
ryonaloli has left #ocaml ["She was Lo, plain Lo, in the morning, standing four feet ten in one sock. She was Lola in slacks. She was Dolly at school. She was Dolores on the dotted line."]
nicholasf has quit [Remote host closed the connection]
larhat has joined #ocaml
jwatzman|work has joined #ocaml
tmtwd has quit [Ping timeout: 260 seconds]
AltGr has joined #ocaml
kolko has quit [Ping timeout: 265 seconds]
kolko has joined #ocaml
jwatzman|work has quit [Quit: jwatzman|work]
nicholasf has joined #ocaml
mnbm has joined #ocaml
nicholasf has quit [Ping timeout: 240 seconds]
CuriousErnestBro has quit [Remote host closed the connection]
evhan has quit [Quit: de irc non curat lector]
evhan has joined #ocaml
<orbitz> Is there anyway to allow ocamldebug to punch through abstract types? I'd like to see what a value is even though I'm not currently in the module that exposes the type.
balojd has joined #ocaml
<def`> orbitz: nop. Abstract types are really unknown (in the most general case)
<def`> you can introspect the value structure though
<orbitz> def`: When I'm in the module that defines it, the debugger can see it. How come it cannot do this if my current execution is not in that module?
<orbitz> by "in th emodule" i mea if I'm stepping through code in that module.
balojd has quit [Remote host closed the connection]
balojd has joined #ocaml
balojd has quit [Remote host closed the connection]
silver has joined #ocaml
Balod has joined #ocaml
Balod has quit [Remote host closed the connection]
Baloda has joined #ocaml
Baloda has quit [Remote host closed the connection]
Balod has joined #ocaml
silver has quit [Quit: rakede]
freusque has quit [Ping timeout: 248 seconds]
kakadu has joined #ocaml
_andre has joined #ocaml
silver has joined #ocaml
yomimono_ has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
<Bluddy[m]> octachron: thanks. Didn't know that was possible.
<Bluddy[m]> merlin doesn't seem to do well with that
sdothum has joined #ocaml
agarwal1975 has joined #ocaml
agarwal1975 has quit [Quit: agarwal1975]
agarwal1975 has joined #ocaml
yomimono_ has quit [Ping timeout: 240 seconds]
zpe has quit [Remote host closed the connection]
copy` has joined #ocaml
pierpa has joined #ocaml
zpe has joined #ocaml
pierpa` has joined #ocaml
wu_ng has quit [Ping timeout: 265 seconds]
agarwal1975 has quit [Quit: agarwal1975]
agarwal1975 has joined #ocaml
agarwal1975 has quit [Client Quit]
ggole has joined #ocaml
Balod has quit [Remote host closed the connection]
Balod has joined #ocaml
Sorella has joined #ocaml
<profmaad> Does anybody know how to use cppo with oasis when building a library?
<profmaad> The library contains a.ccpo.ml, my oasis file for the lib states
<profmaad> 'Modules: A'
<profmaad> and I get
<profmaad> Cannot find source file matching module 'A' in library X
fraggle-boate has quit [Remote host closed the connection]
fraggle-boate has joined #ocaml
<Algebr`> profmaad: check cppo github readme/
<profmaad> I did, but didn't find anything that seemed to help?
Balod has quit [Remote host closed the connection]
<profmaad> Mhh, seems to have fixed itself. Very odd.
Balod has joined #ocaml
rgrinberg has joined #ocaml
Balod has quit [Remote host closed the connection]
rgrinberg has quit [Client Quit]
Balod has joined #ocaml
al-damiri has joined #ocaml
Balod has quit [Remote host closed the connection]
rgrinberg has joined #ocaml
Balod has joined #ocaml
Balod has quit [Remote host closed the connection]
Balod has joined #ocaml
silver has quit [Ping timeout: 240 seconds]
nicholasf has joined #ocaml
zpe has quit [Remote host closed the connection]
mnbm has quit [Quit: Page closed]
teiresias has quit [Remote host closed the connection]
jwatzman|work has joined #ocaml
ygrek has joined #ocaml
ciniglio has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 240 seconds]
<infinity0> is it possible to disable asserts for performance
<infinity0> ah, -noassert
<zozozo> infinity0: ther's also -unsafe
<zozozo> which turns off bound checking for arrays
<Algebr`> how much do you gain from -unsafe?
<Algebr`> on average
pierpa` has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
<zozozo> I'd say it depends on your usage of arrays
<zozozo> if you use mainly iter functions, not much since there is no bound checking
pierpa has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
pierpa has joined #ocaml
<Algebr`> yea, thought it would depend on usage after typing it. Could a lib be built with -unsafe?
<Algebr`> And then user of lib wouldn't have a choice in the matter right?
<Algebr`> or does that not make sense
<zozozo> well, depends on the lib
<zozozo> for isntance, the Hashtbl module in the stdlib uses arrays quite a lot, however, invariants of the hashtbl structure guarantees all array accesses are valid, so turning off bound checking on this module would make sense (assuming there is no bug in the module of course)
<ggole> Hashtbl doesn't bother though
<ggole> If you do bounds checking thoughtfully, the perf hit is really pretty small
<ggole> (Thoughtfully meaning that you use the sign trick to only require one branch, and that the bounds error case branches forwards so as to benefit from static prediction.)
<ggole> I guess there's two branches for polymorphic arrays, due to the float array thing.
jwatzman|work has quit [Quit: jwatzman|work]
SpiceGuid has joined #ocaml
SpiceGuid has quit [Client Quit]
<zozozo> don't think so, the check is done using the size information in the block header, so float arrays should not change much to that
<mrvn> "the sign trick"?
<mrvn> A lot of the time the bounds check fits in free slots inbetween the actual code and is irelevant
<mrvn> And good code that accesses an array often checks the bounds at the start and then knows all other access is safe.
<mrvn> You can even use GADTs tp encode array indexes and have the type system check bounds statically at compile time. There is a Quicksort example out there doing that.
<zozozo> well, it doen't work for resizeable arrays (or similar data structures)
<ggole> zozozo: the header stores the block size. For regular arrays this is the number of elements. For float arrays it is the twice the number of elements.
<companion_cube> you mean minus?
<ggole> mrvn: the sign trick is using unsigned comparisons to avoid having to test for < 0 case separately.
sh0t has joined #ocaml
MercurialAlchemi has joined #ocaml
<zozozo> ggole: depends on the architecture, no ? on 64bits floats only take 1 word so the size should pretty much be equal to the number of elements, or am I missing something ?
AlexRussia_ has quit [Ping timeout: 240 seconds]
<ggole> Oh right, I might be remembering that from 32-bit days.
ryanartecona has quit [Quit: ryanartecona]
ryanartecona has joined #ocaml
nicholasf has quit [Remote host closed the connection]
nicholasf has joined #ocaml
theblatte has quit [Ping timeout: 255 seconds]
theblatte has joined #ocaml
regnat[m] has quit [Remote host closed the connection]
Bluddy[m] has quit [Remote host closed the connection]
barkmadley[m] has quit [Read error: Connection reset by peer]
srenatus[m] has quit [Remote host closed the connection]
M-jimt has quit [Remote host closed the connection]
M-ErkkiSeppl has quit [Remote host closed the connection]
M-martinklepsch has quit [Read error: Connection reset by peer]
M-pesterhazy has quit [Remote host closed the connection]
M-Illandan has quit [Write error: Connection reset by peer]
ygrek has quit [Ping timeout: 276 seconds]
shinnya has joined #ocaml
nichola__ has joined #ocaml
nicholasf has quit [Ping timeout: 260 seconds]
nicholasf has joined #ocaml
nichola__ has quit [Ping timeout: 260 seconds]
jwatzman|work has joined #ocaml
yomimono_ has joined #ocaml
slash^ has joined #ocaml
jao has joined #ocaml
jwatzman|work has quit [Quit: jwatzman|work]
nicholasf has quit [Remote host closed the connection]
yomimono_ has quit [Ping timeout: 240 seconds]
larhat has quit [Quit: Leaving.]
Intensity has joined #ocaml
bruce_r has joined #ocaml
chindy_ has joined #ocaml
chindy_ has left #ocaml ["Leaving"]
chindy has joined #ocaml
regnat[m] has joined #ocaml
AlexRussia_ has joined #ocaml
<Algebr`> my ocaml binary is bsd-3, there's a c binary I'm looking at, its gpl2. I want to rip out some parts of the c binary, write ocaml bindings to it. Does the gpl infect me?
kakadu has quit [Quit: Page closed]
<Algebr`> people are saying yes
shinnya has quit [Ping timeout: 240 seconds]
ontologiae has quit [Ping timeout: 244 seconds]
yomimono_ has joined #ocaml
dougt_ has joined #ocaml
yomimono_ has quit [Ping timeout: 250 seconds]
AltGr has left #ocaml [#ocaml]
<lyxia> Algebr`: "b) You must cause any work that you distribute or publish, that in whole or in part contains or is derived from the Program or any part thereof, to be licensed as a whole at no charge to all third parties under the terms of this License." suggests to me that yes. Were you thinking of some subtlety related to the fact that you're using binaries perhaps?
<lyxia> It might not apply if you just release the bindings...
yomimono_ has joined #ocaml
<lyxia> Hire a lawyer.
ontologiae has joined #ocaml
<dougt_> At http://pauillac.inria.fr/cousineau-mauny/main.html there are links related to the book "The functional approach to programming with Caml". The link for downloading the programs is broken (ftp.inria.fr’s server DNS address could not be found). Is there an alternate site?(
<Algebr`> lyxia: well I didn't want to do the bindings as a separate things, just for use in the ocaml binary
<Algebr`> my gut also says yes
<clockish> Language question: in pattern matching, can I apply the guard and branch to two separate patterns without repeating them?
<clockish> e.g. on section 8.5.2 of http://caml.inria.fr/pub/docs/manual-ocaml/comp.html where it says "This is not the semantics adopted by OCaml"... I want those semantics, but without having to repeat "when guard -> expr" multiple times.
<Algebr`> I think you can if name binding that you use happens to be in both, maybe something like Foo a | Bar b when a > 10 || b > 5 ->
<ggole> clockish: pattern matching doesn't work that way, so you'll have to live with it
<ggole> You can factor out the guard and expr into functions if they happen to be large, that's about it
<Algebr`> oh darn
chindy has quit [Remote host closed the connection]
jao has quit [Ping timeout: 265 seconds]
<clockish> oh well. thanks!
<ggole> It's not an oversight, if you were wondering - making it work that way would involve backtracking
<ggole> Instead of nice decision trees
yomimono_ has quit [Quit: Leaving]
<clockish> Heh, well, in this case I needed the backtracking :P
<ggole> Yeah, it would be nice if it magically worked
<companion_cube> vbmithr: broken link on https://github.com/vbmithr/ocaml-msgpck btw
<companion_cube> (homepage is wrong)
<companion_cube> to the docs, also?
teiresias has joined #ocaml
<orbitz> I ugpraded ot the latest tuareg mode and it's not indenting htings how I want. Anyone have some experience customizing tuareg mode? Specifically, if I have an else begin ... end, the ... gets double indented
manizzle has quit [Remote host closed the connection]
<Algebr`> does anyone use opam lib? I keep hearing how its basically another stdlib
<Algebr`> also, looking for code that parses opam files into some data structure
<Algebr`> rather, the opam code
<companion_cube> I suppose things like opam-publish use the opamlib
lgstate has joined #ocaml
<lgstate> how is it that ocaml is beating jvm languages (clojure, scala) for the hft finance firms?
<lgstate> how is the ocaml gc faster?
<companion_cube> OCaml heap values are generally smaller, I think
<companion_cube> the JVM objects are heavyweight (embedded semaphore) and generics only work on boxed values, even for integers
FreeBirdLjj has quit [Ping timeout: 265 seconds]
<companion_cube> I'm not sure OCaml is much used in *hft* finance
<lgstate> oh; so jvm ints = pointer -> int object; ocaml ints = just store it instead of the ptr, and this is why ocaml ints lose 1 bit ?
<lgstate> is janestreet hft?
<lgstate> maybe I should have said prop trading
kamog has joined #ocaml
<ggole> JVM ints are primitives
<companion_cube> lgstate: in java, `ArrayList<Integer>` is an array of objects; `int array` in OCaml is flat
<companion_cube> ggole: not in generics
<ggole> So, not a pointer (although Integer is a pointer)
<companion_cube> lgstate: I don't think JST is hft
<companion_cube> ggole: as soon as you put it in a generic container, it becomes a pointer
<ggole> I know
<Algebr`> Jane street said they aren't hft
FreeBirdLjj has joined #ocaml
<lgstate> okay; I recant; janestreet is not hft :-)
govg has joined #ocaml
<flux> yeah, they don't have any FPGA projects for OCaml do they ;)
<ggole> The 'lock word' has also gone away for modern JVMs, they do clever things like lock inflation instead
<flux> orbitz, I think the best way is to start using ocp-indent
<companion_cube> ggole: really? that'snice
<companion_cube> there is much work poured into the JVMs anyway
<companion_cube> if only they had proper tailcalls :)
<ggole> Crazy amounts of work
<ggole> In the hundreds of people
<orbitz> flux: is ocp-indent an emacs mode or a proram/
<flux> orbitz, a program, there's emacs code to support it
<flux> funny how ocaml-java isn't really (?) popular, given how it gives parallellism to ocaml, has given for years. is it not otherwise well-performing?
<Algebr`> isn't ocaml-java dead?
<orbitz> flux: is it customizable or is it like gofmt?
<flux> though it might also be that a GC that's fast for Java is not fast for (a typical) OCaml program
<flux> orbitz, I don't know, I haven't customized it
<orbitz> ok
<flux> seems like there is some configuration. not a lot.
<companion_cube> flux: it's closed source, looks as horrible w.r.t bindings as jsoo...
<companion_cube> or used to be closed source, can't remember
<companion_cube> orbitz: ocp-indent is customizable
<orbitz> The JVM isn't a really pleasant environment to operate or program for relative to teh Ocaml runtime
<companion_cube> yeah
<orbitz> companion_cube: thanks, I'll try this
<orbitz> companion_cube: what do these customization do?
<companion_cube> specify the indentation of branches relative to the match, for instance
<companion_cube> ocp-indent --help describes them all
<Algebr`> okay opam-lib packages tests are each just two ines of code...that does nothing
<Algebr`> tests nothing
<Algebr`> ..
<reynir> Make pull request
<orbitz> companion_cube: do you use tuaregmode with ocp-indent?
<companion_cube> I don't use emacs
<thizanne> orbitz: I do
<thizanne> it's straightforward and well documented in the installation
<orbitz> thizanne: Does tuareg and ocp-indent compete for who owns indentation?
<thizanne> no they don't
<thizanne> (require 'ocp-indent)
<thizanne> (add-hook 'typerex-mode-hook 'ocp-setup-indent t)
<thizanne> I just have these lines to setup ocp-indent
<thizanne> I have no idea why it's typerex-mode-hook though
<orbitz> Hrm ok.
<thizanne> (but it works, and I use tuareg)
<Algebr`> reynir: I was mainly looking for examples of how to use the lib, but the types are straightforward, although it eats up quite a bit of top level module names
<orbitz> thizanne: nice, that seemed to do the trick, thanks
orbifx has joined #ocaml
<orbitz> argh, begin/end are still not indenting correctly for me
M-martinklepsch has joined #ocaml
M-jimt has joined #ocaml
Bluddy[m] has joined #ocaml
M-ErkkiSeppl has joined #ocaml
M-pesterhazy has joined #ocaml
srenatus[m] has joined #ocaml
M-Illandan has joined #ocaml
barkmadley[m] has joined #ocaml
CuriousErnestBro has joined #ocaml
TheLemonMan has joined #ocaml
orbifx has quit [Ping timeout: 248 seconds]
AlexRussia_ has quit [Ping timeout: 265 seconds]
<companion_cube> this style of begin/end is very weird
CuriousErnestBro has quit [Ping timeout: 265 seconds]
Muzer has quit [Ping timeout: 255 seconds]
manizzle has joined #ocaml
<infinity0> let fix f = let rec r = f r in r
<infinity0> Error: This kind of expression is not allowed as right-hand side of `let rec'
<infinity0> aw come on ocaml whyyy
kakadu has joined #ocaml
AlexRussia_ has joined #ocaml
<lyxia> cuz we're strict people here
<lyxia> we don't fool around with fixpoints
<companion_cube> we do, but it requires careful application of `lazy`
<companion_cube> (although this fixpoint seems hard to write at all)
CuriousErnestBro has joined #ocaml
<companion_cube> unless `f: 'a lazy_t -> 'a`
<companion_cube> `let fix f = let rec r = lazy (f r) in Lazy.force r` might work
<infinity0> let fix f = let rec r x = f r x in r
<infinity0> this also compiles apparently
<infinity0> i was basically trying to generalise this http://typeocaml.com/2015/01/25/memoize-rec-untying-the-recursive-knot/
<infinity0> (and it works even if f takes more than 1 argument. i haven't tried running it, though)
<ggole> (I had that one sitting around somewhere.)
<infinity0> would my one go into an infinite loop or something, or is it ok
Muzer has joined #ocaml
<companion_cube> it shoudl work, as you define a recrsive function, rather than a value (which is forbidden)
<ggole> You've eta-expanded it, so it should be fine
<infinity0> ah ok, i think i understand now
ryanartecona has quit [Quit: ryanartecona]
TheLemonMan has quit [Quit: "It's now safe to turn off your computer."]
agarwal1975 has joined #ocaml
<infinity0> ok this is actually just the y combinator and this works `let rec fix f = f (fix f)` as well
slash^ has quit [Read error: Connection reset by peer]
<thizanne> infinity0: but you might want an extra argument
<infinity0> mind = blown
<infinity0> oh, why extra? this one compiles ok..
<thizanne> yes but can you use it ?
<thizanne> utop # let rec fix f = f (fix f) in fix (fun f n -> if n = 0 then 1 else n * f (n - 1));;
<thizanne> Stack overflow during evaluation (looping recursion?).
<thizanne> but :
<thizanne> top # let rec fix f x = f (fix f) x in fix (fun f n -> if n = 0 then 1 else n * f (n - 1)) 4;;
<thizanne> - : int = 24
<infinity0> oh i see, in the first expression ocaml tries to completely evaluate "f (fix f)" which involves evaluating (fix f) first but it's not known to be a function
<infinity0> ok, i needed a concrete example to really see what "strict evaluation" results in in this context, thanks
ggole has quit []
manizzle has quit [Remote host closed the connection]
manizzle has joined #ocaml
sh0t has quit [Quit: Leaving]
orbifx has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 250 seconds]
_andre has quit [Quit: leaving]
<orbifx> hello *
ryanartecona has joined #ocaml
mg has quit [Ping timeout: 265 seconds]
mg has joined #ocaml
nicholasf has joined #ocaml
mg has quit [Ping timeout: 248 seconds]
Orion3k has quit [Ping timeout: 250 seconds]
mg has joined #ocaml
foocraft has joined #ocaml
nicholasf has quit [Ping timeout: 265 seconds]
agarwal1975 has quit [Quit: agarwal1975]
kolko has quit [Ping timeout: 276 seconds]
CuriousErnestBro has quit [Quit: Leaving]
<orbifx> Is there aything wrong with using let ... and .. in .. ?
FreeBirdLjj has quit [Remote host closed the connection]
Orion3k has joined #ocaml
rbocquet has quit [Ping timeout: 265 seconds]
<smondet> orbifx: not really wrong but when reading code, the `and` triggers a mental warning: "Attention, mutually recursive functions!!", so using `and` for no good reason can be a bit annoying on the reader (IMHO)
<companion_cube> orbifx: no, they're fine
kakadu_ has joined #ocaml
<orbifx> smondet: I see what you are saying. When there are many lets it cna break the monotony.. :P
<orbifx> but I get your point, will keep it in mind
kolko has joined #ocaml
kakadu has quit [Ping timeout: 240 seconds]
<orbifx> Also, has the syntax for nested record setting been "fixed": { record with foo.bar ... } ?
rbocquet has joined #ocaml
lgstate has quit [Quit: Page closed]
caw has quit [Ping timeout: 250 seconds]
_whitelogger has joined #ocaml
kolko has quit [Ping timeout: 244 seconds]
Leonidas has joined #ocaml
d0nn1e has quit [Ping timeout: 260 seconds]
edwin has joined #ocaml
glesica has joined #ocaml
kolko has joined #ocaml
rfv has joined #ocaml
fUD has joined #ocaml
bitbckt has joined #ocaml
d0nn1e has joined #ocaml
dch has joined #ocaml
noplamodo has joined #ocaml
jyc has joined #ocaml
cschneid has joined #ocaml
caw has joined #ocaml
keteim is now known as mietek
chenglou has joined #ocaml
jcloud has joined #ocaml
rpip has joined #ocaml
groovy2shoes has joined #ocaml
saidinwot has joined #ocaml
TheAuGingembre has joined #ocaml
zozozo has joined #ocaml
mietek has left #ocaml ["NO CARRIER"]
zv has quit [Quit: WeeChat 1.5]
zv has joined #ocaml
zv has quit [Client Quit]
zv has joined #ocaml
zv has quit [Client Quit]
zv has joined #ocaml
kakadu_ has quit [Remote host closed the connection]
nicholasf has joined #ocaml
nicholasf has quit [Remote host closed the connection]
nicholasf has joined #ocaml
nicholas_ has joined #ocaml
nicholasf has quit [Ping timeout: 265 seconds]
orbifx has quit [Ping timeout: 244 seconds]
glesica has quit [Ping timeout: 248 seconds]
glesica has joined #ocaml
ygrek has joined #ocaml
foocraft has quit [Quit: Leaving]
Jaxan has quit [Ping timeout: 265 seconds]
Jaxan has joined #ocaml
al-damiri has quit [Quit: Connection closed for inactivity]
ydl has joined #ocaml
Simn has quit [Quit: Leaving]
ryanartecona has quit [Quit: ryanartecona]
shinnya has joined #ocaml
bruce_r has quit [Remote host closed the connection]
Heasummn has joined #ocaml
ee_ks1 has joined #ocaml