ChanServ changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml 4.02.1 announcement at http://ocaml.org/releases/4.02.html | Public channel logs at http://irclog.whitequark.org/ocaml
claudiuc has quit [Ping timeout: 255 seconds]
<Drup> I'm surprised I didn't do it already, I remember reading one of your burn-camlp4 PR, and I think it was lwt.
<whitequark> Drup: rebased
badon has quit [Quit: Leaving]
WraithM has quit [Ping timeout: 256 seconds]
travisbrady has joined #ocaml
claudiuc has joined #ocaml
AlexRussia has joined #ocaml
rgrinberg1 has joined #ocaml
rgrinberg has quit [Read error: Connection reset by peer]
claudiuc has quit [Ping timeout: 258 seconds]
<Drup> whitequark: I never realized that lwt contains the embryo of zed/lambda-term/utop.
claudiuc has joined #ocaml
<whitequark> embryo? O_o
<Drup> that's not the right word ?
<Drup> ah, maybe it's only a french idioms. :<
<Drup> whitequark: I was talking about everything you removed in the first commit.
badon has joined #ocaml
claudiuc_ has joined #ocaml
claudiuc has quit [Read error: Connection reset by peer]
<whitequark> oh
<Drup> whitequark: the commit that removes the #if windows makes me think we should create a ppx that allows to do a tiny bit of metaprogramming to allow compile time small extensions
<Drup> to abstract over "if if Sys.win32 then return (Unix.foo ...) else run_job (Jobs.foo ...)"
<Drup> you can't abstract normally, since you have different "foo" functions, but it's not normal you can't factorize the code somehow ...
rgrinberg1 has quit [Quit: Leaving.]
NoNNaN has quit [Remote host closed the connection]
NoNNaN has joined #ocaml
MrScout_ has joined #ocaml
rgrinberg has joined #ocaml
thomasga has quit [Quit: Leaving.]
MrScout has quit [Ping timeout: 258 seconds]
MrScout_ has quit [Ping timeout: 258 seconds]
jao has quit [Ping timeout: 255 seconds]
jwatzman|work has quit [Quit: jwatzman|work]
travisbrady has quit [Quit: travisbrady]
milosn has quit [Ping timeout: 252 seconds]
<Drup> whitequark: Oh god, I'm not paid enough to review "Get rid of all instances of "#if windows" that refer to primitives.", how did you even wrote this commit without killing yourself ? X_x
<whitequark> lol
<Drup> you don't seem to have used regexps even
<whitequark> all manually
<whitequark> and in fact I rewrote it entirely after some comments from @diml
<Drup> I would have used regexps.
<Drup> yes, I saw
<Drup> Noooo, the next commit is the same T_T
<whitequark> mwahahaha
<Drup> the worst part is that this code is precisely what should be reviewed carefully X_X
travisbrady has joined #ocaml
patojo has quit [Remote host closed the connection]
jonludlam has quit [Ping timeout: 250 seconds]
<Drup> whitequark: the testing on android is done since ?
<whitequark> what do you mean?
<Drup> "I have yet to test it on Android, but you can start reviewing the changes."
<whitequark> I still do not understand the question
<Drup> in particular, the functions "getlogin getpwnam getgrnam wait4" which you enabled on android
antinomy has quit [Ping timeout: 272 seconds]
<Drup> (they were disabled before)
<whitequark> oh, I think they added them in ndk 10c
<Drup> yeah, but you said you were going to test it, did you ? ^^'
<whitequark> yes, I did and it works
<Drup> fine.
samrat has quit [Quit: Computer has gone to sleep.]
<whitequark> Leonidas: that is odd
antinomy has joined #ocaml
manud has joined #ocaml
avsm has joined #ocaml
Thooms has quit [Ping timeout: 272 seconds]
<Leonidas> whitequark: looks like a problem in ctypes, but I can't really reproduce it at home :)
<Leonidas> maybe I'll try tomorrow
<Drup> whitequark: when you fix the build error, please make a small patch on top of it, so I can review it individually (and eventually merge it after)
<whitequark> Drup: which build error?
<whitequark> oh, ssl
<Drup> (also valid if you correct other things)
<whitequark> I was going to just rebase the whole thing
<Drup> yes, that's my point
<Drup> rebase *after* I review the individual patch
<Drup> so I don't have to play at "where did he changed something"
<whitequark> ahhh ok
<Drup> because it's not a fun game at all :<
<whitequark> maybe if you have a masochistic streak
<whitequark> recommended if you work with software in general, tbh
<Drup> well, I minimized my masochistic tendances, I'm neither a web developer nor a low level one.
<Leonidas> no hunting movl %eax?
<whitequark> nah, lowlevel stuff is cool
<Drup> ok, let me be more precise
<Drup> not a C developer.
<Drup> (from my point of view, it's lower level than me)
rgrinberg has quit [Quit: Leaving.]
<whitequark> btw, Lwt.wrap does not work there
<whitequark> Error: This expression has type unit Lwt.t Lwt.t
<Drup> let wrap1 f x1 = try return (f x1) with exn -> fail exn
<Drup> so yeah, not valid, it's not Lwt.catch ...
darkf has joined #ocaml
rgrinberg has joined #ocaml
<whitequark> Drup: lwt.ml 519
<whitequark> why
<Drup> ?
<Drup> hum
<Drup> I have no idea.
<whitequark> pushed
<Drup> whitequark: very removed allocations, much optimized :D
claudiuc_ has quit [Read error: Connection reset by peer]
<whitequark> well, no harm to do it in the core library
<Drup> sure ^^
claudiuc has joined #ocaml
seanmcl has joined #ocaml
travisbrady has quit [Quit: travisbrady]
avsm has quit [Quit: Leaving.]
milosn has joined #ocaml
lordkryss has quit [Quit: Connection closed for inactivity]
ollehar has quit [Ping timeout: 258 seconds]
<whitequark> Drup: so, did you review it?
<Drup> yes! I was writing some post about something different, sorry!
<Drup> jenkins is still failing, but for bad reasons :(
<Drup> It was not amusing
<Drup> I express all my thanks to my powermetal playlist in carrying me through this journey.
shinnya has quit [Ping timeout: 252 seconds]
<Drup> I did only the visual review, going to do some more check
rgrinberg1 has joined #ocaml
BitPuffin has quit [Quit: See you on the dark side of the moon!]
rgrinberg has quit [Read error: Connection reset by peer]
<whitequark> Drup: fixed manual
<Drup> you see, it wasn't terrible :D
<Drup> huh, the doc doesn't compile :(
<Drup> latex_of_wiki lwt-manual < manual.wiki > manual-wiki.tex.tmp
<Drup> Fatal error: unknown C primitive `lwt_libev_init'
<Drup> w.t.f.
<whitequark> lol
<whitequark> where do I get latex_of_wiki?
<Drup> I don't even know, I didn't know I had that installed xD
<Drup> probably wikidoc
<whitequark> um
<whitequark> and where is that from?
<Drup> which I'm pretty sure is not opamized
<Drup> and which you don't want to look at ever ever
<Drup> oh, it's opamized !
manizzle has quit [Ping timeout: 244 seconds]
<whitequark> [ERROR] No package named wikidoc found.
<Drup> I mean, there is an opam file
<Drup> it's not in the main repo
<whitequark> ugh
<whitequark> [ERROR] wikidoc.dev is not available because it requires OCaml = 4.01.0.
<whitequark> well fuck you too
<Drup> :D
<Drup> whitequark: the wikidoc is pretty much in the state of "look at what jenkin generated on http://ocsigen.org/lwt/dev/manual/ and fix it if it's broken"
<Drup> because running it locally is ... annoying.
_5kg has joined #ocaml
<Drup> whitequark: you can generate the normal ocamldoc though, with "make doc-api"
<whitequark> that works
<Drup> yes
<Drup> (and with no suspicious "not found")
travisbrady has joined #ocaml
samrat has joined #ocaml
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
antinomy has quit [Ping timeout: 272 seconds]
ggole has joined #ocaml
manud has quit [Quit: Be back later ...]
chinglish has joined #ocaml
<Drup> ahahahaha
<Drup> Lwt_event is used inside ocsigenserver
<whitequark> you know what to do :]
<Drup> Yes I do
<Drup> Dive into my bed and swim into sleep.
<Drup> oh, it's an easy fix
q66 has quit [Quit: Leaving]
claudiuc has quit [Remote host closed the connection]
rgrinberg has joined #ocaml
rgrinberg1 has quit [Read error: Connection reset by peer]
<Drup> ok, done, to bed know.
<Drup> now*
rgrinberg has quit [Quit: Leaving.]
rgrinberg has joined #ocaml
manud has joined #ocaml
rgrinberg has quit [Quit: Leaving.]
rgrinberg has joined #ocaml
relrod has quit [Ping timeout: 245 seconds]
travisbrady has quit [Quit: travisbrady]
travisbrady has joined #ocaml
manud has quit [Quit: Be back later ...]
travisbrady has quit [Client Quit]
relrod_ has joined #ocaml
ygrek has joined #ocaml
rgrinberg has quit [Quit: Leaving.]
ontologiae has quit [Ping timeout: 250 seconds]
AlexRussia has quit [Ping timeout: 265 seconds]
bytbox has quit [Remote host closed the connection]
ygrek has quit [Ping timeout: 260 seconds]
shinnya has joined #ocaml
natrium1970 has joined #ocaml
rgrinberg has joined #ocaml
<natrium1970> If I write “type t = A of t | B of int”, I can use a match statement like “match x with A (B n) -> 1 …” Is there a way to bind a “b” to B n during the match? writing “match x with A (B n as b -> 1” does not work.
<natrium1970> Oh. Never mind.
AlexRussia has joined #ocaml
darkf_ has joined #ocaml
<ggole> 'as' often needs to be wrapped in parens
darkf has quit [Ping timeout: 258 seconds]
<natrium1970> That actual code has a more complex variant, like C of t * t, so the pattern needed some extra parentheses inside the components of the tuple. Like
<natrium1970> | C (A p, B q) works as a pattern, but with the as-bindings, it needed a construction like | C ( (A p as a_bound), (B q as b_bound) ).
<ggole> Yep
<ggole> Or a nested match
<natrium1970> Eventually, it will get complicated enough that I will have to do that.
seanmcl has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
keen_______ has joined #ocaml
keen______ has quit [Ping timeout: 264 seconds]
rgrinberg has quit [Quit: Leaving.]
rgrinberg has joined #ocaml
darkf_ is now known as darkf
relrod_ is now known as relrod
darkf_ has joined #ocaml
seanmcl has joined #ocaml
darkf has quit [Ping timeout: 272 seconds]
AlexRussia has quit [Ping timeout: 250 seconds]
rgrinberg has quit [Read error: Connection reset by peer]
darkf has joined #ocaml
darkf_ has quit [Ping timeout: 258 seconds]
seanmcl has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
darkf_ has joined #ocaml
darkf has quit [Ping timeout: 258 seconds]
darkf_ is now known as darkf
natrium1970 has quit [Quit: natrium1970]
Submarine has joined #ocaml
darkf_ has joined #ocaml
darkf has quit [Ping timeout: 258 seconds]
darkf has joined #ocaml
superjudge has joined #ocaml
darkf_ has quit [Ping timeout: 258 seconds]
davine has joined #ocaml
ygrek has joined #ocaml
davine has left #ocaml [#ocaml]
jao has quit [Ping timeout: 272 seconds]
manud has joined #ocaml
AlexRussia has joined #ocaml
Submarine has quit [Ping timeout: 244 seconds]
slash^ has joined #ocaml
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
darkf_ has joined #ocaml
darkf has quit [Ping timeout: 258 seconds]
dmiles_afk has joined #ocaml
NoNNaN has quit [Ping timeout: 250 seconds]
NoNNaN has joined #ocaml
darkf has joined #ocaml
MercurialAlchemi has joined #ocaml
darkf_ has quit [Ping timeout: 258 seconds]
marynate has joined #ocaml
darkf_ has joined #ocaml
milosn has quit [Remote host closed the connection]
darkf has quit [Ping timeout: 258 seconds]
jonludlam has joined #ocaml
Arsenik has joined #ocaml
milosn has joined #ocaml
manizzle has joined #ocaml
lordkryss has joined #ocaml
manud has quit [Quit: Be back later ...]
def` has joined #ocaml
thomasga has joined #ocaml
AltGr has left #ocaml [#ocaml]
avsm has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 264 seconds]
Arsenik has quit [Ping timeout: 250 seconds]
chambart has joined #ocaml
jonludlam has quit [Ping timeout: 258 seconds]
darkf_ is now known as darkf
samrat has quit [Quit: Computer has gone to sleep.]
ygrek has quit [Ping timeout: 244 seconds]
jbrown has quit [Remote host closed the connection]
jbrown has joined #ocaml
ikaros has joined #ocaml
seanmcl has joined #ocaml
ontologiae has joined #ocaml
def` has quit [Ping timeout: 264 seconds]
Simn has joined #ocaml
eyyub has joined #ocaml
jbrown has quit [Remote host closed the connection]
seanmcl has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
jbrown has joined #ocaml
avsm has quit [Quit: Leaving.]
def` has joined #ocaml
fraggle_ has quit [Ping timeout: 258 seconds]
fraggle_ has joined #ocaml
thomasga has quit [Quit: Leaving.]
thomasga has joined #ocaml
BitPuffin has joined #ocaml
marynate has quit [Read error: Connection timed out]
ontologiae has quit [Ping timeout: 252 seconds]
Leonidas has quit [Ping timeout: 258 seconds]
Leonidas has joined #ocaml
MercurialAlchemi has joined #ocaml
chambart has quit [Ping timeout: 260 seconds]
Muzer has quit [Excess Flood]
Muzer has joined #ocaml
samrat has joined #ocaml
thomasga has quit [Quit: Leaving.]
chinglish has quit [Ping timeout: 264 seconds]
eyyub has quit [Ping timeout: 240 seconds]
eyyub has joined #ocaml
def` has quit [Quit: def`]
manizzle has quit [Ping timeout: 256 seconds]
thomasga has joined #ocaml
oscar_toro has quit [Ping timeout: 245 seconds]
q66 has joined #ocaml
oscar_toro has joined #ocaml
oscar_toro has quit [Client Quit]
pgomes has joined #ocaml
oscar_toro has joined #ocaml
avsm has joined #ocaml
thomasga has quit [Quit: Leaving.]
Arsenik has joined #ocaml
myyst has quit [Quit: Leaving]
thomasga has joined #ocaml
myyst has joined #ocaml
oscar_toro has quit [Ping timeout: 252 seconds]
myyst has quit [Quit: Leaving]
antinomy has joined #ocaml
ontologiae has joined #ocaml
Hannibal_Smith has joined #ocaml
chinglish has joined #ocaml
marynate has joined #ocaml
ontologiae has quit [Ping timeout: 240 seconds]
<ggole> Occasionally it is really annoying that pattern matching can't look into array references.
michipili has joined #ocaml
thomasga has quit [Quit: Leaving.]
<michipili> Hi there! OCaml port for FreeBSD is ready. If you wish to try it, see https://github.com/michipili/ports-bsd/tree/ocaml-4.02.1
<michipili> There is a port for labltk as well.
<avsm> michipili: great! you need a separate port for camlp4 as well i think?
waneck has quit [Read error: No route to host]
<michipili> asvm: You are right
<michipili> !
<michipili> I forgot that one.
<michipili> What is the difference between camlp4 and camlp5? Surely there are some, but…
<ggole> camlp5 is the original
<ggole> (The p4 stands for "four ps", not the version number.)
<michipili> which in turn stands for?
<ggole> Um, pre-processor and pretty printer, I think?
<michipili> pre-tty printer looks like the pun of the day! :)
<ggole> It's a huge crazy metaprogramming/parsing/printing mess thing.
<companion_cube> ggole: what do you mean? you can match agaisnt arrays
<michipili> wild guess for p5 ?
<ggole> companion_cube: I mean, if you have type t = Foo of int * int | ..., you can't match against the contents of an array indexed by those ints.
<companion_cube> oh
<companion_cube> that would be akin to views
<ggole> Yeah.
<ggole> michipili: even better, camlp5 used to be called camlp4
<ggole> So there's old documentation sitting around that is *very* confusing.
<michipili> Yeaah I never used camlp[45] but had blurry remembrances about these naming issues…
<michipili> The new @-annotations should make camlp4 more or less obsolete, if I understand correctly.
<ggole> Let's hope so.
samrat has quit [Ping timeout: 250 seconds]
samrat has joined #ocaml
AlexRussia has quit [Ping timeout: 272 seconds]
myyst has joined #ocaml
myyst has quit [Remote host closed the connection]
myyst has joined #ocaml
myyst has quit [Client Quit]
AlexRussia has joined #ocaml
thomasga has joined #ocaml
AlexRussia has quit [Quit: WeeChat 1.1-dev]
AlexRussia has joined #ocaml
milosn has quit [Remote host closed the connection]
thomasga has quit [Client Quit]
AlexRussia has quit [Ping timeout: 272 seconds]
Hannibal_Smith has quit [Quit: Leaving]
AlexRussia has joined #ocaml
AlexRussia has quit [Ping timeout: 240 seconds]
kakadu_ has joined #ocaml
pgomes has quit [Quit: Leaving]
AlexRussia has joined #ocaml
myyst has joined #ocaml
myyst has quit [Client Quit]
thomasga has joined #ocaml
myyst has joined #ocaml
larhat has joined #ocaml
travisbrady has joined #ocaml
q66[lap] has quit [Quit: Textual IRC Client: www.textualapp.com]
q66[lap] has joined #ocaml
darkf has quit [Quit: Leaving]
thomasga has quit [Quit: Leaving.]
Thooms has joined #ocaml
thomasga has joined #ocaml
thomasga has quit [Quit: Leaving.]
thomasga has joined #ocaml
acieroid has quit [Ping timeout: 250 seconds]
marynate has quit [Quit: Leaving]
acieroid has joined #ocaml
araujo has quit [Read error: Connection reset by peer]
araujo has joined #ocaml
thomasga has quit [Quit: Leaving.]
travisbrady has quit [Quit: travisbrady]
rand000 has joined #ocaml
Hannibal_Smith has joined #ocaml
travisbrady has joined #ocaml
avsm has quit [Quit: Leaving.]
Thooms has quit [Quit: WeeChat 1.0.1]
ontologiae has joined #ocaml
thomasga has joined #ocaml
waneck has joined #ocaml
milosn has joined #ocaml
bytbox has joined #ocaml
waneck has quit [Read error: No route to host]
tharugrim has quit [Ping timeout: 265 seconds]
pgomes has joined #ocaml
waneck has joined #ocaml
tharugrim has joined #ocaml
c74d has joined #ocaml
c74d has quit [Read error: Connection reset by peer]
c74d has joined #ocaml
myyst has quit [Read error: Connection reset by peer]
myyst has joined #ocaml
<Drup> eyyub: ping
pgomes has quit [Ping timeout: 252 seconds]
pgomes has joined #ocaml
Arsenik has quit [Remote host closed the connection]
oscar_toro has joined #ocaml
<nicoo> Drup: Do you remember what the doc says about the number of variants in the same type? I can't find it again in the manual :o
<Drup> "enough for humans".
<nicoo> (variants as in constructors, not as in poly variants)
<ggole> Less than 251, I think
<ggole> That's for constructors with arguments. You can have pretty much as many nullary constructors as you like.
shinnya has quit [Ping timeout: 272 seconds]
<ggole> Nope, 246
jabesed has joined #ocaml
shinnya has joined #ocaml
<mrvn> ggole: 2 billion on 32bit
<mrvn> I bet the compiler runs out of memory way before you manage to have 2 billion constructors without argument on a 32bit system.
bytbox has quit [Remote host closed the connection]
<ggole> Yeah, seems likely.
ikaros has quit [Quit: Ex-Chat]
boogie has joined #ocaml
slash^ has quit [Read error: Connection reset by peer]
slash^ has joined #ocaml
art-w has quit [Ping timeout: 258 seconds]
art-w has joined #ocaml
manud has joined #ocaml
travisbrady has quit [Quit: travisbrady]
chinglish has quit [Quit: Nettalk6 - www.ntalk.de]
samrat has quit [Quit: Computer has gone to sleep.]
AlexRussia has quit [Ping timeout: 244 seconds]
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
BitPuffin has quit [Ping timeout: 264 seconds]
<nicoo> ggole: Thanks a lot
BitPuffin has joined #ocaml
* nicoo wonders how bad it would be to force 32-byte alignment for OCaml values on x86
travisbrady has joined #ocaml
<nicoo> Drup: Trying to make my evil idea (about unifying foo * bar and (foo * bar)) work :3
<Drup> Oh.
JokerDoom has joined #ocaml
<nicoo> On 64-bits platforms, it is (relatively) straightforward. On x86, though, I think I need to play with alignment and cram data (well, tags) in the pointers
<ggole> What evil idea is this?
<nicoo> ggole: Basically, Bar of (foo * baz) and Bar of foo * baz are represented differently currently because one can be “transformed” into a tuple without allocating, but has one added level of indirection
<ggole> Sure.
madroach has joined #ocaml
<nicoo> If one can cram the constructor's tag in the pointer, Bar of (foo * baz) is exactly like Bar of foo * baz with an added indirection (i.e. the second one can be “just” a length-2 cell), and it makes perfect sense to drop that level of indirection
_JokerDoom has joined #ocaml
<nicoo> -> they are represented the same -> they should be the same.
<nicoo> (Not sure I'm being clear)
_JokerDoom has quit [Read error: Connection reset by peer]
_JokerDoom has joined #ocaml
<nicoo> I've had a look at what The Manual promises about the FFI, and it seems it is possible to do the change without breaking (well-behaved) C code
<ggole> Oh, hmm.
<nicoo> But I'm not sure whether cramming the tags in the pointers is doable in 32bits (because 32-byte alignment is a bit big)
JokerDoom has quit [Ping timeout: 240 seconds]
manud has quit [Quit: Be back later ...]
<ggole> So wrapping and unwrapping are masking of the pointer rather than dereference.
manud has joined #ocaml
AlexRussia has joined #ocaml
<ggole> It's a bit similar to packing nullary constructors.
manud has quit [Ping timeout: 255 seconds]
ontologiae has quit [Ping timeout: 265 seconds]
larhat has quit [Quit: Leaving.]
bytbox has joined #ocaml
<nicoo> ggole: A bit, yes
<nicoo> Also, Foo of (x,y) for an already-allocated tupple becomes alloc-free
<ggole> Yeah, just munge the pointer with the constructor bits
travisbrady has quit [Quit: travisbrady]
pgomes has quit [Quit: Leaving]
ggole has quit []
slash^ has left #ocaml [#ocaml]
<mrvn> nicoo: Foo of (a * b) and Foo of a * b both have a 2-tuple for a * b. In the later case the tuple has the Foo tag, in the former you have another one-tuple with Foo tag pointing at it.
<mrvn> nicoo: Where do you see pointer munging?
kakadu_ has quit [Ping timeout: 246 seconds]
<mrvn> nicoo: The reason why Foo of (a * b) can't be a single 2-tuple is that you can have Foo of (a * b) | Bar of (a * b), let x = (1, "") let foo = Foo x let bar = Bar x. If you munge the constructor into the tuop
<mrvn> tuple then Bar overwrites Foo
* mrvn seems to be missing something on the idea
nicoo has quit [Remote host closed the connection]
nicoo has joined #ocaml
<mrvn> nicoo: On 32bit bits 31-2 are the address and are all relevant. Bit 0 is a tag. I think bit 1 is unused. Do you want to encode the constructor in 1 bit?
larhat has joined #ocaml
<nicoo> mrvn: I don't get where the “overwriting” is occuring in the example you gave
<nicoo> Also, as I said earlier, I was considering increasing the alignment constraints for values (to 32 bytes) to get enough useable bits in the pointers
<nicoo> (on 32 bits platforms)
<mrvn> nicoo: if you represent both types the same, with the tag in the header of the memory block, then Foo and Bar would use the same space and overwrite each other
<nicoo> But the impact of alignment isn't obvious :(
<mrvn> nicoo: misses that. 32 byte align gives you 4 bits. That should work usually.
<mrvn> s/misses/missed/
<nicoo> mrvn: 4 bits isn't enough. The manual guarantees 200-someting variants
<mrvn> nicoo: so big types need the indirection
<mrvn> nicoo: or an extra word in the header
manud has joined #ocaml
<nicoo> mrvn: Non-uniform representation would make the FFI really messy
<mrvn> indeed. that's why most stuff doesn't use it
<nicoo> Also, in the example you gave, foo would be a pointer to x, with some bits encoding the tag for Foo, and bar would be a pointer to x, with some bits encoding the tag for Bar. The tag is never written inside x
<mrvn> nicoo: you said you wanted the same representation, which would use the bits in the header, not in the pointer.
<nicoo> I'm not even understanding that sentence. (It is perfectly possible that I'm tired enough not to make sense)
<mrvn> doesn't matter. I get your idea now. 32bit realy is too small for this.
manud has quit [Ping timeout: 260 seconds]
<mrvn> On 64bit system you usualy have plenty spare bits at the top of the pointer. Not sure what the cost of masking for every pointer access would be though.
<nicoo> That's not completely obvious. I guess I should play with the heap profiler branch to see how the allocation sizes are distributed
<nicoo> mrvn: Mangling pointers (esp. just masks) is fairly cheap, compared to the cost of acccessing memory
<mrvn> How are floats aligned on x86?
<nicoo> They should be at least 16-byte aligned (for SSE & so on)
<mrvn> but does ocaml do that?
matason has joined #ocaml
<nicoo> TBH, it is late enough in the evening that I don't want to dive in the compiler to check
jgjl has joined #ocaml
milosn has quit [Ping timeout: 255 seconds]
michipili1 has joined #ocaml
jabesed has quit [Quit: Konversation terminated!]
michipili has quit [Ping timeout: 244 seconds]
lordkryss has quit [Quit: Connection closed for inactivity]
rgrinberg has joined #ocaml
<nicoo> mrvn: Anyways, thanks a lot for the input :)
<adrien> mrvn: x86_64 mandates SSE2
<adrien> so you need that alignment
ikaros has joined #ocaml
milosn has joined #ocaml
Submarine has quit [Ping timeout: 255 seconds]
rand000 has quit [Quit: leaving]
manud has joined #ocaml
girrig has quit [Ping timeout: 245 seconds]
girrig has joined #ocaml
<nicoo> adrien: The question is whether it is aligned so on x86
<adrien> (probably not :) )
<adrien> also
<adrien> do you really think there would be a dirty but valid trick that wouldn't be taken advantage of by the ocaml runtime?
struktured has quit [Ping timeout: 258 seconds]
ontologiae has joined #ocaml
ontologiae has quit [Ping timeout: 252 seconds]
manud has quit [Quit: Be back later ...]
Hannibal_Smith has quit [Quit: Leaving]
<eyyub> do you believe that mirage will be a "killer-app" for OCaml ?
<Drup> isn't it already ?
<eyyub> Even from outside ?
nox_ is now known as nox
araujo has quit [Ping timeout: 244 seconds]
araujo has joined #ocaml
myyst has quit [Quit: Leaving]
manud has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 264 seconds]
matason has quit [Read error: Connection reset by peer]
rgrinberg has quit [Quit: Leaving.]
myyst has joined #ocaml
<nicoo> adrien: Yes, I really think so.
<nicoo> adrien: The trick I mentionned is valid. The question is “just” knowing what would be the impact of alignment constraints on x86
rgrinberg has joined #ocaml
Simn has quit [Quit: Leaving]
struktured has joined #ocaml
arj has joined #ocaml
jgjl has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
rgrinberg has quit [Quit: Leaving.]
ikaros has quit [Quit: Ex-Chat]
struktured has quit [Ping timeout: 258 seconds]
oscar_toro has quit [Ping timeout: 240 seconds]
lordkryss has joined #ocaml
arj has quit [Quit: Leaving.]
jonludlam has joined #ocaml
Arsenik has joined #ocaml
jonludlam has quit [Ping timeout: 250 seconds]
AlexRussia has quit [Ping timeout: 256 seconds]
manud has quit [Quit: Be back later ...]
keen________ has joined #ocaml
keen_______ has quit [Ping timeout: 245 seconds]
ontologiae has joined #ocaml
ontologiae has quit [Ping timeout: 264 seconds]