gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.1 http://bit.ly/nNVIVH
gnuvince has joined #ocaml
Anarchos has quit [Quit: Vision[0.9.7-H-090423]: i've been blurred!]
ulfdoz_ has joined #ocaml
sepp2k has quit [Remote host closed the connection]
ulfdoz has quit [Ping timeout: 264 seconds]
ulfdoz_ is now known as ulfdoz
madroach has quit [Ping timeout: 265 seconds]
madroach has joined #ocaml
n00b6502 has joined #ocaml
<n00b6502> ocaml vs haskell.. vs lisp.. any opinions?
<wmeyer> n00b6502: all nice
<n00b6502> is |> unique to F#
<wmeyer> nope, it's just a combinator, you can define it yourself
<wmeyer> infix function application
<n00b6502> ah great so ocaml has that
<wmeyer> it has even builtin support
<n00b6502> (i made # do that in haskell)
<wmeyer> for performance
<wmeyer> in haskell you have $
<n00b6502> which is the same thing but the other way round i think (in f#, <| ?)
<n00b6502> what appeals about ocaml is the basic object.component syntax being available
<wmeyer> |> yes it's reverse application
<wmeyer> object # method ?
<n00b6502> even just record access
<wmeyer> module . field
<wmeyer> haskell has first order selectors
<n00b6502> i'm in 2 minds about haskell
<n00b6502> mostly amazing , but it seems a lot of complexity re-appears to do basic things
<wmeyer> agreed
<wmeyer> so go for OCaml
<n00b6502> seems to me the main 'payoff' of fp is how concisely you can do things with lambdas , partial application... saves alot of the creation of temporary objects that you do in C++ and elsewhere
<wmeyer> yes, remember gc, and no explicit allocation
<wmeyer> so these things will not happen without runtime support
<wmeyer> even though C++0x11 have lambdas
<wmeyer> of course nobody is insane to return them
<n00b6502> you'd have to be careful about referencing stack data for sure..
<wmeyer> you could allocate it on heap, but then no longer you forget about it, and BTW: you still need to allocate the environment on the heap
<n00b6502> ok let (|>) a b = b a
<wmeyer> yep
<n00b6502> ;; is a bit weird to see but i can cope with that
<wmeyer> in fact: external (|>) = "%revapply"
<wmeyer> you don't need it
<wmeyer> in toplevel yes, but normally i never use it
<n00b6502> you have to write "List.map", is there a way to bring a module into the namespace, or would i need to make an alias to just write map f ...
<wmeyer> open List
<wmeyer> module L = List
<wmeyer> List.(map f l)
<wmeyer> let open List in map f l
<n00b6502> neat.
<wmeyer> but the advice is not to do it
<wmeyer> for some modules it feels right
<wmeyer> open Format
<wmeyer> is probably a good practice
<n00b6502> List seems so fundemental ... map deserves its place
<wmeyer> yes, but in ML you don't have overloading
<wmeyer> so the type inference is principal
<wmeyer> you get principal type
<wmeyer> and that will work
<wmeyer> with type classes you trade function level annotations for local annotations
<n00b6502> does "list" bring in many unexpected symbols then
cacho has quit [Ping timeout: 246 seconds]
<n00b6502> how is ocaml for range of implementations... i guess most of the knowledge would go across to F#
<wmeyer> so you have OCaml, Standard ML, F#
<wmeyer> there is one OCaml
<wmeyer> which has somewhat neater type system than SML and have no standard
<n00b6502> is F# really ocaml.net .. or are there many microsoft extentions
<wmeyer> many
<wmeyer> but some people actually write code for both in the same codebase
<n00b6502> superset of ocaml? o do they remove anything
<wmeyer> with minot tweaks
<wmeyer> they overlap
<n00b6502> ok
<wmeyer> OCaml has: objects, polymorphic variants, first class modules
<wmeyer> none of these is in F#
<n00b6502> i've never written anything serious outside of c/c++
<wmeyer> (objects are, but different)
<wmeyer> and the biggest thing, funky module system, with functors
<wmeyer> is AFAIK not present in F#
<wmeyer> but is recognisable featue of SML
<wmeyer> (somebody might correct me)
<wmeyer> so the modules are cornerstone of ML
<n00b6502> has all the type inference i think, thats nice
<wmeyer> OCaml is practical
<wmeyer> as F#
<wmeyer> but if you want fast native code, then just go for OCaml
<wmeyer> there are extremely performant SML compilers too, like Mlton
<wmeyer> (that does weird things like partial specialisation - full text program optimisation)
<wmeyer> F# is also good in terms of performance AFAIK
<n00b6502> is there an LLVM backend for ocaml (i gather GC and LLVM may not mix, but i've heard of people using shadow stack..)
<wmeyer> Haskell has also good performance especially for functional code
<wmeyer> there is some experimental one
<n00b6502> ocaml seems to have most of the good stuff i encountered in haskell so far.. tuples, destructuring tuples as arguments
<n00b6502> does look like ocaml has most of what I liked in haskell, minus the bits that irritated me :)
<wmeyer> many people concur that here :)
<wmeyer> you still can write monadic code
<wmeyer> and emulate laziness
<wmeyer> it will not be as efficient but still I don't think OCaml is suboptimial generally vs. Haskell
<n00b6502> i dont "think" in laziness yet, so its probably not an issue for me
<wmeyer> C++ was fun back in a days, until I started OCaml
cacho has joined #ocaml
<wmeyer> it's ocassionally useful
<wmeyer> but i prefer not to be forced
<n00b6502> not a showstopper, but can one get ocaml onto iOS and android
<wmeyer> yes, you can
<wmeyer> there is a port
<wmeyer> for both
<wmeyer> s/is/are/
<n00b6502> ah great
<wmeyer> iOS port is in production
<wmeyer> android perhaps less so
<wmeyer> (but no hard data, you'd need need to check it yourself)
<n00b6502> ocaml originates 1996 ?
<wmeyer> yes
<wmeyer> so there was CAML
<wmeyer> written in Lisp
<wmeyer> then Camllight come, a C interpreter for CAML dialect
<wmeyer> came*
<wmeyer> then OCaml came with a native compiler
<n00b6502> is there a perfix form of multiply .. (*) is telling me its a comment
<wmeyer> ( * )
<wmeyer> yes it's clumsy, but it's not too bad
<n00b6502> i'd define a mul, add etc for sanity perhaps
<wmeyer> it's ok to always separate tokens with space
<wmeyer> these functions are for instance in Int or Float module
<wmeyer> or Int64, Int32
<wmeyer> so you can do: List.fold_left Int32.add Ol [1;2;3;4;5;6;7;8]
<wmeyer> so you can do: List.fold_left Int32.add Ol [1l;2l;3l;4l;5l;6l;7l;8l]
<wmeyer> (correction)
<n00b6502> ok neat
<wmeyer> I know it might be annoying with no overloading
<wmeyer> so 1 * 2.
<wmeyer> won't type check
<wmeyer> 1. * 2.
<wmeyer> will also not
<n00b6502> if you made an let add a b = a+b ;; ... would that infer the types correctly in List.fold_left add 0l [10l;20l;30l]
<wmeyer> 1. .* 2. will do the trick
<wmeyer> nope
<wmeyer> + is for Int
<wmeyer> int type
<wmeyer> not for int32
<n00b6502> what is 'Int' usually ... platform/implementation dependant ?
<wmeyer> yep, on 32 bit platform is 31 bits for instance
<n00b6502> tagged memory ?
<wmeyer> exactly.
<wmeyer> so the OCaml gc is of course precise
<wmeyer> and runtime needs to be able to traverse the structurures
<wmeyer> therefore it needs to know how to disinguish between a pointer and integer
<wmeyer> it has performance consequences
<wmeyer> both good sides and bad sides
<wmeyer> the bad side is that everything apart from int is boxed
<wmeyer> but otherwise the allocations is very cheap
<n00b6502> needs extra instructions to unpack ?
<wmeyer> needs allocation per float, int32 etc.
<wmeyer> to unpack needs dereference
<wmeyer> you might think it sucks
<wmeyer> in fact is not too bad
<n00b6502> there's probably synergy between immutable and GC
<n00b6502> i gather
<wmeyer> yes, you are right
<wmeyer> C/C++ prefers to mutate data, because can't allocate anything :-)
<wmeyer> well it can, but you know what that means in practice
<wmeyer> copying, smart pointers, or manual pointer shuffling
<n00b6502> very different mindset.
<wmeyer> yes :)
<n00b6502> i wouldn't go near anything with gc, but the synergy appears to be (GC + multithread + immutable)
<n00b6502> ^usually wouldnt
<wmeyer> yes, it goes this direction
<n00b6502> i'm trying to think why its 'ocaml' i tried last.. haskell has more limelight?
<wmeyer> or (manual mem, locks, mutable)
<wmeyer> I dunno :-)
<wmeyer> Haskell is kind of king of functional languages
<wmeyer> and have very academic community
<wmeyer> and somewat bigger than OCaml
<wmeyer> people usually like to be on the edge
<wmeyer> and either something perfect or nothing
<wmeyer> i don't know what is exactly a problem
<n00b6502> might sound strange but i find the loss of "." operator for record acess very offputting. i think it would make interfacing with conventional libraries seem awkward
<wmeyer> maybe people's mindset
<wmeyer> dot operator is practical
<wmeyer> but selectors in OCaml are not first class
<wmeyer> you can't say
<wmeyer> type t = { lhs : string; rhs : int }
<wmeyer> lhs { lhs="x"; rhs=42}
<wmeyer> and pass lhs somewhere
<wmeyer> you need to say { lhs="x"; rhs=42}.lhs
<n00b6502> need to wrap in a lambda i guess
<wmeyer> which is sometimes nicer
<wmeyer> but sometimes you want a first class selector
<wmeyer> however in practice is not a big deal
<wmeyer> let get_lhs { lhs } = lhs
<n00b6502> i would definitely prefer . behaving like in regular languages
<wmeyer> get_lhs { lhs="x"; rhs=42}
<n00b6502> i'm ok with that
<wmeyer> but then you can do List.map lhs
<wmeyer> not List.map (fun {lhs} -> lhs)
<wmeyer> or List.map (fun x -> x.lhs)
<wmeyer> it depends, but it does not hurt me either :)
<n00b6502> put it this way. when i've looked into Lisp, i can handle prefix maths just fine. but loss of "." really grates. same with haskell- everything is amazing but then i just found loss of "." starting to feel very unnatural. i think to have most of what those have... but with "." as per normal langugaes would be awesome
<wmeyer> yes, it's nice that OCaml can look like C too :)
<wmeyer> and like Haskell too :)
<wmeyer> ok, i gtg, I will be zombie at my daytime job, see you next day?
<n00b6502> ok
<n00b6502> thanks for the info
<wmeyer> (not your fault, I got another chat too)
<wmeyer> ok good night!
mattrepl has quit [Quit: mattrepl]
MiggyX has joined #ocaml
gnuvince has quit [Ping timeout: 252 seconds]
gnuvince has joined #ocaml
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Excess Flood]
Progster has joined #ocaml
Progster has quit [Client Quit]
<n00b6502> ah ocaml needs +. *. for floats insteaed of + *
<n00b6502> every language has something really weird in it :)
<pippijn> n00b6502: overloading doesn't work well with ocaml's type system
<pippijn> n00b6502: you could make a polymorphic +, but then it works on all types
<pippijn> if + worked for int and float, then what would the type of (+) be?
<n00b6502> a -> a ... but ... the language that does that has a broken record system :)
<n00b6502> (a-> a-> a sorry)
<pippijn> no, then it would work for everything
<pippijn> like the ordering and equality operators
<pippijn> val ( + ) : 'a -> 'a -> 'a = <fun>
<n00b6502> oh so its only the addition of haskell typeclasses that allows it ? Num a => a-> a-> a
<pippijn> that's one way, yes
<pippijn> ocaml has classes that could be abused for such a thing
<n00b6502> i thnink i could probably cope with +. *.
<pippijn> I find myself using floats pretty rarely
<n00b6502> strings mostly ?
<n00b6502> heh 3d graphics... vector types mostly
<n00b6502> i guess the typeless languages just produce lots of runtime errors from allowing + on anything
<pippijn> n00b6502: mostly strings, yes
targetron has joined #ocaml
Fnar has joined #ocaml
thomasga has joined #ocaml
ankit9 has joined #ocaml
<targetron> can you declare multiple local variables in one line?
<_habnabit> let x = 1 and y = 2 in ...
<n00b6502> not just comma ? is and an operator ?
<_habnabit> yes
<n00b6502> whats bitwise or logical and
<n00b6502> & && like c perhaps
targetron has quit [Quit: Leaving]
<adrien> lor, land
<_habnabit> && is logical
<_habnabit> and yeah, bitwise operators don't use symbols
<adrien> "&" and "&&" are the same, and "or" and "||" are the same
<adrien> "&" and "or" are deprecated however
<adrien> and _please_ don't use them
<pippijn> doing this more neatly would be easy in ocaml, but in C++, it would just get longer
ftrvxmtrx has quit [Quit: Leaving]
Cyanure has joined #ocaml
chambart has joined #ocaml
Yoric has joined #ocaml
cago has joined #ocaml
ankit9 has quit [Ping timeout: 264 seconds]
ocp has joined #ocaml
ocp has left #ocaml []
ankit9 has joined #ocaml
mika1 has joined #ocaml
chambart has quit [Ping timeout: 268 seconds]
Cyanure has quit [Remote host closed the connection]
ftrvxmtrx has joined #ocaml
BiDOrD has joined #ocaml
BiDOrD_ has quit [Read error: Operation timed out]
braibant has joined #ocaml
rixed has quit [Ping timeout: 260 seconds]
ontologiae has joined #ocaml
chambart has joined #ocaml
sivoais has quit [Ping timeout: 248 seconds]
chambart has quit [Ping timeout: 246 seconds]
chambart has joined #ocaml
cdidd has quit [Ping timeout: 246 seconds]
ontologi1e has joined #ocaml
ontologi1e has quit [Read error: Connection reset by peer]
ontologiae has quit [Read error: Connection reset by peer]
ontologiae has joined #ocaml
eni has joined #ocaml
MiggyX has quit [Quit: MiggyX]
<n00b6502> 31bit ints / tagged memory scares me a bit
<adrien> why?
<n00b6502> e.g. gc should be possible another way .. does it vary between implementations
<adrien> between implementations of what?
<n00b6502> ocaml itself (or is there just the one)
<adrien> there's one main implementation
<adrien> then the other implementations usually implement ocaml plus some changes
<adrien> i.e. feature forks
<n00b6502> 95% of my impression is posative
<n00b6502> e.g. its got everything i like about haskell, but with bonus of sane 'structs' and . accessor
<n00b6502> was the explanation correct that one bit is reserved to distinguish pointers
<n00b6502> for compacting GC scan
<adrien> well, if you're interested in ocaml's internals, you can read https://rwmj.wordpress.com/tag/ocaml-internals/ :-)
<flux> n00b6502, well, it does vary in the sense 64-bit platforms have 63-bit integers :)
<n00b6502> heh.
djcoin has joined #ocaml
<n00b6502> i guess i have to spend a few years building my own language to get everything the way i want it
djcoin has quit [Client Quit]
<flux> if you do actually need 32-bit integers, they do exist. sadly they are not that convenient to use.
<adrien> n00b6502: actually, you could look at HLVM, it's really an implementation thing but garbage collectors aren't trivial
<n00b6502> an llvm based implmenetation.. i gather llvm isn't designed for gc languages but it can be fudged
<n00b6502> is it 31 bits of float too
<adrien> I don't know if Int32 can be unboxed
<adrien> also, you might want to look at ATS if you want to avoid running a GC pretty often :P
<n00b6502> i would guess its possible to make an implementation where tag bitfields are in arrays parallel to the main heap...
<n00b6502> just googling ATS ocaml now..
<n00b6502> what problems does OCaml suit ? i became interested in FP from dealing with parallelism in C++
eni has quit [Ping timeout: 246 seconds]
djcoin has joined #ocaml
djcoin has quit [Quit: WeeChat 0.3.7]
djcoin has joined #ocaml
<flux> n00b6502, floats are boxed when stored, also ocaml only has doubles, although they are called floats
<n00b6502> ouch ok
<flux> (they are not boxed in arrays or records of floats or when they are optimized in loops)
Yoric has quit [Ping timeout: 244 seconds]
<n00b6502> thats tolerable i guess
sivoais has joined #ocaml
<adrien> there are a few tricks to help the compiler and it's something that is being improved
<n00b6502> i guess in F# things may be different
sepp2k has joined #ocaml
<ontologiae> n00b6502: not the same amount of $ to develop optimization on the compiler, too
sivoais has quit [Ping timeout: 260 seconds]
<djcoin> Hey maybe you should change the title of the channel to OCaml 4 :)
<djcoin> s/you/someone
<n00b6502> are there any ocaml implementations that emit C as intermediate ... haskellers dislike that idea but perhaps not being lazy it suits ocaml better
err404 has joined #ocaml
chambart has quit [Ping timeout: 244 seconds]
sivoais has joined #ocaml
fraggle__ has joined #ocaml
fraggle__ has quit [Client Quit]
err404 has quit [Ping timeout: 246 seconds]
cago has quit [Quit: Leaving.]
<ontologiae> n00b6502: ocaml comiler has an option to emit C-- in LISP syntax
_andre has joined #ocaml
err404 has joined #ocaml
<ousado> ATS has a GC but can also live without it
<ousado> and compiles to C
<ousado> and has unboxed versions of records, tuples, basic types
<hcarty> n00b6502: let x, y = 1, 2 in ... also works for naming multiple values together
<n00b6502> thanks
err404 has quit [Remote host closed the connection]
mika1 has quit [Ping timeout: 246 seconds]
Ptival has joined #ocaml
mika1 has joined #ocaml
chambart has joined #ocaml
cago has joined #ocaml
chambart has quit [Ping timeout: 276 seconds]
chambart has joined #ocaml
gnuvince has quit [Ping timeout: 264 seconds]
emmanuelux has joined #ocaml
chambart has quit [Ping timeout: 246 seconds]
gnuvince has joined #ocaml
<nicoo> ousado: Yes, I've been playing with ATS, it is fun
smondet has joined #ocaml
<ousado> nicoo: yeah
<ousado> nicoo: ATS2 is in the making currently, improving some flaws of ATS
<nicoo> Oh, nice
<nicoo> ousado: Is there a dev. version somewhere ?
<ousado> just the type-checker, AFAIK
<nicoo> Ah, ok
<ousado> e.g. better support for templates, read-only viewtypes, pluggable constraints-solver, non-linear constraints
<nicoo> Hmmm, nice :°)
<ousado> and HXI said he'd finish it this summer
<ousado> so there should be news soon
<nicoo> Thanks
<flux> is the standard library still gpl?
<flux> (of ATS)
<ousado> just looking at prelude of ATS2
<ousado> LGPL
diego_diego has joined #ocaml
<ousado> I'm pretty sure he'd just change it if someone asks
<ousado> .. hm.. LGPL is not sufficient, since there are templates involved
diego_diego has quit [Client Quit]
ankit9 has quit [Quit: Leaving]
<ousado> looks quite active
<djcoin> WHy would people make stuff GPL or LGPL :\ I guess it's a bit early and does not help the spread of ocaml
<ousado> djcoin: ATS is another language, and I think the author just used the same header for everything
<djcoin> oh sorry, did not dig the link
<ousado> it's a research project becoming "real" currently
<ousado> and he's very interested in adoption, so I don't think he'll introduce any showstoppers deliberately
<ousado> there's ##ats, btw
smondet has quit [Remote host closed the connection]
fasta_ is now known as fasta
rwmjones is now known as rwmjones_hols
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
smondet has joined #ocaml
smondet has quit [Remote host closed the connection]
smondet has joined #ocaml
ChristopheT has joined #ocaml
bzzbzz has quit [Remote host closed the connection]
err404 has joined #ocaml
eni has joined #ocaml
cago has quit [Quit: Leaving.]
mika1 has quit [Quit: Leaving.]
b` has joined #ocaml
<b`> Hello, what is the popular way in ocaml to generate bindings for external C functions? I am wondering how bindings with large num of functions such as ocaml-allegro were produced
Submarine has quit [Remote host closed the connection]
chambart has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
<adrien> by hand, maybe helped by a tool
<b`> tool such as swig?
<b`> or any other suggestion please?
<adrien> no, not swig, please! :P
<adrien> swig makes ugly code
<adrien> swig is ugly
<adrien> swig was targetted at C++ and python, when you controlled both sides
<adrien> as for which tools, it depends on the data you have at hand
<adrien> for instance, for lablgtk2, there is a generator that uses data extracted from gtk-doc's output
<flux> there's this other tool I can't remember
<adrien> cowboy! :P
<adrien> forklift, but good luck finding it (and it's not in a terribly good shape)
cdidd has joined #ocaml
<flux> no, something else..
<adrien> ah, idl
<adrien> ocaml-idl (or with no dash)
<flux> yeah, that
<adrien> the issue is that pretty often, you won't get a native API
<adrien> if you use generic tools (swig, ocamlidl), expect a generic API :-)
<b`> thanks, i will have a look at these. I am trying handcoding too but I get terse segfault messages right now, so was looking at automating
thomasga has quit [Quit: Leaving.]
thomasga has joined #ocaml
rwmjones_hols has quit [Ping timeout: 268 seconds]
chambart has quit [Ping timeout: 244 seconds]
err404 has quit [Remote host closed the connection]
chambart has joined #ocaml
sepp2k has quit [Ping timeout: 246 seconds]
ontologiae has quit [Read error: Connection reset by peer]
ontologiae has joined #ocaml
<adrien> b`: generators aren't magic (or sometimes, they are, especially swig) and you can't expect them to always work so it's good to learn to do it by hand
ftrvxmtrx has joined #ocaml
sepp2k has joined #ocaml
osa1 has joined #ocaml
eni has quit [Ping timeout: 264 seconds]
chambart has quit [Ping timeout: 244 seconds]
<flux> wish there was a library for building c/c++/ocaml bindings, though
<flux> there are many things to screw up.
osa1 has quit [Quit: Konversation terminated!]
<adrien> at runtime?
eni has joined #ocaml
tlockney has quit [Excess Flood]
tlockney has joined #ocaml
Kakadu has joined #ocaml
pangoafk is now known as pango
ontologiae has quit [Ping timeout: 244 seconds]
<b`> i am ending up learning C finally
djcoin has quit [Quit: WeeChat 0.3.7]
Xizor has joined #ocaml
<n00b6502> what are the limitations on getting data between ocaml & c
<n00b6502> given GC vs non GC worlds
<flux> if it's allocated by ocaml allocation functions, it should be followable from the gc roots
<flux> you should also now keep non-gc-maintained pointers to such data in C, because gc can move data
<n00b6502> i guess if you're just throwing values through API calls its easier
<flux> yes.
thomasga has quit [Quit: Leaving.]
<flux> especially if they are basic values, not records etc
b` has quit [Remote host closed the connection]
<ousado> not sure how old this is, but it looks like it's covering a number of questions WRT C interop http://www.linux-nantes.org/~fmonnier/ocaml/ocaml-wrapping-c.php
<flux> I'm pretty sure the principles haven't changed for quite a while
<flux> it has changed that it used to be slow to have many gc roots, nowadays it's not that costly
jave has quit [Read error: Operation timed out]
<adrien> if the ffi changed even the slightest, the breakage would be funny to watch :P
jave has joined #ocaml
<ousado> did ocaml always have a moving GC?
<flux> maybe not, but it has had it for very long
<flux> adrien, yeah, there should be more macros and functions to hide details, to enable changes
ChristopheT has quit [Ping timeout: 246 seconds]
ChristopheT has joined #ocaml
Christop` has joined #ocaml
Christop` has left #ocaml []
ChristopheT has quit [Client Quit]
ChristopheT has joined #ocaml
Yoric has joined #ocaml
Fnar has quit [Remote host closed the connection]
gnuvince has quit [Ping timeout: 260 seconds]
Xizor has quit [Ping timeout: 260 seconds]
gnuvince has joined #ocaml
osa1 has joined #ocaml
chambart has joined #ocaml
sivoais has quit [Ping timeout: 268 seconds]
chambart has quit [Ping timeout: 276 seconds]
_andre has quit [Quit: leaving]
osa1_ has joined #ocaml
osa1 has quit [Read error: Connection reset by peer]
osa1_ has quit [Ping timeout: 245 seconds]
sivoais has joined #ocaml
gnuvince has quit [Ping timeout: 245 seconds]
osa1 has joined #ocaml
eni has quit [Quit: Leaving]
barronax has joined #ocaml
thomasga has joined #ocaml
Yoric has quit [Ping timeout: 246 seconds]
sexymale has joined #ocaml
<sexymale> hi all
osa1 has quit [Quit: Konversation terminated!]
<barronax> Anyone know how to complete data input for I/O functions like read_int in the tuareg mode? When I press RET, tuareg waits until I complete the line with ";;", which messes up input processing.
<thelema> barronax: the best I have is to not run your program under tuareg/emacs
<barronax> Gah, I was hoping that wouldn't be the answer! :-)
sexymale has quit []
<ChristopheT> barronax: Please file a bug at https://forge.ocamlcore.org/projects/tuareg/
osa1 has joined #ocaml
djcoin has joined #ocaml
Kakadu has quit [Quit: Konversation terminated!]
ChristopheT has left #ocaml []
Sablier has quit [Remote host closed the connection]
osa1 has quit [Ping timeout: 246 seconds]
lazythunk has joined #ocaml
barronax` has joined #ocaml
barronax has quit [Ping timeout: 276 seconds]
thomasga has quit [Quit: Leaving.]
lazythunk has quit [Quit: lazythunk]
fds has quit [Quit: Working.]
ftrvxmtrx has quit [Ping timeout: 240 seconds]
Yoric has joined #ocaml
ftrvxmtrx has joined #ocaml
djcoin has quit [Quit: WeeChat 0.3.7]
<thelema> Is anyone here going to OUD who can share a room?
Yoric has quit [Ping timeout: 244 seconds]
<nicoo> thelema: I only I could go :)
<dsheets> thelema: I am going but don't have lodging plans on Wed,Thurs,Fri,Sat nights
<barronax`> I've noticed the following idiom (http://codepad.org/8Z4hKl3v) in the standard library quite a bit, and I'm not sure why you would write code like that.
emmanuelux has quit [Remote host closed the connection]
emmanuelux has joined #ocaml
<thelema> barronax`: sequencing
<thelema> barronax`: if written the second way, the function will be applied to list elements in reverse order
emmanuelux has quit [Remote host closed the connection]
<barronax`> thelema: So if the f argument had side-effects you'd possibly have a problem? The acutaly construction of the list seems equivalent, but I guess the evaluation order changes
<barronax`> Oh, I see.
<barronax`> In map (function x -> print_string (string_of_int x) ; x+1) [1; 2; 4];;
<barronax`> The first returns 421.., the second 124. Hehe
emmanuelux has joined #ocaml
<thelema> the evaluation order of ocaml expressions is officially undefined, but for efficiency is implemented as right to left
<barronax`> Thanks thelema.