mbishop changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | Grab Ocaml 3.10.0 from http://caml.inria.fr/ocaml/release.html (featuring new camlp4 and more!)
Demitar has quit [Read error: 110 (Connection timed out)]
jlouis_ has joined #ocaml
alkoma has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
ser_ has joined #ocaml
ser_ has quit [Remote closed the connection]
mordaunt has joined #ocaml
mordaunt has quit [Read error: 104 (Connection reset by peer)]
Proteus has quit ["Leaving"]
jnkm has left #ocaml []
wy has joined #ocaml
yminsky has joined #ocaml
zmdkrbou has joined #ocaml
Demitar has joined #ocaml
mordaunt has joined #ocaml
cratylus has joined #ocaml
Demitar has quit [Connection reset by peer]
cratylus has left #ocaml []
alkoma has quit ["ChatZilla 0.9.79 [Firefox 2.0.0.4/2007051502]"]
jlouis has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
yminsky has quit []
jlouis_ has joined #ocaml
Associat0r has quit []
kelaouch1 has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
yminsky has joined #ocaml
kelaouchi has quit [Read error: 110 (Connection timed out)]
yminsky has quit [Client Quit]
buluca has quit [Read error: 113 (No route to host)]
Associat0r has joined #ocaml
pants2 has joined #ocaml
jeffwheeler has joined #ocaml
<jeffwheeler> I'm trying to use ocaml-dbus, which as far as I can tell doesn't have any documentation beyond the simple header files and the C source code; I've gotten by sending method calls, but can't figure out how, in a client, to get the response (return) value from a method call.
<jeffwheeler> I think it has to do with DBus.Connection.send_with_reply; should I then sleep and periodically be checking for a response?
<jeffwheeler> If so, how do I check the final response? I can check the _status_ using DBus.PendinCall.get_completed, but seem to be stuck there.
filp has joined #ocaml
filp has quit [Client Quit]
dibblego has quit [Remote closed the connection]
ttamttam has joined #ocaml
bluestorm has joined #ocaml
jeffwheeler has quit ["Leaving."]
ygrek has joined #ocaml
pants2 has quit [Read error: 110 (Connection timed out)]
asmanur has joined #ocaml
wy has quit ["Ex-Chat"]
ertai has joined #ocaml
opening` has quit [Connection timed out]
Morphous has joined #ocaml
Amorphous has quit [Read error: 110 (Connection timed out)]
kmeyer has joined #ocaml
ttamttam has left #ocaml []
ttamttam has joined #ocaml
ttamtta1 has joined #ocaml
ttamtta1 has quit [Remote closed the connection]
<tsuyoshi> imo camlp4 is a poor substitute for lisp macros
Morphous is now known as Amorphous
<flux> I think camlp4's greatest limitation is that it cannot really interface with the type system.. but going around that would probably mean undecidable compilation
<flux> tsuyoshi, I haven't dealt with lisp macros, how are ocaml's more poor?
<tsuyoshi> not sure how it could be improved though, without switching to lisp syntax
<tsuyoshi> flux: it's more complicated in ocaml
<pango_> that's my understanding too that to get lisp macro, you need a language isomorphic to lisp at syntax level
<tsuyoshi> I mean, you need a whole manual to describe how to se camlp4
<tsuyoshi> how to use
<tsuyoshi> for lisp it's just.. "here's how defmacro works"
<tsuyoshi> but this:
<tsuyoshi> suppose you have a Time module which defines and extensively uses Time.date_of_string which parses the ISO8601 basic format ("YYYYMMDD"). Suppose you need the full power of the module, but recognizing the ISO8601 extended format ("YYYY-MM-DD"). Tough luck: you have to get the module maintainer to edit the function Time.date_of_string - you cannot redefine the function yourself in your module
<flux> you can however do module TimeEx which has everything that Time has and the more advanced parsing also
<flux> I would personally prefer to see from code A.b that function b from module A is actually being called
<tsuyoshi> you can redefine modules though
madroach has joined #ocaml
<flux> locally
<tsuyoshi> his argument is totally bogus
<flux> oh, right, he didn't know that you could do that locally
<tsuyoshi> "you cannot redefine the function yourself" is just not true
<flux> it depends what you mean by that, though
<tsuyoshi> ack.. I'm pretty lagged
<tsuyoshi> I guess with all the tourists here for high season it might remain this way for a while
jlouis has joined #ocaml
<madroach> hi! I just had a look at pervasives.ml, because I'm having performance issues with calculating many logarithms. Can you tell me what the _three_ different strings in the external declarations in pervasives.ml mean?
<flux> I don't remember off-hand (and actually I don't know where else to check except mailing lists) but atleast there is a byte-code and native code versions
<flux> now, the third one, can't remember :). perhaps if you'll provide an example it'll jolt someone's memory
ertai has quit [Read error: 110 (Connection timed out)]
<tsuyoshi> it's an extra flag
<madroach> flux: that's what I know. Documentation doesn't mention anything else.
<madroach> external log : float -> float = "caml_log_float" "log" "float"
<tsuyoshi> it's undocumented but if it's "float" then it means that the function takes unboxed floats
<tsuyoshi> there are a couple other flags but I forget what they are
<madroach> tsuyoshi: ah, thanks and let me guess, its only valid for native code?!?
<tsuyoshi> it's pretty easy to figure out from looking at the source though
<tsuyoshi> madroach: no, it should work with byte code too
<tsuyoshi> iirc the other flags are completely useless outside the compiler, so I didn't bother remembering them
<madroach> ah, ok. Now I'm wondering, why there is a c-wrapper code for the log function in bytecode... hmmm It simply does a caml_copy_double...
<madroach> anyway. bytecode is unusable slow in my case...
<tsuyoshi> heh.. the only time I've used bytecode is for getting a backtrace on an exception
<tsuyoshi> when a newer version of ocaml makes it into debian I probably won't use it ever again
<flux> I suppose that's why I use bytecode too.. but it does compile slightly faster, too.
jlouis_ has quit [Read error: 110 (Connection timed out)]
<pango_> it's a bit old but, I hope, still mostly accurate (I think NaN handling has been made more conformant since then)
<pango_> (since 3.08)
<tsuyoshi> yeah
<tsuyoshi> the part in that that says "Intermediate results of arithmetic expressions are not boxed." is basically true because while arithmetic expressions are still regular function applications, all the float primitives have that "float" flag
<pango_> which on the other hand means that the use of other functions (non-inlined calls, at least) break that assumption
<bluestorm> tsuyoshi: if we had a lisp syntax for ocaml
<bluestorm> we could do lisp macros with it
<bluestorm> lisp macros are simple because lisp doesn't have any syntax : the only structure is the list, so program are easy to transform (and easy to transform wrong, too)
<bluestorm> camlp4 feels cluttered because the syntax is much more structured
<bluestorm> if you had a lispish (unstructured) syntax for ocaml, you could add lisp macros
<bluestorm> iirc, that's what Liskell does for Haskell
<bluestorm> now the question is : do you prefer easy macros, or structured syntax ?
<madroach> what would be about closures? For example this:
<madroach> let iter f v = for i=0 to Array.length v - 1 do
<madroach> v.(i) <- f v.(i)
<madroach> done in
<madroach> iter log v
<madroach> is log inlined in this case and does any boxing happen?
<pango_> It's half-funny that OCaml gets a bad score at "recursive" benchmark because one fibonacci implementation uses floats (http://shootout.alioth.debian.org/gp4/benchmark.php?test=recursive&lang=ocaml&id=2)
kmeyer has quit [Read error: 113 (No route to host)]
<tsuyoshi> recursion is kind of slow in ocaml even without floats
<pango_> madroach: among things, if you've read above url, it may help to prevent iter from being overly polymorphic (iter f (v: float array) = ...)
<pango_> but only looking at asm (ocamlopt -S) will tell
jedai has quit [Read error: 113 (No route to host)]
ttamttam has left #ocaml []
<Smerdyakov> tsuyoshi, what evidence do you have of that?
<pango_> madroach: it seems using -inline and/or -unsafe can make a difference too
<madroach> pango: my real function is constrained. (it uses (+.)). What I'm wondering about is the speedup I get when I change
<madroach> sum := !sum +. log (if a=b then 0. else 1.) to
<madroach> sum := !sum +. (if a=b then 0. else 1.)
<madroach> This is iterated in three for-loops 3200x3200x86 times. Inside the for loops there is a classift_float and a pattern matching over 4 different strings. The whole process takes 207 seconds when using log, but it takes 40 seconds without. It the log so slow?!??
<pango_> log 0. ?
<flux> that's purely for testing, otherwise you'd just use -infinity and zero, right?-)
<madroach> oh, sorry. Thats just one branch of the match. The other one looks like
<madroach> sum := !sum +. scale (abs_float (a-.b))
<pango_> I wonder what are the consequences of such 'simplifications'... The compiler is not that smart, but still...
<madroach> That branch is executed in 95% of all iterations. where scale is a parameter of the function. Usually I just pass log.
<madroach> Now I'm wondering if my cpu really spends 160 seconds just by calculating those 3200x3200x86 logs.
<madroach> while those 3200x3200x86 pattern matchings, float_classifys, branches and other stuff. Just needs 40 seconds.
<bluestorm> hm
<flux> madroach, have you tried a functional approach?
<pango_> have you tried -inline? if that doesn't work, I guess you'll have to specialize your function for scale = log... Or use an optimizing compiler, like MLton (to outstrip Smerdyakov ;) )
<flux> sum is boxed afterall..
<Smerdyakov> Right, it's worth reminding everyone who doesn't know that SML has a much better optimizing compiler than OCaml does. :P
<bluestorm> is it possible that log 0. were much slower than other logs ?
<madroach> ok, I already tried specializing my function for scale=log. now its' really all about just leaving that single log away or keeping it. Making a speedup of about 5x
<madroach> bluestorm: just trying that.
<flux> it'd be great if sml and ocaml code could be interfaced neatly with each other (I haven't tried, so maybe they can), that way you could gradually try sml out
<flux> often it's not viable to rewrite the whole project in another language
<flux> perhaps a language translator would work too
<madroach> bluestorm: that was a good guess. Now I can do it in 85 secs.
<madroach> I just added 1. to the argument of log, so that log only receives positive arguments.
<madroach> could it be that on my 386 kernel the compilers don't manage to call the FYL2X instruction for computation of the logarithm?
ertai has joined #ocaml
<pango_> a sum of logarithms is the logarithm of the products... You could also use log just once in this case, if you don't to anything else with sum, and don't get an overflow
<madroach> pango_: hey, that's nice! Just the accuracy could suffer a bit...
mordaunt has quit [Read error: 104 (Connection reset by peer)]
ertai has quit ["Lost terminal"]
<madroach> I just tried the same in c. It takes exactly 55s to compute the logarithms. So that would explain the speedup very well!
<tsuyoshi> ocaml's log is just a single line c function: caml_copy_double(log(Double_val(f)));
<tsuyoshi> so only the caml_copy_double() is going to make it slower than c
|Catch22| has quit [Read error: 104 (Connection reset by peer)]
<madroach> tsuyoshi: yeah, that's what I figured out. With native could there shouldn't be any difference left.
<tsuyoshi> well, the compiler doesn't open code that
<pango_> (wondering about the use of -ffast-math)
<madroach> I just couldn't believe at first that the native log is so slow.
<tsuyoshi> it might not be too hard to make it open code that instead of just calling a standard library function
<tsuyoshi> but I'm not too familiar with floating point code in assembly so I couldn't do it...
<pango_> $ diff -u test.s.inline10.unsafe test.s.inline10.unsafe.ffastmath
<pango_> ...
<pango_> -fldl0(%esp)
<pango_> +fldl(%ebx)
<pango_> +fldln2; fxch; fyl2x
<pango_> ...
<tsuyoshi> so fldl must be the fp equivalent of movl right?
<pango_> so it seems that adding -ffast-math to ocamlopt makes a difference
<tsuyoshi> what is fldln2? fyl2x?
<madroach> the logarithus dualis of x times y.
<madroach> fldln2...
<madroach> fldln is load
ertai has joined #ocaml
<madroach> fast-math is enourmously speeding up the c code.
<madroach> no, sorry, fldln2 is push ln 2 onto the stack.
<madroach> hmm
<madroach> pango_: these are the lines used when fast-math is active? So how is the logarithm calculated without -ffast-math??
<malodios> the i387 is still the polish calculator
<madroach> malodios: I think so.
buluca has joined #ocaml
asmanur has quit [Success]
<pango_> "call log"... provided by -lm I suppose
<bluestorm> does someone here use otags ?
<pango_> sometimes
<bluestorm> i just tried a camlp4 3.10 port
opening has joined #ocaml
<ertai> bluestorm: good idea
<bluestorm> thanks
<Associat0r> any F# people here?
<Smerdyakov> What's an "F# person"?
pango has joined #ocaml
pango_ has quit [Remote closed the connection]
<madroach> Fortran sharp?!?
<bluestorm> madroach: ocaml sharp
<Associat0r> it is like ocaml for .NET
<Associat0r> Smerdyakov
<Associat0r> madroach
<Associat0r> bluestorm
<bluestorm> ?
<Smerdyakov> Associat0r, you didn't yet say what an "F# person" is.
<Associat0r> a person shaped like an F
<bluestorm> hum
<bluestorm> i've got preprocessor errors when using {< >}
<bluestorm> have you heard of anything about that ?
<bluestorm> ( {< foo = bar >} works, but the empty {< >} fails )
<bluestorm> i may file a bug report
ChristopheT has joined #ocaml
<bluestorm> ertai:
<bluestorm> i've got a bug whith camlp4orf and "{< >}" in the source
<bluestorm> "assertion failed", same as http://caml.inria.fr/mantis/view.php?id=4307
<bluestorm> is it the same bug ?
jlouis_ has joined #ocaml
ertai has quit [Read error: 110 (Connection timed out)]
jlouis has quit [Read error: 110 (Connection timed out)]
ertai has joined #ocaml
jlouis has joined #ocaml
asmanur has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
slow_sara has joined #ocaml
ChristopheT has left #ocaml []
madroac1 has joined #ocaml
jonathanv has joined #ocaml
jeffwheeler has joined #ocaml
<jeffwheeler> As far as I can tell, there's no way to send or receive a GList using the DBus API -- is that correct?
<ertai> bluestorm: what preprocessor, what version for your pb with {< >}
<bluestorm> camlp4 3.10
<bluestorm> i can give you a minimal test file
<bluestorm> hm
<bluestorm> "let foo = {< >}"
<bluestorm> ocamlc -pp camlp4o test.ml
<bluestorm> (camlp4o test.ml alone won't fail)
madroach has quit [Read error: 110 (Connection timed out)]
jonafan has quit [Read error: 110 (Connection timed out)]
pants2 has joined #ocaml
<pango> plain ocamlc fails, however
<pango> "This object duplication occurs outside a method definition"
<bluestorm> the source is not valid
<bluestorm> let foo = object method bar = {< >} end
<bluestorm> should work
<bluestorm> (and raise the error too)
<bluestorm> in case you're interested, here is my otags porting attempt : http://bluestorm.info/tmp/otags-3.10-beta.tar.gz
<slow_sara> q: why doesn't the type in the else work?
<slow_sara> let rec foo(ai) = function
<slow_sara> | 0 -> true
<slow_sara> | 1 -> false
<slow_sara> | ai -> if ai == 4 then 0 else foo(ai mod 3) ;;
<pango> both branches of the "if" should have the same type
<pango> (because it's also the type of the "if" expression as a whole)
<slow_sara> how about
<slow_sara> | ai -> if ai == 4 then foo(0) else foo(ai mod 3) ;;
<slow_sara> both branches are foo(int) but still has type int->bool used here with type bool
<pango> the other problem is the use of 'function' keyword, that makes foo a function of two arguments
<slow_sara> oh? thanks. how do I fix that?
<pango> in this code, by removing (ai)... let rec foo = function ...
ertai has quit [Read error: 110 (Connection timed out)]
<jdavis_> I'm trying to use the built-in "Set" module. Do I have to create an ordered type first, or can I just pass a comparator function somehow?
<slow_sara> *kisses* That works!!
<pango> or let rec foo ai = match ai with ...
<slow_sara> can I pass multiple args
<slow_sara> let rec foo ai, bi, ci = match ai, bi ,ci with ... ?
pwnguin has joined #ocaml
<pango> jdavis_: you need to provide a module of type OrderedType, but that can be a litteral module
<pango> jdavis_: like, module StringSet = Set.Make(struct type t = string let compare = String.compare end)
<jdavis_> pango: That sounds like what I want to do, thanks!
<pango> jdavis_: which is also what happens when you write module StringSet = Set.Make(String)
<jdavis_> pango: I see. I am still trying to learn Ocaml so I'm not familiar with what a module really is. I didn't know there was such a thing as a literal module.
<Smerdyakov> slow_sara, what are you using to learn OCaml? I would expect most sources explain how to do multiple-argument functions.
<pango> jdavis_: .ml/.mli pairs are just a specific case... check http://caml.inria.fr/pub/docs/manual-ocaml/manual004.html
<jdavis_> pango: why can't you specify a literal module by itself, like "struct type t = string let compare = String.compare end;;"
<jdavis_> pango: Ok, I'll read that.
<pango> jdavis_: you can declare a module with that, but modules aren't first class values
<pango> like, module M = struct type t = string let compare = String.compare end
<slow_sara> Smardyakov, ocaml-tutorial.org it certainly has a multi arg examples that work
<jdavis_> pango: Ah, I see.
<slow_sara> Smardyakov, but not sure they work with match
pwnguin has left #ocaml []
<slow_sara> let rec foo a = match a with | 0 -> true | _ -> foo 0 ;;
<slow_sara> vs
<slow_sara> let rec foo a b = match a b with | 0, 0 -> true | _, _ -> foo 0 0 ;;
<slow_sara> for example
pwnguin has joined #ocaml
<pango> both let foo a b and let foo (a, b) are correct, but have a different meaning. in the first case foo is a function of two values (well, simplifying...), whereas in the second case it's a function of a single value (a 'pair', or tuple of two elements)
<pango> match, on the other hand, only accepts one value, but you can use a tuple to do pattern matching on its elements
<pango> the only freedom you have with match is to write match (a, b) with or match a, b with... It's so common to do pattern matching on tuples that parenthesis are optional here
<slow_sara> ah-ha
<slow_sara> pango -- where did you learn it all? ;)
<pango> 'developing applications with objective caml' online book + user manual, and all the resources available on the web (ocaml mailing list, for example)
<pango> (ocaml-tutorial.org didn't exist at the time)
slow_sara has quit []
buluca has quit [Read error: 113 (No route to host)]
ertai has joined #ocaml
buluca has joined #ocaml
ertai has quit [Read error: 104 (Connection reset by peer)]
ertai_ has joined #ocaml
<bluestorm> i'm not sure ocaml-tutorial provide a consistent way for beginners to learn caml, though
<pango> neither am I, I still personally prefer 'developing apps...' approach
<bluestorm> it's a wiki, it could be reordered
<bluestorm> Haskell guys did a quite good job with the Haskell wikibook
kmeyer has joined #ocaml
<pango> ocaml-tutorial is ok to get 'a taste of the language', but is not deep enough once one is really serious about learning to use it
<Smerdyakov> I'm going to have to disagree. I've read hardly anything about OCaml outside of the manual, and I've found the information I need just fine.
<bluestorm> Smerdyakov: i'm not sure everybody can learn a language by reading a manual
<bluestorm> (or has the motivation to do so)
<Smerdyakov> Well, most people who can't won't do very well with OCaml.
<pango> giving 'a taste of the language' can be fine too, in some contexts
<madroac1> I learned it from develping apps with ocaml. But as reference the manual is way more handy.
<Smerdyakov> madroac1, that last sentence was a great example of why punctuation matters.
<Smerdyakov> madroac1, it's unclear whether you meant the book or the literal activity of developing applications with OCaml.
<madroac1> :-D
<madroac1> Well, I meant the boot. But both applied. To really learn a language you don't have to read books. Just get the pieces you need to get started, then just do it.
<pango> maybe the main problem with ocaml-tutorial atm, is the domain name ;)
<madroac1> s/boot/book/
<pango> it's more like, an introduction
<pango> madroac1: it depends, there's certainly ways of using new languages that you can only learn by either reading books, or lots of other people's code
<pango> otherwise, it's like the old saying, "you can write Basic code in any language" ;)
<madroac1> thats right. But i think its suffiecient to know whats possible and where you can look up how to do it.
<pango> for anything as complex as a programming language, you don't really have the choice
<Smerdyakov> We need a standard apprenticeship system, where an experience programmer reads your code to help you learn the right style.
<Smerdyakov> s/experience/experienced
<jeffwheeler> As a beginner to OCaml, I've found ocaml-tutorial extremely useful; it's an easier intro than the manual, but I use both together.
<jeffwheeler> The manual is a good reference for methods and the like, while the tutorial is a good syntax reference.
<Smerdyakov> I guess you come from OO-land if you say "methods." ;)
<jeffwheeler> Err, yes...
<jeffwheeler> "functions"
kmeyer has quit [Remote closed the connection]
ahnfelt has joined #ocaml
<jeffwheeler> (Is it incorrect to call them methods when they're part of an object?)
<Smerdyakov> No, that's correct, but you won't find many of those in the manual.
<ahnfelt> I know this is a trivial question (sorry), but my google-fu is failing tonight: how do you declare a type alias?
<ahnfelt> Uhh.. nevermind. I've been doing it right, the syntax error was elsewhere.
<bluestorm> type a = b ?
<bluestorm> caml light use type a == b
<ahnfelt> Yeah, thank you :)
<bluestorm> (and maybe the revised syntax does that too)
<ahnfelt> The ocaml+twt whitespace syntax is tempting
<bluestorm> orbitz: regarding your "ocaml sucks" links, i just found http://rafb.net/p/Svl2fu83.html in the Emacs Lisp manual; even the lisp guys want "silent name conflict resolutions"
pwnguin has left #ocaml []
yminsky has joined #ocaml
kmeyer has joined #ocaml
asmanur is now known as asma
asma has quit [Remote closed the connection]
yminsky has quit [Client Quit]
ygrek has quit [Remote closed the connection]
yminsky has joined #ocaml
jeffwheeler has quit ["Leaving."]
madroac1 has quit [Remote closed the connection]
glen_quagmire has joined #ocaml
<ahnfelt> Aren't silent name conflict resolutions only remotely desirable if you're really polluting your namespace?
<ahnfelt> If you're cherry-picking the symbols to import, it's nice to get a compiler error
<glen_quagmire> no link on the topic about good free book/tutorial?
<bluestorm> glen_quagmire: http://caml.inria.fr/pub/docs/oreilly-book/index.html is quite good
<glen_quagmire> thank you
<Associat0r> btw can you change the object#member to object.member in ocaml?
<flux> in theory you can, but then you'd need to pick another syntax for accessing record fields
<bluestorm> Associat0r: why would you do that ?
<bluestorm> that would conflict with other notations
<bluestorm> (record access)
<Associat0r> looks prettier
<bluestorm> ...
<flux> I kinda like the a#b-syntax, how is a.b prettier?
<flux> see, that discussion can go nowhere :)
<bluestorm> Associat0r: a simple regexp would do the job
<Associat0r> the # is too much for my eyes
<bluestorm> exchange [a-z_]#[a-z_] and [a-z_].[a-z_]
<bluestorm> Associat0r: wait a little
<bluestorm> you'll get used to it
<Associat0r> I am using F#
<Associat0r> so I don't need to yet
<Associat0r> does anyone do game development with ocaml here?
yminsky has quit []
ertai_ has quit [Read error: 110 (Connection timed out)]
<ahnfelt> Associat0r: I don't, but I did do a fair amount of hobbyist game development earlier in other languages. Is it a OCaml-specific question?
<flux> associat0r, I wrote this for fun: http://www.modeemi.cs.tut.fi/~flux/goba/
<bluestorm> flux: have people used it for fun ?
<flux> I don't think it has that many (any?) users. if they do use it, I'm thinking it's not used for work ;).
yminsky has joined #ocaml
<Associat0r> I was just curious
<ahnfelt> Ah :)
<Associat0r> flux : do you have any tips or traps to lookout for
<Associat0r> and what difficulties did you experience
<flux> associat0r, hmm.. not really.. I remember having some trouble with the sdl bindings; trouble of the segmentation fault kind
<flux> I think generating a face for an empty string for example caused a segfault
<flux> and not initializing everything properly could cause trouble
<flux> otherwise I found sexplib very nice for writing the networking support
<Associat0r> and what about the code design? how much functional could you use?
<flux> many pieces are functional, however the program is mostly imperative: the game objects have state which is mutated
<flux> doing that functionally when game objects interact becomes complicated..
<flux> for that particular piece I didn't need to think much of performance issues.. however, some effort has gone into not doing the same work twice
<flux> the tiles in the screen are composed from multiple instructions, but when one such tile is generated, it's held in memory
<flux> this works in this case because new kinds of tiles aren't generated constrantly or in bursts
<Associat0r> are you planning todo more game stuff?
<flux> so when you shoot a piece of grass and the grass transparency increases, it'll only need to generate a few more tiles
<flux> maybe, if an inspiration hits :)
<flux> it's not very likely to get much of an "audience" though, which does reduce the motivation
<flux> I haven't received any bug reports, which is telling about the audience size ;)
jedai has joined #ocaml
<Associat0r> yeah I know what you mean
<flux> it could be fun to do something with opengl. my opengl-capable hardware isn't very, well, opengl-capable, so I wouldn't be able to use many advanced features; on the other hand, using them would mean studying them in some detail
<flux> at times I've thought of making a rewrite of Sopwith 2, an old dos-game
<flux> (infact so old that I think I originally played it on an IBM XT)
<Associat0r> is that that side scroller airplane game?
<flux> yes!
* pango memories...
<pango> I even completed it once :)
<ahnfelt> Did you just stick it on that site, or did you submit it to gamehippo etc.?
<pango> of course the name has to be Sopwith OCaml ;)
<Associat0r> yeah
<flux> ah, the first hit is the game, and dosbox works :)
<flux> ahnfelt, it's on linuxgames and freshmeat
<ahnfelt> ah
<flux> actually a google search turns out a lot of links
<flux> it appears many sites are fed from atleast those sites..
<ahnfelt> If you want inspiration for Sopwith like games, Triplane Turmoil is a good laugh
<Associat0r> you should look at jetstrike
<pango> mmmh I don't remember the cows of Sopwith 2, so I guess I only player Sopwith (1)
<pango> s/player/played/
jlouis_ has joined #ocaml
ahnfelt has quit ["Ex-Chat"]
jlouis has quit [Read error: 110 (Connection timed out)]