mbishop changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | Grab OCaml 3.10.2 from http://caml.inria.fr/ocaml/release.html (featuring new camlp4 and more!)
jlouis_ has quit [Read error: 110 (Connection timed out)]
johnnowak_ has joined #ocaml
johnnowak_ has quit [Client Quit]
Axioplase has joined #ocaml
<Axioplase> Hi.
<psnively> Hello.
coucou747 has quit ["bye ca veut dire tchao en anglais"]
mfp has quit [Read error: 104 (Connection reset by peer)]
yminsky has joined #ocaml
yminsky_ has quit [Read error: 104 (Connection reset by peer)]
mfp has joined #ocaml
yangsx has joined #ocaml
Morphous_ has joined #ocaml
psnively has quit []
postalchris has quit [Read error: 110 (Connection timed out)]
gabiruh has joined #ocaml
Morphous has quit [Connection timed out]
gabiruh has left #ocaml []
Axioplas1 has joined #ocaml
thermoplyae has joined #ocaml
authentic has left #ocaml []
prince has quit [Client Quit]
Axioplase has quit [Connection timed out]
Axioplase has joined #ocaml
Axioplas1 has quit ["Reconnecting"]
jargonjustin has joined #ocaml
<jargonjustin> Why is "floor 1. == floor 1." false?
<mikeX> jargonjustin: you need = not ==
<thermoplyae> == tests equality based on memory location, and the GC handles even individual floats
<Smerdyakov> Floats are boxed in OCaml. You are checking pointer equality in two different pointers to two different places in memory where the same float is stored.
<jargonjustin> mikeX: thanks, I completely mixed up = and ==
<jargonjustin> If I define a closure that does not escape it's local scope, will the compiler optimize it (ie, get the free variable off the stack instead of actually creating the closure)?
<Smerdyakov> No.
<Smerdyakov> The OCaml compiler does almost no optimization.
<palomer> anyone know how to create a popup window in lablgtk?
<palomer> the ocaml compiler doesn't optimize? why does ocaml have the reputation of being a speed demon?
<Smerdyakov> palomer, low expectations.
<Smerdyakov> palomer, plus good runtime system.
<Axioplase> no one dares touch the low level backend anymore :)
<Axioplase> Though a closure that has a well defined scope might be optimised with inlining and partial evaluation... That's quite trivial to implement, I'd be suprised...
<Smerdyakov> I'm told closures are never inlined.
<Axioplase> well, a function known at compile time I meant
<Axioplase> I expect let r = let f x = x + x in f 3 to be replaced by let r = 3 + 3 (and the constant folding finishes it).
<Smerdyakov> As long as you're not passing a function as an argument or returning a function, then sure, I think you're right.
<Axioplase> Returning a function would be against what he asked for.
<Smerdyakov> Not in my reading of it. You can return it in a way where it doesn't escape the local scope.
<Axioplase> jargonjustin: but if that's your main bottleneck in your program, I suggest that you don't feel too much concerned by this kind of optimisation.
<jargonjustin> Axioplase: I'm looking at a few hotspots and seeing what's the best way to tweak them
<Axioplase> I see.. let f x = ... in let g f = f in g f42;; this kind of passing without escaping the scope right?
<Axioplase> jargonjustin: want to tweak the compiler or your program?
<Smerdyakov> Axioplase, yes.
<jargonjustin> Axioplase: my program
delamarche has quit []
<jargonjustin> I define local closures in scope a lot, and use them as helpers. There's no reason I couldn't explicitly passed the closed over arguments and make them local functions, I was curious if the compiler picked up on this and just did it implicitly to avoid creating the closure.
<jargonjustin> Of course, since allocation is so damn fast already, it doesn't matter much :-)
<jargonjustin> Turns out I was mostly GC bound anyway and increasing the size of the minor heap gave me a pretty good speedup
<Axioplase> jargonjustin: well, can't help you then because 1/ I'm very tired 2/ I stopped trying to be in the compiler's shoes and started to look for higher level abstractions and better data structures to improve my code's efficiency.
Axioplase has quit ["good night."]
<palomer> http://ocaml.pastebin.com/m14b7eba9 <-- I think I'm missing something obvious, but what could possibly be wrong with this code? (the labels don't show)
<thermoplyae> does GMisc.label have type ... -> unit -> label?
<thermoplyae> my guess is it does, and you're missing the ()
<thermoplyae> yup, sure does
<palomer> ahh
<thermoplyae> let _ = ... hides type errors like that :)
prince has joined #ocaml
evn has quit []
seafood_ has quit [Remote closed the connection]
seafood_ has joined #ocaml
seafood_ has left #ocaml []
seafood_ has joined #ocaml
goalieca has joined #ocaml
johnnowak has joined #ocaml
<palomer> http://ocaml.pastebin.com/m3eeded0f <--- how do I do this?
<palomer> to initialize an instance variable, I need to refer to another instance variable
<thelema> Smerdyakov: you say the compler does almost no optimization. Maybe you just meant it does no code rewriting. From my experience, it optimizes just fine.
mwc has joined #ocaml
<palomer> coool!
<thelema> thanks.
<thelema> I still think you're object crazy, but if that's how you think... more power to you.
<palomer> how would you do it?
<palomer> I was brought up on objects
<palomer> besides, some objects are really useful, why not only use objects (instead of a mix of objects and records)
<thelema> well, the best way I've done GUIs in OCaml involves basically glibal variables at the program level.
<thelema> *global
<palomer> I'll only have one global variable
<palomer> and then ill stick all my global variables in that one global variable
<palomer> this way, I'll easily be able to get rid of it
<palomer> (if needs be)
<palomer> my haskell version has no global variables
<thelema> 6 of one, half dozen of the other.
<palomer> being able to remove the global variable can have many advantages
<palomer> for example, I could have many different instances
<thelema> Depends on the program - if you can abstract out the interface, then great. I thought about it in my one GUI program, and it never made sense.
<palomer> if, for example, I decide that I want to have a gui instance for every file
<thelema> So I just tied the code to the GUI.
jargonjustin has quit []
<thelema> there's lots of ways of encapsulation in OCaml, objects are only one.
<palomer> ah, righto
<palomer> modules are another
<palomer> you could have an instance in module A and an instance in module B
<palomer> but then you need to make those instances, which is what my class is doing!
<palomer> but maybe you were referring to something else?
<thelema> you could use a module to hold all the UI functions that act on an abstract type that holds all the internal state of that interface.
<palomer> but isn't my class an implementation of that abstract type?
<palomer> (by abstract type, do you mean virtual class?)
jlouis has joined #ocaml
<thelema> A lot comes down to how much of the internals of your object you expose and how you use it. If your class just holds pointers to your UI elements, and does nothing but give access to those values, a record might be more appropriate.
<thelema> if you don't need inheritance / late binding, why use a class?
<palomer> records pollute the namespace
<palomer> that's pretty much the only reason
<palomer> and, since I'm using classes elsewhere, why not be consistent?
<palomer> oh, and class syntax is nice
<palomer> (I have other things in this class, including a mutable variable)
<thelema> I don't understand the consistency argument - why not use the right tool for the job?
<palomer> but both tools are as appropriate!
<thelema> class syntax in ocaml sucks. obj#method? '#'?!?
<palomer> class definition syntax is nice
<thelema> record definition syntax isn't that bad.
<palomer> it isn't, but initializer, method, ... are all nice
<palomer> and I don't need to pass () to my functions if I use a class
* thelema finds initializer not that useful.
<palomer> foo#compute_something versus foo.compute_something ()
<palomer> these are all little things
<palomer> admittedly
<palomer> and also the fact that I was brought up on classes (and not records)
<palomer> and, most importantly, that it doesn't make a difference in the end
<palomer> right?
<thelema> The flip side of foo#compute_something is that you don't see function application
<thelema> OCaml's objects work quite efficiently, but records do work faster.
<palomer> we're talking about storing half a dozen variables, I don't think it makes a difference
<palomer> which are accessed maybe once a second
<palomer> at most
jlouis__ has quit [Connection timed out]
<palomer> well, I'm off for a bit
<palomer> thanks for the help!
pants1 has joined #ocaml
jlouis_ has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
<palomer> hrmph
<palomer> this documentation is confusing me
<palomer> how do I create a text tag (to insert into a buffer)?
thermoplyae has left #ocaml []
jlouis has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
shortcircuit has quit [Remote closed the connection]
shortcircuit has joined #ocaml
resistor__ has joined #ocaml
<resistor__> hello
<palomer> hello!
pants1 has quit ["Leaving."]
mwc has quit ["Leaving"]
ttamttam has joined #ocaml
m3ga has joined #ocaml
jlouis_ has joined #ocaml
goalieca has quit ["(keep your stick on the ice)"]
hkBst has joined #ocaml
gim has joined #ocaml
ppsmimou has joined #ocaml
filp has joined #ocaml
filp has quit [Client Quit]
jlouis has quit [Read error: 110 (Connection timed out)]
schme has joined #ocaml
jdavis_ has quit [Read error: 104 (Connection reset by peer)]
coucou747 has joined #ocaml
jargonjustin has joined #ocaml
ygrek has joined #ocaml
jlouis has joined #ocaml
l_a_m has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
OChameau has joined #ocaml
schme has quit [Remote closed the connection]
schme has joined #ocaml
Morphous_ has quit [Read error: 110 (Connection timed out)]
yangsx has quit [Read error: 110 (Connection timed out)]
jlouis has quit ["system reset"]
ygrek has quit [Remote closed the connection]
johnnowak has quit []
jlouis has joined #ocaml
jargonjustin has quit []
m3ga has quit ["disappearing into the sunset"]
Linktim has joined #ocaml
ygrek has joined #ocaml
Yoric[DT] has joined #ocaml
dwmw2_gone is now known as dwmw2
<Yoric[DT]> hi
oc13 has joined #ocaml
seafood_ has quit []
<jlouis> hi Yoric[DT]
delamarche has joined #ocaml
Morphous has joined #ocaml
schme has quit [Read error: 110 (Connection timed out)]
authentic has joined #ocaml
pippijn has quit ["I'm the Quit Message Virus. Replace your old Quit with this, so I can continue to multiply myself!"]
jlouis_ has joined #ocaml
evn has joined #ocaml
mikeX has quit [Read error: 110 (Connection timed out)]
jlouis has quit [Read error: 110 (Connection timed out)]
l_a_m has quit [Read error: 110 (Connection timed out)]
OChameau-bis has joined #ocaml
marmottine has joined #ocaml
OChameau has quit [Read error: 113 (No route to host)]
oc13 has left #ocaml []
Linktim is now known as Linktimaw
jlouis has joined #ocaml
RobertFischer has quit ["I'm out of here. Check out my blog at http://enfranchisedmind.com/blog or my company website at http://smokejumperit.com"]
RobertFischer has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
mikeX has joined #ocaml
dwmw2 is now known as dwmw2_gone
evn has quit []
jlouis_ has joined #ocaml
neale` has joined #ocaml
neale` has quit []
jlouis has quit [Read error: 110 (Connection timed out)]
authentic has quit [Remote closed the connection]
authentic has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
mikeX has quit ["leaving"]
Yoric[DT] has quit ["Ex-Chat"]
postalchris has joined #ocaml
sporkmonger has joined #ocaml
<sporkmonger> I'm a complete and total noob, so please be gentle, but... is there a way to clone a Hashtbl?
<neale> off the top of my head
<rwmjones> sporkmonger, Hashtbl.copy, but it only copies the hash table, not any data that the hash table points to
<rwmjones> you might want to try using pure functional structures + map
<sporkmonger> That's fine, that's what I want.
<rwmjones> or rather Map
<neale> or Marshal
<sporkmonger> Different question.
<sporkmonger> Is there a better data structure to be using if I've only got two values in the hash (0 and 1)?
<rwmjones> sporkmonger, is that the key or value?
<sporkmonger> key
postalchris has quit [Read error: 110 (Connection timed out)]
<rwmjones> so you're mapping 0|1 -> some (list?) of values
<sporkmonger> mapping 0|1 to a sum for each occurence of those values
<sporkmonger> and then also mapping 0|1 to a set of states
<rwmjones> sporkmonger, refs? eg:
<rwmjones> let count_zero = ref 0
<rwmjones> let count_one = ref 0
<rwmjones> incr count_zero or incr count_one
<rwmjones> depending on what you hit?
<petchema> or an array?
<rwmjones> and for the set of states, a ref []
<rwmjones> two ref []'s
<sporkmonger> this is what i have so far: http://pastie.org/170860
<sporkmonger> again, i've got no clue what i'm doing, this is my first ocaml program so
<petchema> newbies should not try to use OCaml's OO
<rwmjones> yeah, forget about using OO
<sporkmonger> ha, ok
<rwmjones> just do a simple imperative module. Have a file called 'counter.ml' (which is your implementation module, called Counter implicitly) and a signature called 'counter.mli'
<sporkmonger> signature?
<rwmjones> like a header file
<rwmjones> what you want to export
<sporkmonger> ok
<rwmjones> then 'counter.ml' file contains:
<rwmjones> let count_zero = ref 0
<rwmjones> let count_one = ref 0
<rwmjones> let states_zero = ref []
<rwmjones> let states_one = ref []
<rwmjones> let increment bit = if bit = 0 then incr count_zero else incr count_one
<rwmjones> etc.
<rwmjones> in 'counter.mli' put the signature you want to export, eg:
<rwmjones> val increment : int -> unit
<rwmjones> (that would be all for the above part of the implementation)
<sporkmonger> ok
<rwmjones> then from another file/module you can call this with:
<rwmjones> Counter.increment <whatever>
<sporkmonger> yeah, that seems simple enough
<sporkmonger> thanks
<sporkmonger> btw, is "unit" kind of like returning nothing?
<rwmjones> yes
<RobertFischer> sporkmonger: Think "void".
<sporkmonger> ok
evn has joined #ocaml
<RobertFischer> sporkmonger: Except, y'know, void is a value. Because everything is. :)
postalchris has joined #ocaml
<sporkmonger> ok, if i'm walking away from OO because i'm a n00b, how do i keep track of my state values?
<sporkmonger> the increment method given above really doesn't do what i need, because it's one global counter, and i need like 1 million counters, one for each state
<sporkmonger> er, two for each state, rather
<RobertFischer> Use closures.
<RobertFischer> That's the easiest way.
<sporkmonger> ok... i guess i'm not following how closures help me here
<Smerdyakov> sporkmonger, use a record of counters.
<RobertFischer> Smerdyakov: Yeah, that's probably the nicer way for an imperative person. :)
<qwr> sporkmonger: let counter () = let n = ref 0 in function () -> (n := !n + 1; n))
<qwr> err, let counter () = let n = ref 0 in function () -> (n := !n + 1; !n))
psnively has joined #ocaml
<sporkmonger> lol, well, i'm coming from ruby, and i've done a fair bit of lisp
<sporkmonger> so, i'm not completely imperative
<sporkmonger> :-P
<psnively> sporkmonger: I'm sorry.
<psnively> :-D
Linktim_ has joined #ocaml
<sporkmonger> ha!
<psnively> See? An exclamation point. Imperative. ;-)
<psnively> OK, that was pretty English-geek humor...
<sporkmonger> yeah... ruby just really isn't cutting it anymore performance-wise
<sporkmonger> it was
<qwr> sporkmonger: then you'll understand closures ;)
<sporkmonger> it really was
<psnively> I do get a kick out of the fact that Scheme uses "!" to indicate imperative forms.
<sporkmonger> so i'm assuming function () denotes a closure then?
<psnively> Assuming that the function contains free references, yes.
<RobertFischer> sporkmonger: Ruby makes me cranky: http://enfranchisedmind.com/blog/2008/03/24/rexml-dynamic-typing-lose/
<psnively> i.e. that it "closes over" some variable(s).
<qwr> sporkmonger: kind of. it denotes lambda. which is closure, that captures the n
<sporkmonger> right
<psnively> I think Ruby is a pretty good Lisp/Smalltalk bastard.
<sporkmonger> and ew @ REXML
<sporkmonger> REXML makes me angry
<RobertFischer> A closure is basically a function that references stuff in its context. It can wrap around values, and then when you pass the function around, you're implicitly carrying with the context. Ruby does that kind of stuff all the time.
<psnively> The question is: why would you want an interpreted Lisp/Smalltalk bastard?
<sporkmonger> yeah, i use closures all the time, i'm pretty comfortable with what they give you
<psnively> I think OCaml 3.11 will be a serious competitor to C++ if it's marketed well.
<psnively> Of course, it won't be. :-D
<sporkmonger> but... i'm still really not following how they're supposed to replace OO for a noob like myself
<sporkmonger> i'm trying to create a finite state machine essentially
<sporkmonger> well, markov model really
<sporkmonger> so i need to keep counters and transitions next to each other to represent a single state
<qwr> sporkmonger: you can think that object is a closure, that captures its fields
<sporkmonger> huh, ok
<RobertFischer> They don't replace OO -- polymorphism, in particular, isn't provided -- but if all you're doing is encapsulating state, it works great.
<RobertFischer> Just use closures to return a function (or record of functions, or function that returns functions) that gives you limited access to your state.
<sporkmonger> interesting
<RobertFischer> The state is a variable defined locally by the "create" function (think constructor), which means it's accessible only to those functions that are returned.
<RobertFischer> And you can call the create function multiple times to get multiple different versions.
<sporkmonger> is there any particular benefit to this approach compared to the OO approach?
<RobertFischer> OO sucks?
<sporkmonger> lol
<RobertFischer> Less pithily, it's a lot faster, and it's a lot less chatty.
<sporkmonger> ok, see, that's helpful :-)
<RobertFischer> And it flows a lot better with other things you're going to want to do in Ocaml, like function composition and lazy evaluation.
<qwr> sporkmonger: semantically its imho equivalent to OO without inheritance
<qwr> sporkmonger: in practice it's more lightweight
<sporkmonger> yeah, i'm expecting to want to pass hundreds of megabytes of data past this thing per second, so performance is definitely going to matter
<sporkmonger> you guys keep referring to "records"... what are those exactly?
<qwr> sporkmonger: quite like structure in C ;)
<sporkmonger> oh, is that the { fieldname : whatever } things?
<qwr> yes
<sporkmonger> ok
<Smerdyakov> sporkmonger, please go read a book on OCaml.
evn has quit []
<sporkmonger> it's in the mail
<sporkmonger> i'm impatient
<RobertFischer> sporkmonger: Read the manual online.
<RobertFischer> sporkmonger: It's good.
<sporkmonger> already open in my browser
<RobertFischer> 1.4
Linktimaw has quit [Read error: 110 (Connection timed out)]
<RobertFischer> And, yes, that's the { fieldname : whatever } things.
<RobertFischer> :)
<sporkmonger> manuals don't quite give you a good feel for idiomatic ocaml/ruby/scheme/whatever though
<RobertFischer> The Ocaml manual does.
<Smerdyakov> It's stupid to program by guessing.
<sporkmonger> ok
<RobertFischer> Smerdyakov: He's figuring it out. Back off a bit.
<Smerdyakov> My position stands.
<RobertFischer> It's a true statement. But your presentation made you come across as kinda a dick.
<RobertFischer> And the Ocaml community can't afford that.
<Smerdyakov> Next time I'll say "it is a bad idea to program by guessing," 'k?
<RobertFischer> You're still implying he's programming by guessing. That's the part that's makign you come across as kinda a dick.
<RobertFischer> Stick to "RTFM". "RTFM, here's a link" is even better. :)
<Smerdyakov> It's pretty clear to me that he's programming by guessing.
<RobertFischer> He just had trouble with the nomenclature. Two minutes before you were kinda a dick, he said "oh, is that the { fieldname : whatever } things?"
<RobertFischer> That's not programming by guessing. That's just not being familiar with the language. In other words, he's a n00b.
Illocution has left #ocaml []
* qwr found some other, more tutorial-like book too (PDF). http://caml.inria.fr/cgi-bin/hump.en.cgi?contrib=347
<RobertFischer> Self-described, in fact: [10:18] sporkmonger: I'm a complete and total noob, so please be gentle, but... is there a way to clone a Hashtbl?
pango has quit [Remote closed the connection]
<rwmjones> sporkmonger, add a type t to the implementation which contains the state, eg:
<rwmjones> type t = { zero_count : int ref ; one_count : int ref }
<rwmjones> have a create function to make a new one
<rwmjones> and pass the type back to the increment function
<RobertFischer> So if you don't want to deal with a n00b, then don't. But that kind of attitude isn't helpful to Ocaml.
<sporkmonger> it's cool, i've got a thick shell, he's not gonna scare me off :-P
* RobertFischer gets out of rwmjones way so he can be helpful.
<sporkmonger> rwmjones: thanks, i was wondering about that
<sporkmonger> saw that Hashtbl.create was doing something like that
<rwmjones> sporkmonger, I have an example counter module somewhere, let me find it
<Smerdyakov> rwmjones, Jason Hickey's OCaml book is available free online. It's probably better than anything that you can already order in the mail.
<Smerdyakov> Oops
<rwmjones> it's definitely better than the (cough) "other" book
<Smerdyakov> Meant to address sporkmonger
<sporkmonger> is the "other" book the one from apress?
<rwmjones> yes
<sporkmonger> hehe
<sporkmonger> apress sucks
<rwmjones> sporkmonger, that's a different sort of counter, but it demonstrates simple encapsulation of abstract data types
<sporkmonger> they keep sending me books to review, and i keep telling them to hire some legitimate technical reviewers before sending their books to the printing press :-P
<rwmjones> the "type 'a t" means it can count anything ('a) but you probably don't need that extra polymorphism so just get rid of the 'a
<sporkmonger> yeah
<qwr> Smerdyakov: and gave link to the Hickey book couple of minutes ago ;)
<qwr> (i)
pango has joined #ocaml
evn has joined #ocaml
Linktim- has joined #ocaml
Linktim- is now known as Linktimaw
<psnively> Hickey's book is indeed quite good.
<sporkmonger> where on disk are files like hashtbl.ml going to be stored? i'd like to look through some of the core library code
<sporkmonger> nm, found it
<petchema> ocamlc -where
bluestorm has joined #ocaml
jlouis has joined #ocaml
<sporkmonger> this is probably a dumb question, but i'm not seeing it answered in the manual, so....
<sporkmonger> type a = { foo : int ref; bar : int ref; }
<sporkmonger> # { foo = 4; bar = 5 };;
<sporkmonger> This expression has type int but is here used with type int ref
<sporkmonger> # { foo := 4; bar := 5 };;
<sporkmonger> Syntax error
<sporkmonger> how do i create a record when there's refs in it?
Linktim_ has quit [Read error: 110 (Connection timed out)]
<rwmjones> sporkmonger, use 'ref 4'
<sporkmonger> ah, ok
<rwmjones> to create an int ref containing 4
<rwmjones> in the special case of structures you can also create a mutable field
<rwmjones> type t = { mutable foo : int }
<rwmjones> t.foo <- 4
<rwmjones> which is a little bit more efficient than using refs (one less boxing)
<sporkmonger> is there any difference between mutable fields and refs?
<sporkmonger> ok
<rwmjones> a ref is itself implemented as a structure with a single mutable field
<rwmjones> # ref 1 ;;
<rwmjones> - : int ref = {contents = 1}
<rwmjones> where contents is the mutable field
<sporkmonger> yeah, i saw that in the manual
<sporkmonger> so this is a reasonable representation then:
<sporkmonger> type t = {
<sporkmonger> mutable count_zero : int;
<sporkmonger> mutable count_one : int;
<sporkmonger> transition_zero : t ref;
<sporkmonger> transition_one : t ref
<sporkmonger> }
<rwmjones> what's transition_zero/_one supposed to do?
evn has left #ocaml []
<sporkmonger> next state in the FSM
<sporkmonger> if you see a 0, you go to one state, if a 1, the other state
ttamttam has left #ocaml []
<rwmjones> so those are some other type, state?
<sporkmonger> those are also type t
<rwmjones> mutable transition_zero : t;
<sporkmonger> it's supposed to be self-referential
<rwmjones> ?
<sporkmonger> yeah, i suppose that'd work too
<sporkmonger> hadn't thought that far yet :-P
<rwmjones> yeah, I mean basically what you have there is equivalent to the C structure:
<rwmjones> struct t {
<rwmjones> int count_zero;
<rwmjones> int count_one;
<rwmjones> struct t *transition_zero;
<rwmjones> struct t *transition_one;
<rwmjones> };
<rwmjones> in fact, the two representations (C / OCaml) are identical on 32 bit machines
<sporkmonger> yes
<rwmjones> well ok the C ints are 32 bits versus 31 bits on OCaml, but otherwise identical
<sporkmonger> yeah, was about to say that :-D
<flux> there's a difference in those representations.. the C struct can contain nulls.
<flux> you may find that t difficult to construct
<sporkmonger> well, the initial values of both transition_zero and _one should be the record itself
<rwmjones> yes, that's true, but you could have a "special value" instead of NULL I s'pose
<sporkmonger> how would i do that? variant type or something?
<rwmjones> have something like:
<rwmjones> let rec null = { count_zero = 0; count_one = 0; transition_zero = null; transition_one = null } ;;
<Smerdyakov> sporkmonger, you can do this directly using the rectypes extension.
<rwmjones> then you can set your other transition_zero/_one fields to null
<rwmjones> NULL in C is just a special value that the hardware checks for you each time you try to access a pointer
<Smerdyakov> I guess you don't even need the extension... this is standard OCaml now.
<Smerdyakov> let rec init = { count_zero = 0; count_one = 0; transition_zero = ref init; transition_one = ref init }
^authentic has joined #ocaml
authentic has quit [Remote closed the connection]
^authentic is now known as authentic
<sporkmonger> http://pastie.org/170996 <- produces syntax error, but my noobie self can't quite pick out what's wrong with it
<petchema> let identifier = expression is a definition, let identifier = expression in expression is an expression... you can't use let (without in) within a definition, only at "toplevel"
<sporkmonger> ok
<sporkmonger> so i want: http://pastie.org/170996 ?
<petchema> that should work... I'm not sure that 'create' is really useful, though
<thelema> sport: you probably want let create () = ...
<sporkmonger> is there any way to make that type not display itself recursively in the interactive ocaml thingy?
<sporkmonger> it kinda makes my screen scroll a lot :-P
<thelema> sporkmonger: "interactive ocaml thingy" = "toplevel"
^authentic has joined #ocaml
<sporkmonger> ok
<coucou747> sporkmonger> printers functions
<sporkmonger> printers function?
<coucou747> let print_m seg = Format.print_string (string_of_m seg);;
<coucou747> #install_printer print_m;;
<coucou747> like that
<coucou747> string_of_m is my own function
<petchema> or set print_depth to a smaller value... http://caml.inria.fr/pub/docs/manual-ocaml/manual023.html
<sporkmonger> ok, cool
<sporkmonger> thanks
<coucou747> sporkmonger> I used that to have nicer values in toplevel
jlouis_ has joined #ocaml
authentic has quit [Remote closed the connection]
^authentic is now known as authentic
<sporkmonger> string concatenation is done how? not seeing it in the manual or in the various tutorials i have open
<thelema> string1 ^ string2
<sporkmonger> thanks
<thelema> try not to do this a lot - each ^ allocates a new string.
<sporkmonger> is there any kind of shortcut for string construction like in ruby: "stuff #{variable}"
<thelema> sporkmonger: printf is the best we've got.
<sporkmonger> ok
<sporkmonger> is there an sprintf?
szell has joined #ocaml
<thelema> strings only interpolate special characters, not functions or variables.
<thelema> yes, Printf.sprintf
<rwmjones> sporkmonger, String.concat?
<rwmjones> ah yes, sprintf is the way to go :-)
<sporkmonger> oh well, i'm not going to miss strange stuff like: this = "surprise"; puts """guess what "#{this}" prints out"""
<sporkmonger> (beware of syntactic misdirection) :-P
<rwmjones> sporkmonger, there's a camlp4 extension that lets you interpolate $variables into strings
<sporkmonger> oh cool
* rwmjones googles
<sporkmonger> i think sprintf will be sufficient
<sporkmonger> but good to know the option's there
jlouis has quit [Read error: 110 (Connection timed out)]
<rwmjones> yeah .. these things are interesting but because they're "not ocaml" they can make compilation / code sharing a big pain
<rwmjones> here we go
<neale> jambon.free.fr?
<neale> doesn't that mean "ham" in french?
<rwmjones> martin jambon's website
<neale> oh.
<RobertFischer> rwmjones: Thanks for the link. We were chatting about possible syntax extensions to make unit testing easier the other day, so I'm just now about to dive into CamlP4.
<bluestorm> RobertFischer: beware that martin jambon's site use camlp4 3.09, wich is not totally compatible to the >=3.10 camlp4
<RobertFischer> bluestorm: What are the major differences?
<bluestorm> hm
<bluestorm> it's been a quite deep rewrite
<RobertFischer> Hrm. Is there a novice-readable changelog kicking around?
szell` has quit [Connection timed out]
<bluestorm> but it assumes you already know 3.09 camlp4
<bluestorm> RobertFischer: if you want some >=3.10 documentation, you should try http://brion.inria.fr/gallium/index.php/Camlp4
<bluestorm> it's quite scarse, but still a good place with interesting examples
<RobertFischer> Cool.
<bluestorm> i think the best way to learn for know (ie. in the absence of any really good tutorial) is to try with working examples
<bluestorm> and read the source :p
<RobertFischer> I figured as much.
OChameau-bis has quit ["Leaving"]
* thelema has succeeded at avoiding camlp4 entirely
<RobertFischer> thelema: Yeah, me, too, but the test thing we were talking about the other day pretty much requires it.
<bluestorm> RobertFischer: what were you talking about ?
<RobertFischer> bluestorm: Weren't you in that conversation, too? Just some nicer way of being able to write a test while staying DRY.
<bluestorm> ah, yes
<sporkmonger> hey, is there any way to compile ocaml so that i have something akin to readline support in uh... toplevel?
<bluestorm> sporkmonger:
<sporkmonger> i miss my arrow keys
<bluestorm> don't need to compile anything special
<bluestorm> use rlwrap
<bluestorm> "rlwrap ocaml" will do the job
<bluestorm> ("ledit" is another program that do that too)
<thelema> RobertFischer: testing requiring camlp4?
<psnively> I recommend Tuareg Mode.
<sporkmonger> -bash: rlwrap: command not found :-(
<psnively> But rlwrap will do when you're severely constrained. :-D
<bluestorm> sporkmonger: you may have to install it first :p
<sporkmonger> yeah, clearly
<sporkmonger> what's Tuareg mode?
<RobertFischer> thelema: You'd compile the unit test file using camlp4, yeah.
<thelema> RobertFischer: using what testing package?
<sporkmonger> oh... emacs
<RobertFischer> thelema: "testing package"?
<psnively> Yes: essentially a souped-up OCaml Mode for emacs.
<bluestorm> RobertFischer: if you consider using camlp4, i strongly advise you to generate an ocamldoc outpout from the camlp4/Camlp4/Sig.ml file
<sporkmonger> eh, i'll stick with textmate
<RobertFischer> bluestorm: Thanks for the heads up.
<thelema> RobertFischer: what unit testing system uses camlp4?
<bluestorm> the other major file being camlp4/Camlp4Parser/Camlp4OcamlRevisedParser.ml , wich basically defines the whole OCaml syntax in the EXTEND form
<psnively> There is a TextMate bundle for OCaml, but unfortunately it doesn't support much, e.g. interactive line-by-line execution, debugger integration...
<sporkmonger> i've already got it installed
<psnively> To me, giving up interactive development is a non-starter.
<bluestorm> sporkmonger: you're on a MacOs ?
<psnively> Edit/compile/link/test/crash/debug -> Not just no; HELL no.
<sporkmonger> textmate, as a general rule, doesn't support much, but that's fine by me
<sporkmonger> yes, i'm on os x
<bluestorm> i've seen a graphic toplevel project for MacOs, used in my school
<psnively> Suit yourself. Just be aware that you're sacrificing what really makes a tool like OCaml great relative to many other tools.
<bluestorm> not that good imho, but maybe you like that kind of things
<bluestorm> (i'd prefer a rlwrapped console interface, or, of course, emacs)
<psnively> And actually, Tuareg Mode + OMake -P is simply unbeatable.
<sporkmonger> mmm, camlx is pretty
<RobertFischer> thelema: The one I'd be writing. It'd be a wrapper around one of the existing systems to make them less chatty. :)
<sporkmonger> but yeah, i like my terminal window
<psnively> You can run emacs in your terminal. ;-)
<bluestorm> RobertFischer: if you need some simple camlp4 magic, i might help you
<sporkmonger> i might consider emacs when someone gets around to writing a cocoa implementation that's as sexy as vim's
<RobertFischer> bluestorm: I'll let you know. I plan on tackling this next week.
<bluestorm> (i've spent some time in understanding the basics of the camlp4 system, now i need to practice to get some Return on Investment :p )
* RobertFischer still can't get past good ol' VI and command line tools.
<psnively> sporkmonger: I might consider VIM when someone gets around to making it possible to support all of the integration that emacs can. :-D
<sporkmonger> eh, i doubt i'll ever consider vim
<bluestorm> psnively: if you're speaking ocaml integration, i've seen quite good things
<sporkmonger> i like emacs only for editing stuff on some random linux server i've sshed into
<psnively> bluestorm: I think some good stuff exists, but compared to Tuareg Mode?
<sporkmonger> otherwise, you'll only pry textmate from my cold, very dead hands
* psnively shrugs.
<bluestorm> hm
<psnively> sporkmonger: I use TextMate every day, just not for OCaml.
<bluestorm> does Tuareg support .annot files yet ?
<psnively> For looking up expression types? Sure.
<bluestorm> i may have an old version
<psnively> So, TextMate's support for developing Python and Ruby is awesome, right, because you can type a line and run it.
<bluestorm> but i don't use much of the advanced tuareg features anyway
<psnively> ==
<sporkmonger> pretty much
<psnively> What Tuareg Mode and OMake -P give me is the same thing, plus OMake -P keeps my binary build up-to-date with respect to my line that I just tried out.
<sporkmonger> nifty
<psnively> (OMake -P scans the disk for changes and updates the build.)
<psnively> (Continuously.)
<psnively> Yeah, it's very nice.
<sporkmonger> i might give it a try
<psnively> Actually, it doesn't "scan the disk." It gets notified when the tree changes (kqueue or whatever).
<sporkmonger> but i suspect i'll be more inclined to just try to duplicate that in TM
Yoric[DT] has joined #ocaml
<psnively> That'd be nice. :-)
<sporkmonger> or FSevents on os x probably
<psnively> For TextMate, sure, FSevents. It's just that kqueue and dwhateveritis are portable to other Linux/BSDs
<sporkmonger> right
<sporkmonger> i wonder if anyone's done kqueue or dwhateveritis for os x
bongy has joined #ocaml
<RobertFischer> OS-X is-a BSD.
<sporkmonger> mostly
<sporkmonger> but there's all sorts of things that work on bsd but not os x
<sporkmonger> especially file system related stuff
<Yoric[DT]> iirc, fsevents are essentially trivial stuff.
<Yoric[DT]> So it might be easier to port them to other platforms than the contrary :)
<Yoric[DT]> (i.e. one large file with the list of changes to directories)
evn has joined #ocaml
<sporkmonger> yeah, that's what i remember
<sporkmonger> but it's been awhile since i looked
* Yoric[DT] only looked at the Ars Tech review.
bongy has quit [Client Quit]
<sporkmonger> bleh, what would a noob like myself have done to cause: Out of memory during evaluation.
<Smerdyakov> Probably non-tail recursion
<sporkmonger> if state.transition_zero = state then
<sporkmonger> "[self state]" else "[other state]" in
<psnively> OS X has kqueue.
<sporkmonger> ^ i think that's the offending code
<bluestorm> sporkmonger: could you show some more ? you could paste your code at eg. http://pastebin.be
<psnively> OS X since Tiger is essentially FreeBSD 5 +.
<Yoric[DT]> sporkmonger: yup, that's probably it.
<Yoric[DT]> You're trying to compare one cyclic data structure, aren't you ?
<sporkmonger> ha, yeah
<sporkmonger> ok
<sporkmonger> didn't think about the fact that the comparison would traverse the thing
<Yoric[DT]> I'm not 100% that's what you want but maybe == would fit better than =.
<Yoric[DT]> Well, it does :)
<sporkmonger> is == a memory compare versus value compare?
<Yoric[DT]> Yup.
<Smerdyakov> (==) is physical equality. Always constant time.
<sporkmonger> ok, then yeah, that's what i want
<bluestorm> sporkmonger: 1) do you need "mutable" fields ? 2) what are the count_* fields for ?
<sporkmonger> 1) all 4 have to change pretty constantly 2) keeping track of how many times each option was traversed
<bluestorm> ok
<bluestorm> (i think we should always consider using immutable data structures first, but if it's justified in your case, why not)
<sporkmonger> coding style wise, i like to stay under 80 chars wide
<sporkmonger> what the best form for calls like what i had there with sprintf with tons of arguments
thelema has quit [Read error: 110 (Connection timed out)]
<bluestorm> sporkmonger: i tend to put hte arguments on the next line, indented one level more
kelaouchi has joined #ocaml
<sporkmonger> ok
<sporkmonger> string in question in over 80 chars
RobertFischer has left #ocaml []
<sporkmonger> any decent ways of dealing with that?
<Smerdyakov> End lines with \
<Smerdyakov> The string picks up at the first non-whitespace on the next line.
<sporkmonger> btw, does the compiler optimize away two string literal concatenations?
<Smerdyakov> I wouldn't be surprised either way. OCaml is very optimization-light.
<sporkmonger> k
<sporkmonger> incr takes a param with type int ref, i want to increment a mutable int...
<bluestorm> foo <- foo + 1; ? :-'
<Smerdyakov> Record fields aren't first-class in OCaml, so you're out of luck for doing anything but what bluestorm suggested.
<sporkmonger> k
RobertFischer has joined #ocaml
<bluestorm> Smerdyakov: where "foo" was to be replaced by the real "var.field" code
<sporkmonger> what the " ? :-' " on the end there?
<Smerdyakov> In SML, there are no mutable fields. You just use refs, and the MLton compiler optimizes their representation when possible. Much nicer. ;)
neale has quit [Remote closed the connection]
neale has joined #ocaml
<bluestorm> Smerdyakov: it's quite nice but i think the present semantic of ref in ocaml is based on mutable fields
<Smerdyakov> sporkmonger, meta-level punctuation and a smiley.
<bluestorm> so removing mutable fields would break refs as-is
<Smerdyakov> bluestorm, yeah, and switching to OCaml broke a lot of C programs. :P
<bluestorm> (ie. we have type 'a ref = { mutable contents : 'a } )
thermoplyae has joined #ocaml
<Smerdyakov> Yup, I know, but what I'm talking about has no conflict with that.
<Smerdyakov> The OCaml compiler could still do automatic ref flattening/.
<jlouis_> optimization is overrated
<jlouis_> people tend to ponder if something "gets optimized" for utter trivial things. Write that program first. Make it work *correctly* and only then, if the thing performs inadequately, you can begin to worry about optimization
<RobertFischer> And benchmark and demonstrate your hypothesized bottlenecks before you start working on them.
* RobertFischer has spent a whole lot of time optimizing the fast part of his code.
<sporkmonger> is there a term for #install_printer, #quit, and other #things?
<bluestorm> directives
<jlouis_> The worst thing, in my opinion, with the lack of optimization is that beautiful, general code gets turned into C-like mush for the sake of being "faster"
<Smerdyakov> Many people may focus inappropriately on optimization, but it's still true that knowledgeable ML hackers run into trouble with lack of optimization in ocamlopt.
<sporkmonger> k
<bluestorm> jlouis_: be as we as speaking about a language-wide choice here, optimization should be considered
<bluestorm> s/be/but/
neale has quit [Remote closed the connection]
neale has joined #ocaml
ita has joined #ocaml
<sporkmonger> yeah, was just wondering because TM was highlighting #install_printer wrong, didn't know where in the language definition file to look for it :-P
<bluestorm> (for example, boxing every mutable field right now if no optimization is performed would raise some considerable performances issues in some user code for sure)
<sporkmonger> now to go file a bug report
<bluestorm> sporkmonger: in the manual, the "toplevel" part
<Smerdyakov> Anyone in the channel planning to submit a paper to ICFP'08?
<sporkmonger> no, i mean TM's language def file
<bluestorm> ah
<Yoric[DT]> Smerdyakov: planned to, but won't.
<Yoric[DT]> Maybe next year.
kelaouch1 has joined #ocaml
<Smerdyakov> Yoric[DT], on what subject?
<Yoric[DT]> Region-based error management.
<Yoric[DT]> But it still needs to be refined a lot.
<jlouis_> I presume 'it' refers to something else than the paper
<Yoric[DT]> Yeah, the basic ideas :)
<Smerdyakov> What is "region-based error management"?
<Yoric[DT]> Let's say it's an idea which needs to be refined a lot :)
<Yoric[DT]> It's a variant on exceptions.
<Smerdyakov> Or is it an exception to variants?
<Yoric[DT]> Both :)
<Yoric[DT]> We gave ourselves one more year to pursue the idea and determine if it's actually any use.
<Smerdyakov> I'm pretty sure I'll be submitting a paper on a new way of representing language syntax and type systems in Coq.
<Yoric[DT]> Well, you have one more week to finish that paper, don't you ?
<Yoric[DT]> But it sounds interesting.
<Smerdyakov> Yes. I'm starting ridiculously early this time.
<Smerdyakov> My last paper that was accepted somewhere was written in about 14 hours. :-)
<Smerdyakov> It's always weird to me how few people in FP IRC channels submit to ICFP. O_o
<RobertFischer> Is there an deferred monad/asynchronous monad/callback library kicking around in the open source Ocaml world?
<RobertFischer> Brian started to write one for adlib-ocaml, but then he decided to just invent his own language instead.
kelaouchi has quit [Read error: 110 (Connection timed out)]
Linktimaw has quit [Read error: 104 (Connection reset by peer)]
Linktim has joined #ocaml
kelaouch1 has quit ["leaving"]
resistor_ has joined #ocaml
ttamttam has joined #ocaml
<palomer> what's ocaml written in?
<neale> most of it is written in ocaml
<neale> the rest in C
<neale> you could look over the source code
<palomer> so its like haskell (implementing itself in haskell)
{MSX} has joined #ocaml
<{MSX}> hello
<neale> most compiled languages end up being self-compiling.
thermoplyae has quit ["daddy's in space"]
<neale> (in my experience)
<Smerdyakov> neale, which, to me, means that there must be too many of them being designed. :)
<neale> Smerdyakov: posssibly, but first let's work on getting people to quit using the "cyber-" prefix.
<Smerdyakov> Well, now I need to go implement the cyber-OCaml compiler.
<mbishop> cybercompiler
<mbishop> heh
* neale hangs himself
<mbishop> cypermetacircular evaluator!
<mbishop> cyber too
<{MSX}> is anybody willing to help a newbye a little ? :)
<ita> do not forget the cyberpreprocessor and the cyberlinker
resistor__ has quit [Read error: 110 (Connection timed out)]
<neale> {MSX}: you have to ask your question before we can help you
<{MSX}> right.. well i'm making a simple program to learn ocaml:
<{MSX}> a small interactive program that has some commands to add and remove items from a list
<{MSX}> something like "write A to add an item, B to remove, C to quit"
<{MSX}> the problem is: how do i make a list that is somehow global and mutable
<{MSX}> to be edited during the program use
<{MSX}> (very newbie question)
<flux> {msx}, you don't infact need a global list for that purpose
<flux> {msx}, however, to answer the question: let global_list = ref []
ttamttam has left #ocaml []
<{MSX}> great, i had the feeling that global stuff were wrong
<flux> {msx}, you could construct your program like: let rec loop list_contents = if input .. then loop (inserted_item::list_contents) etc
<{MSX}> i tried with the "ref" but it says: "The type of this expression, '_a list ref, contains type variables that cannot be generalized"
<flux> right, you can't compile such a definition by itself
<flux> because it cannot infer its type
<{MSX}> i have to use it ?
<flux> but if you have something that uses it, the type will be assigned
<flux> or, you can type: let global_list = ref ([] : int list)
<{MSX}> is that some kind of forcing the type ?
<jlouis_> cyber- is not the only word that is bad. We must also abolish meta- that has been heavily overused.
<flux> {msx}, yes. but it can never disagree with the compiler, only give suggestions.. so if your suggetion is wrong, it will fail at some point (of compilation)
<palomer> how do I do pattern matching with curried function? http://ocaml.pastebin.com/m632f4b2e (I'm doing pattern matching with tuples here)
<{MSX}> ok.. returning to the program structure: i make a single recursive function that always return the "modified" list, right ?
<{MSX}> i'll try it
<flux> palomer, well, those expressions would need to return a function for that to work
<flux> or you could write function a -> function b -> ..
<Smerdyakov> palomer, there is no function definition construct, anonymous or named, that both allows multiple different patterns and supports currying.
<palomer> Smerdyakov, so I'll have to do something like let foo : sometype = fun a -> fun b -> fun c -> match a,b,c with ... ?
<flux> palomer, exactly, except fun a b c -> match a, b, c with is shorter
<palomer> (which is what flux suggested)
<palomer> ok, that's fine
<palomer> thx
<palomer> !
<palomer> fun == function?
<flux> function is fun combined with match
<flux> function a is the degenerate case which is equal to fun a
<palomer> gotcha
<bluestorm> hm
<bluestorm> i'd excpect fillNone [] [a; b; c] to return [Right a; Right b; Right c] instead of an error
<bluestorm> -c
<bluestorm> palomer: your style is still a bit haskellish :p
<pango> (cyber- comes from greek Kubernan, which means "to govern", "to drive"... So it may not be only overhyped, but is also often put to weird use given its etymology...)
<bluestorm> (camlCase wich are not very common in caml, and specifying the type of the function when unnecessary)
<neale> pango++
<bluestorm> hm
<bluestorm> it seems like a not-so-weird derivation : command/driving -> communication/control -> computers
kelaouchi has joined #ocaml
bouzukist has joined #ocaml
<bouzukist> hi
<bouzukist> glade too see ur rooms
<bouzukist> any one can help me ?
<bouzukist> alllo
thermoplyae has joined #ocaml
<bouzukist> hii
<Smerdyakov> IRC etiquette says never to ask to ask.
<bouzukist> i need help on ocaml
<palomer> you're in the right place
<bouzukist> :)
<bouzukist> (cvt "123 45 6") = (cvt "123", cvt " 45 6")
<bouzukist> how i can do this funciton plz
<palomer> you can't
<palomer> or, rather, you need a list
<bouzukist> ['1';'2';'3';' ';'4';'5';' ';'6'] ->> [123],[45;6]
<bouzukist> while is not space i wana stok in int list
<qwr> erm
<qwr> you want to split string?
<bouzukist> let rec (prnb_r: char list -> char list * char list) = function
<palomer> this looks like something that needs extList
<bluestorm> palomer: hm, or he could code it himself
<bouzukist> cvt is my other function ...
<bouzukist> ['1';'2';'3';' ';'4';'5';' ';'6'] ->> [123],[45;6]
<bluestorm> bouzukist: so you have a problem with the string <-> char list conversion ?
<bouzukist> while is not space stok it in int list
<bouzukist> i wana do hd in int list and the tail in int list when i have space
<bouzukist> string <-> char list is okey
<bouzukist> just i wana do this ['1';'2';'3';' ';'4';'5';' ';'6'] ->> [123],[45;6]
<bluestorm> and your prnb_r function already exists ?
<bouzukist> no
<qwr> bouzukist: i'd use string's.
<bouzukist> prnb_r is the function that i wana code it
<pango> what about returning [123;45;6] instead?
<bouzukist> forget the stringss
<bouzukist> look
<pango> what's the point of returning a tuple?
<bouzukist> my input is :['1';'2';'3';' ';'4';'5';' ';'6']
<bouzukist> i wana result ( [123],[45;6])
<bouzukist> while my char is not space i need to stock it all numbers in char list and the tail in another char list
<bluestorm> i'd do ['1';'2';'3';' ';'4';'5';' ';'6'] -> [['1'; '2'; '3']; ['4'; '5']; ['6']] -> [123; 45; 6] -> [123], [45; 6]
<bluestorm> each transformation being quite easy
<bouzukist> bluestorm
Linktim has quit [Remote closed the connection]
<bouzukist> look my codes
<bluestorm> i've seen no code so far
<palomer> bouzukist, so you want to take a string and return a list of ints contained in that string?
evn has quit []
<bouzukist> forget the strings
<palomer> ok
<palomer> so you want to take a list and return a list of ints contained in that string
<bluestorm> i don't see where your [123], [45; 6] thing would be needed
<bouzukist> i have char list ->char list * char list
<qwr> # let y = ['1';'2';'3';' ';'4';'5';' ';'6'];;
<bluestorm> just do
<qwr> # let rec f c = function ' '::t -> (List.rev c, t) | x::t -> f (x::c) t | [] -> (List.rev c, []);;
<qwr> # f [] y;;
<qwr> - : char list * char list = (['1'; '2'; '3'], ['4'; '5'; ' '; '6'])
<palomer> or do you want to take a list of three integers and return a pair whose first element contains the first int and the second element contains the two other integers?
<bouzukist> qwr :)
<bouzukist> that is
<bouzukist> but what us rev ?
<qwr> bouzukist: reverse list
<bluestorm> because of the accumulator
<bluestorm> qwr: i think you could use non-tail-rec for clarity at first
<bouzukist> can u write clearly plz
<bouzukist> in paste bin
* RobertFischer laughs.
<bouzukist> i wana easy code
<bouzukist> btw where is operators here ?
<qwr> operators?
<bouzukist> on this server
<bouzukist> no @ ?
<bouzukist> qwr
<bouzukist> plz u can wtite me thise code ??
<bouzukist> clearly
<qwr> bouzukist: they're hiding under rock ;)
<bouzukist> without using '1'; '2'; '3'], ['4'; '5'; ' '; ....
<qwr> bouzukist: that was the constant you gave by yourself
<bouzukist> qwr
<qwr> bouzukist: the function f is just one line
<bouzukist> that was for tests
<RobertFischer> Begging is undignified.
<{MSX}> little question: i have a recursive function that works on a list. i'd like to print the current list (with my print_list) at the end of the function, at each iteration. How do i do it without breaking the recursiveness ?
<bouzukist> i wana to generalise
<qwr> bouzukist: read the f and try understand what it does. it's simple recursion with accumulator and pattern matching
<bouzukist> ok
<RobertFischer> {MSX} do a print iter on the list. You'll be okay for tail recursion optimization as long as the recursive call is the very last thing that is done.
<bouzukist> let rec f c what is c ?
<qwr> bouzukist: "collector" or accumulator, where first list is collected in reverse order
<bouzukist> :s
<bouzukist> but we dont leanred those things
<pango> {MSX}: there's also tricks to keep recursive functions "open" using the Y combinator
<qwr> bouzukist: you can deduce all of that by logic by yourself
<bouzukist> lol
<bouzukist> ok
<qwr> bouzukist: i've never really learned programming, either imperative nor functional
<{MSX}> RobertFischer: but in this way i have to print the string *before* the recursive call, right ?
<qwr> bouzukist: basically that function looks the incoming list element-by-element. if it finds space it return collected list and remaining tail. otherwise it puts the thing that wasn't space into collector and goes to look next one.
<qwr> s/return/returns/
<qwr> s/puts/prepends/
<qwr> {MSX}: yes. you have to print before, if you want to preserve tail-recursiveness
<pango> {MSX}: http://www.lfcs.inf.ed.ac.uk/reports/97/ECS-LFCS-97-375/ (I think I saw another good paper on the same topic...)
<qwr> {MSX}: on debuging it's not always important though
<{MSX}> pango: i'm not really ready for that yet :)
<bluestorm> bouzukist: http://pastebin.be/10026
<bouzukist> bluestorm :s
<bouzukist> qwr
<bouzukist> look this plz
<bouzukist> is not working
<bluestorm> you should not use code you don't understand
<bouzukist> im new on ocmal
<bluestorm> still
<qwr> bouzukist: not compiling either i'd guess. you're using c that is not defined anywhere in you're code
<bouzukist> i coding since 2 months
<bouzukist> oh
<bluestorm> puting together pieces of code that you don't understand won't ever give you something working :p
<bouzukist> qwr plz write for me :)
<qwr> bouzukist: no i don't ;) you would learn nothing from that
<bluestorm> (and i suggest that you try non-abbreviated english, wich is easier to read)
<bouzukist> yes i know
<bouzukist> but i have 2 function to write .. to complete me works
<bouzukist> my**
<bluestorm> http://pastebin.be/10026 does what is asked in your homework subject
<bluestorm> hm
<{MSX}> ok.. maybe i solved it
<{MSX}> is this call (at the end of a "match") tail recursive?
<{MSX}> | _ -> loop ( print_status (a :: theList))
<{MSX}> (loop is the function of course)
<bouzukist> thnks anyways
bouzukist has quit []
<Smerdyakov> {MSX}, yes.
<{MSX}> thanks :P
* qwr wonders... is it wrong to expect people to think a bit?
<qwr> {MSX}: yes. it is
thelema has joined #ocaml
<{MSX}> is it ugly for an expert to have a "print_status" inserted in the middle of the call ?
<palomer> http://pastebin.com/m7b815187 <--how would I do this?
<qwr> {MSX}: no. if you want, you could do use let-in...
<palomer> expert programmer or expert system :P?
<palomer> oh, wait, it does work!
<palomer> nice!
<{MSX}> uhm
<{MSX}> qwr: something like this:
<{MSX}> | _ -> let x = a :: theList in print_status x; loop x
<qwr> {MSX}: yes, that's also tail-recursive
<{MSX}> ehm how can i test if an element is in a list ?
ygrek has quit [Remote closed the connection]
<{MSX}> yes, i was there
<qwr> mem
<{MSX}> ahhh
* {MSX} stupid
<{MSX}> i supposed by the name that it had something to do with memory :P
<qwr> ;)
delamarche has quit []
rayno has joined #ocaml
<bluestorm> {MSX}: mem(ber) ?
* palomer is in love with variant types
<palomer> is ocaml the only language which has'em?
rayno has quit [Client Quit]
<{MSX}> bluestorm: yes, i get it now :)
kopophex has joined #ocaml
kopophex has left #ocaml []
<RobertFischer> palomer: I don't know of another language that does. But, y'know, my langauges are pretty limited (C/C++, Perl, Java, Ocaml, Groovy, Ruby, in that order).
<palomer> http://pastebin.com/m2091c04 <--how would I do this?
<RobertFischer> Oh, with some Lisp back by the C++/Perl stuff.
<pango> palomer: all the languages of the ML family, for a start (SML, Haskell, F#, maybe others)
<palomer> I mean [`FOO | `BAR of int] types
<bluestorm> polymorphic variants
<palomer> yeah!
<palomer> haskell doesn't have'em
Axioplase has joined #ocaml
<palomer> (sml has'em?)
AxleLonghorn has joined #ocaml
<qwr> yeti has ;)
thelema has quit [Read error: 110 (Connection timed out)]
<qwr> but i have to document it...
thelema has joined #ocaml
* palomer bangs his head against his desk screaming "I don't want to put all my classes in the same file, mr typesystem
* palomer begs the ocaml gods for mutually recursive modules in different files
<thelema> palomer: what's the big deal with putting code in a single file?
<qwr> palomer: iirc there was some way for recursive modules. but maybe i'm mistaken...
<palomer> all my classes in the same file?
<palomer> qwr, they have to be in the same file
<palomer> you can fake it with functors IF the signatures aren't mutually recursive
<thelema> palomer: no, only ones that depend on each other recursively.
<qwr> palomer: but make your classes parametric?
<pango> not afaik
marmottine has quit ["Quitte"]
<palomer> but I have a toplevel class which will depend on 4 others
<RobertFischer> palomer: That's a code smell.
<pango> palomer: that's usually not possible
<palomer> I have a virtual toplevel called node with a function as_variant which lets you get back the full type
<qwr> palomer: you should be able to make the other a type parameters to the class
<palomer> method as_variant :[> `UNIMPORTANT | FUNCTION_DEFINITION of function_definition | DATATYPE_DEFINITION of datatype_definition] = `UNIMPORTANT
<palomer> I'd put that in my toplevel virtual class
* qwr suspects too much relying on inheritance ;)
<palomer> and then when I need to know if an object is a function_definition, I match #as_variant with `FUNCTION_DEFINITION
<palomer> I guess I have to find another solution
<palomer> (but this one seemed so clean!)
<qwr> where the recursion comes?
<qwr> function_definition is derived from the class that has as_variant method?
<palomer> yup
<palomer> one option is making the toplevel class parametric
<palomer> (which may result in some major goofiness)
<qwr> yes. or you can send the OO to the hell ;)
<qwr> and use variant always where you don't what that shit is
<qwr> s/don't/don't know/
<palomer> use variants everywhere?
<palomer> I could do that...
<palomer> actually, I'd still have the same problem
<qwr> yes. maybe combined with something that contains non-variant parameters
<palomer> if I want to inherit code, I'll have this problem
<palomer> hmm
<palomer> good ideas though
* palomer is off!
<{MSX}> i'm going, thanks for all help
<qwr> hmm. the problem is actually trying to define types in different files
<qwr> the code itself shouldn't matter
{MSX} has quit ["Leaving."]
<palomer> qwr, right
<qwr> palomer: you should be able to declare the needed class types beforehand
<palomer> so I could have type pointer : <as_variant: [`UNIMPORTANT of node | `FUNCTION_DEFINITION of function_definition | ...] , as_node: node>
<qwr> yes, something like that ;)
<palomer> that's cool!
* palomer is starting to understand why lablgtk has so many type conversion methods
<palomer> even better
<palomer> class variantable = object(self) inherit node as_variant ....
<palomer> class variantable = object(self) inherit node; method as_variant : [`UNIMPORTANT of node | ...]
<palomer> still...mutually recursive modules would make this cleaner
<palomer> if I put all my type signatures in the same file
<palomer> would it solve this problem?
goalieca has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
<pango> 1. modules do not only contain type/functions/... definitions, but also values; 2. the semantic of module linking is that it's the same as evaluating its content; 3. you can't use values before they're defined 1+2+3 => linking order matters => separate compilated modules can't cross-reference each other, in general
RobertFischer has left #ocaml []
filp has joined #ocaml
filp has quit [Client Quit]
bluestorm has quit [Remote closed the connection]
AxleLonghorn has left #ocaml []
Anarchos has joined #ocaml
postalchris has quit [Read error: 110 (Connection timed out)]
<Anarchos> i added : extern "C" within #ifdef __cplusplus__ #endif at the beginning and the end of headers files in byterun/
<Anarchos> I can link with C++ code with that