rwmjones changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | Grab Ocaml 3.10.1 from http://caml.inria.fr/ocaml/release.html (featuring new camlp4 and more!)
middayc has quit [Connection timed out]
seafood_ has joined #ocaml
ulfdoz has quit [Connection timed out]
ozzloy has joined #ocaml
ulfdoz has joined #ocaml
Mr_Awesome has joined #ocaml
ulfdoz has quit [Success]
ulfdoz has joined #ocaml
<ozzloy> does anyone in here program Gtk with ocaml?
buluca has quit ["Leaving."]
litb has quit [Remote closed the connection]
wy has quit [Read error: 113 (No route to host)]
jlouis_ has quit [Remote closed the connection]
jlouis has joined #ocaml
maayhem has joined #ocaml
<maayhem> hello
<maayhem> is it possible to iterate on the all content of a Map ? (constructed from Map module)
<maayhem> in normal time I would use List.map over a list, but for some reason here I have to use a Map.Make(string) instead of a list
<maayhem> and Id like to call a function on all -keys- of the map, if thats possible.
jlouis has quit [Remote closed the connection]
jlouis has joined #ocaml
<tsuyoshi> ozzloy: I do
<ulfdoz> maayhem: you can use fold for this.
Mr_Awesome has quit ["aunt jemima is the devil!"]
<maayhem> ulfdoz, thanks
<ulfdoz> if the result is also a map, you could use mapi, too.
seafood_ has quit []
Mr_Awesome has joined #ocaml
thermoplyae has joined #ocaml
<ulfdoz> ~~/go #gentoo
wy has joined #ocaml
wy has quit [Client Quit]
jlouis_ has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
|jeremiah has quit [Read error: 110 (Connection timed out)]
jeremiah has joined #ocaml
jderque has joined #ocaml
<ozzloy> tsuyoshi: thanks! what kinda apps do you make with it?
thermoplyae has quit ["daddy's in space"]
maayhem has quit ["Leaving"]
bluestorm has joined #ocaml
jderque has quit [Read error: 113 (No route to host)]
Associat0r has quit []
pwnguin has joined #ocaml
jderque has joined #ocaml
<pwnguin> is mod a keyword or an operator?
<bluestorm> iirc, it's treated specifically by camlp4 parser's,
<bluestorm> hm
<bluestorm> pwnguin: it's a keyword
<bluestorm> and the bit-shifting infix functions are as well
<pwnguin> so i cant override it via let (mod) = num_mod;;
<bluestorm> hm
<bluestorm> i'm not sure about that
<bluestorm> might work :p
<pwnguin> hmm
<pwnguin> Reference to undefined global Num
<bluestorm> works.
<pwnguin> =(
<bluestorm> # let (mod) a b = a b;;
<bluestorm> val ( mod ) : ('a -> 'b) -> 'a -> 'b = <fun>
<bluestorm> # print_endline mod "foo";;
<bluestorm> foo
<bluestorm> - : unit = ()
<bluestorm> pwnguin: ocaml nums.cma
Mr_Awesome has quit ["aunt jemima is the devil!"]
<pwnguin> ?
<bluestorm> if you're testing in the toplevel
<pwnguin> ah
<bluestorm> you have to load the Num library
<pwnguin> order matters
<pwnguin> the toplevel has certain deficiencies
<bluestorm> modules given to the cli are evaluated in-order
<bluestorm> pwnguin: wich are ?
<pwnguin> like bksp yielding ^H
<bluestorm> (i know of some, but i know of things that actually aren't)
<bluestorm> pwnguin: use ledit or rlwrap
<bluestorm> this one wasn't.
<pwnguin> ledit?
<bluestorm> the toplevel doesn't embed any "user-friendly editor" code
<bluestorm> but you have external programs for that
<pwnguin> which is why i dont use the toplevel :P
<bluestorm> it's not a good reason
<bluestorm> with ledit or rlwrap
<pwnguin> gedit works fine for me
<bluestorm> you can have editing facilities
<bluestorm> added to the toplevel
<pwnguin> hmm
<bluestorm> pwnguin: sometimes the toplevel is handy (for example in your case, trying re-binding (mod))
<bluestorm> it's a shame you don't use it because you were not informed of the easy way to overcome this not-a-limitation
<pwnguin> in which case, i run the toplevel
<bluestorm> so i'd suggest you to try ledit or rlwrap
<pwnguin> i just nabbed ledit and
<pwnguin> wtf mate
<bluestorm> rlwrap may even be packaged for your distribution
<bluestorm> hm
<bluestorm> pwnguin: you use "ledit ocaml"
<bluestorm> and you've got an editing-aware toplevel
<bluestorm> with, iirc, history
<bluestorm> it's still not heaven, but much better than ^H
<pwnguin> intersting
<pwnguin> you can override (+)
<pwnguin> err
<pwnguin> you can override (=)
<bluestorm> you can get the "true meaning" back with Pervasives.(+)
<pwnguin> i dont think i'll need that for this program
<bluestorm> and at some point, overriding hurts readability
<pwnguin> actually, i think it improves it here
<pwnguin> all it does is add together all the primes below a million
<pwnguin> as this is larger than 2^31 or something
<bluestorm> hm
<pwnguin> i need to replace the operators with a bigint lib
<bluestorm> iirc, Num modules already provides some syntaxic sugar
<bluestorm> +/ , -/ , */, etc.
<pwnguin> yea
<bluestorm> btw
<bluestorm> for such cases, you might just use floats
<pwnguin> whats the fun in that?
<bluestorm> hm
<bluestorm> i'm not sure it's fun
<bluestorm> but it's fast
<bluestorm> and simple
<pwnguin> but will it hold the number?
<bluestorm> (i'm not sure, but i guess reasonable-range floats computations are faster than Bigint, but still accurate)
<bluestorm> hm
<pwnguin> i need it 100 percent accurate
<pwnguin> and im thinking the significand will be too long
<bluestorm> # sum 1000000;;
<bluestorm> - : float = 37550402023.
<bluestorm> ( http://pastebin.be/8372 )
<pwnguin> well
<pwnguin> a million floats
<pwnguin> well done
<pwnguin> i guess a million bools
<bluestorm> you guess right
<bluestorm> and still it's sub-second delay in the toplevel
<bluestorm> (wich mean sub-sub-second delay in native code)
<pwnguin> use time :P
<bluestorm> hm
<bluestorm> unless you want to recompute that every second
<bluestorm> i don't see the problem with that :p
<pwnguin> certainly not viable on embedded systems
<bluestorm> hm
<pwnguin> i doubt the compiler even bothers with bitfields
<bluestorm> he doesn't
<bluestorm> i saw a library doing this recently
<bluestorm> hm
<pwnguin> but fret not
<pwnguin> its just a toy application
<bluestorm> $ time ./test
<bluestorm> real 0m0.222s
asmanur has joined #ocaml
<pwnguin> its a bit sad the GC isn't thread safe
<bluestorm> hm ?
<bluestorm> if you need simple concurrency, you can use fork()
<pwnguin> well, can't take advantage of multicore systems without it
<bluestorm> what about multiple processes ?
<pwnguin> well, i suppose theres message passing
<pwnguin> so it looks like sieve theory is a real win
<bluestorm> i suggest you have a real look at multi-processes
<bluestorm> some people did some tests
<bluestorm> and it seems that forking, that is having independants GCs, but simpler
<bluestorm> may in some cases be better that having a complicated (thus slower) multi-threading GC
<bluestorm> (i mean, performance-wise)
<pwnguin> in non multithreaded apps or?
<bluestorm> ?
<pwnguin> well, if you have a multithreaded GC with only a single thread, theres clearly an amount of overhead in synchronizing an uncontended heap or whatever
<bluestorm> ah
<bluestorm> i mean in multithreaded apps
<pwnguin> well, that's one of those "embarrassingly" parallel apps ;)
ita has joined #ocaml
<bluestorm> hm
<bluestorm> pwnguin: you mean the sieve ?
<pwnguin> no
<pwnguin> the ray tracer
<pwnguin> its a high computation, low communication problem
<bluestorm> ah
<pwnguin> oh, heh
<pwnguin> a thread
<pwnguin> (mailing list thread)
<pwnguin> but yes, that last one is what i mean
<pwnguin> anyways,
<pwnguin> my program finished =(
<pwnguin> 37550402023
<pwnguin> real 10m27.008s
<bluestorm> :)
<pwnguin> just a really stupid system
<bluestorm> ?
<pwnguin> take each number from a million down to 2
<bluestorm> and test primality ? o_O
<pwnguin> check if its divisible by 2,3,5, up to sqrt of the number
<pwnguin> yea
<pwnguin> arrays ftw
<bluestorm> (ftw ?)
<pwnguin> "for the win"
<pwnguin> meaning, they win, i lose
<bluestorm> could be "for the worse" as well :p
<pwnguin> not if you're hip to jouvenile internet lingo
<pwnguin> ok
<pwnguin> so how do i tell ocamlopt to use nums?
<bluestorm> ocamlopt nums.cmxa
<pwnguin> doah
<pwnguin> im thinking if i built a list of primes, that would speed up prime detection
<pwnguin> but
<pwnguin> the memory usage would probably exceed the sieve array anyways
<bluestorm> the sieve looks like a good idea
<pwnguin> did you write that up or just find it?
<bluestorm> hm ?
<pwnguin> the pastebin code
<bluestorm> ah, just wrote it for test purposes
<bluestorm> in case you're interested
<bluestorm> i even rewrote "sum" in a "functional style"
<pwnguin> heh
<bluestorm> much shorter, but maybe a bit less efficient, because of the numerous 0. +. ..., and you seems very mad about efficiency :p
<pwnguin> heh
<pwnguin> but the loc will make people cry ;)
<bluestorm> hm
<bluestorm> could be nicely written with Yoric's camlp4 extension
<bluestorm> Array.fold_left (+.) 0. [| float i | i <- [|1..n|]; sieve.(i) |]
<bluestorm> 1..(n-1)
<pwnguin> yes yes. plenty fast
Mr_Awesome has joined #ocaml
<pwnguin> if its any consolation
Mr_Awesome has quit [Read error: 104 (Connection reset by peer)]
<pwnguin> it only takes two minutes when compiled to native code
Mr_Awesome has joined #ocaml
Mr_Awesome has quit [Read error: 104 (Connection reset by peer)]
Mr_Awesome has joined #ocaml
<bluestorm> you should try the sieve thing
<bluestorm> so we could compare Bigints and floats
<pwnguin> and im pretty sure i still got it wrong =(
seafood has quit [calvino.freenode.net irc.freenode.net]
seafood has joined #ocaml
<pwnguin> it'd probably be easier to just move the sieve to Num
Snark has joined #ocaml
ozzloy has quit [Read error: 104 (Connection reset by peer)]
seafood_ has joined #ocaml
ozzloy has joined #ocaml
<pwnguin> its about the same
<pwnguin> i can't measure it
<pwnguin> oh, duh
<pwnguin> it helps if i put in a call
<pwnguin> so float is about 4 times faster
<pwnguin> but i think the point of some of these problems is to require bigint
<bluestorm> you could try with Int64
<bluestorm> but i'd bet float is faster anyway
<pwnguin> i doubt that
<pwnguin> interesting
<pwnguin> it is, but not by much
<bluestorm> :p
<pwnguin> i wasnt aware you could have un-else'd if statements
<bluestorm> ah
<bluestorm> defaults to ()
<bluestorm> that's usually not considered "good style"
<bluestorm> but sieve is an imperative algorithm anyway
<pwnguin> actually, small note
<pwnguin> you can start j at i * i
<bluestorm> hmm
<bluestorm> seems right
<bluestorm> because multiples under that have a lesser divisor
<pwnguin> sure
<pwnguin> well, the next problem looks ugly =(
<pwnguin> huge array of numbers
<pwnguin> anyways, thanks for the help and discussion
Associat0r has joined #ocaml
Associat0r has quit [Read error: 104 (Connection reset by peer)]
ita has quit [Read error: 110 (Connection timed out)]
Yoric[DT] has joined #ocaml
<Yoric[DT]> hi
<bluestorm> hi Yoric[DT]
<bluestorm> i just found an "interesting comprehension camlp4 extension" this morning
<bluestorm> tought you may be interested in it, but actually i think it's yours :D
<bluestorm> i still don't like the "loops" part, but the comprehension are very nice
<bluestorm> i regret it's not as "modular" as it could be
<Yoric[DT]> :)
<bluestorm> e.g. you emebed LList and SdlFlow, while they could be separate dependencies
<Yoric[DT]> How modular would that be ?
<bluestorm> i mean, at the source level
<Yoric[DT]> Oh, that.
<Yoric[DT]> Yeah, that's annoying.
<Yoric[DT]> I'm considering a change for version 0.2 .
<bluestorm> does SDLflow really gives you something more than Stream for comprehensions purpose ?
<bluestorm> i haven't looked at the source yet, but i'm a bit surprised you need such a sophisticated library
<bluestorm> hm, brunch time
asmanur_ has joined #ocaml
asmanur__ has joined #ocaml
<Yoric[DT]> No, SDFlow is not really needed.
asmanur has quit [Read error: 110 (Connection timed out)]
asmanur_ has quit [Read error: 110 (Connection timed out)]
hkBst has joined #ocaml
<bluestorm> hm
<bluestorm> Yoric[DT]: seems your LList code would benefit from a "lazy patterns" syntax extension
<Yoric[DT]> Yep.
<Yoric[DT]> Good thing I have one :)
<bluestorm> hm
<Yoric[DT]> I'll include it in version 0.2 .
<bluestorm> ok
<bluestorm> one more thing
<Yoric[DT]> Yes ?
<bluestorm> i'm not sure the behaviour of "range" is very natural
<bluestorm> for the 2..0 stuff
<bluestorm> i mean, in most case we actually expect that to be empty
<Yoric[DT]> Yeah, in version 0.2, [ 2 .. 0 ] is empty .
<bluestorm> :p
<Yoric[DT]> :)
<bluestorm> and you could provide an "unfold" function
<bluestorm> that would, in other things, allow to create descendent ranges easily
<Yoric[DT]> Which lets us define factorial n as List.fold ( * ) 1 [ 1 .. n] .
<Yoric[DT]> I'm not sure I understand.
<bluestorm> hm
<bluestorm> the classic list unfold is
<Yoric[DT]> s/fold/fold_left
<bluestorm> let rec unfold pred iterate acc = if pred acc then [] else acc :: unfold pred iterate (iterate acc)
<bluestorm> for example let range a b step = unfold ((<) b) ((+) step) a
<Yoric[DT]> ok
<bluestorm> hmm
<bluestorm> the haskell unfold ( unfoldr :: (b -> Maybe (a, b)) -> b -> [a] ) is a bit more generic, but not as easy to use
asmanur__ has quit [Connection timed out]
<Yoric[DT]> I guess I could include both.
<bluestorm> (on the other hand, using a Maybe/option instead of the predicate make unfold more similar to Stream.from)
<bluestorm> hm
<bluestorm> is the "lazy pattern" syntax extension you promised for 2.0 based on http://code.google.com/p/ocaml-patterns/, or your own code ?
<Yoric[DT]> It's based on ocaml-patterns.
<bluestorm> interesting
asmanur__ has joined #ocaml
<Yoric[DT]> I've contributed a few bugfixes and optimizations.
<bluestorm> did you have problems for providing both classical and revised extensions ?
<Yoric[DT]> My first contribution was to make that extension compatible with both.
<bluestorm> :p
<bluestorm> that's nice
<Yoric[DT]> I don't think it's merged in the trunk yet.
asmanur_ has joined #ocaml
<Yoric[DT]> Gottago.
<Yoric[DT]> Talk to you later.
Yoric[DT] has quit ["Ex-Chat"]
musically_ut has joined #ocaml
<musically_ut> Is there a module available for Matrix multiplication on Ocaml yet? As far as I can remember, there was none a couple of years back.
<bluestorm> do you have real performance constraints ?
<bluestorm> if you need really big matrixes and so on
<bluestorm> iirc there are ports of some FORTRAN libraries
<musically_ut> Wow.
<bluestorm> there was a "mathematical" Ocaml Summer of Code project, you may look on that side too, but i'm afraid it may be dead
<musically_ut> I don't in particular have performance constrains .. but I was looking at how easy/difficult it is to do matrix calculations in Ocaml ...
<bluestorm> hm
<bluestorm> if it's basic things, the simpliest way is probably to code them yourself
<bluestorm> (i mean, matrix multiplication is a five lines of code thing)
<musically_ut> And so far I have found that they are easier in Python, hellish in Perl and a piece of cake in Matlab and Octave ... while C lies in between Python and Perl ..
<musically_ut> And I think I will ... it'll be a good thing to practise a little imperative programming in Ocaml too.
<musically_ut> Thanks bluestorm.
marmottine has joined #ocaml
asmanur__ has quit [Read error: 110 (Connection timed out)]
asmanur_ has quit [Connection timed out]
Amorphous has quit [Read error: 104 (Connection reset by peer)]
bluestorm has quit ["Konversation terminated!"]
Yoric[DT] has joined #ocaml
<Yoric[DT]> hi again
Amorphous has joined #ocaml
seafood_ has quit []
jderque has quit ["leaving"]
middayc has joined #ocaml
<middayc> that TIOBE lang index has been posted .. any comments? http://www.tiobe.com/index.htm?tiobe_index?2007
<pango> the main frame is empty if you don't have js enabled ;)
<pango> (above string may not be an URL per RFC1738 either)
<middayc> yes that url is a little strange with two ?
<middayc> you don't have js enabled?
<pango> not by default
<middayc> but it's the web 2.0 man :)
<pango> security implications of js are just starting to pop up, but there's probably much more to come
<pango> I only enable js on a per case basis
asmanur__ has joined #ocaml
asmanur__ is now known as asmanur
<middayc> aha , yes I agree somewhat with you
bluestorm has joined #ocaml
filp has joined #ocaml
xavierbot has joined #ocaml
xavierbot has quit [Remote closed the connection]
Snrrrub__ has joined #ocaml
jderque has joined #ocaml
Snrrrub has quit [Read error: 110 (Connection timed out)]
jlouis has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
musically_ut has quit [Remote closed the connection]
musically_ut has joined #ocaml
<bluestorm> musically_ut: so how is your matrix stuff going ?
<musically_ut> bluestorm: I am writing functions for them :)
<musically_ut> And am reconsidering whether I should continue writing my assignments in Ocaml ... I can shift to Python ...
jderque has quit ["brb"]
* Yoric[DT] prefers OCaml.
<flux> what a curious coincidence, so do I!
<Yoric[DT]> Strange, that.
love-pingoo has joined #ocaml
pango has quit [Remote closed the connection]
pango has joined #ocaml
marmottine has quit ["Quitte"]
jderque has joined #ocaml
zmdkrbou has quit [Read error: 110 (Connection timed out)]
<middayc> what would you switch to python? I coded in python few years back
cyrilRomain has joined #ocaml
middayc has quit []
ttamttam has joined #ocaml
middayc has joined #ocaml
<middayc> (I got disconnected)
l_a_m has quit [Remote closed the connection]
<middayc> (in case someone anwered the python question in the meantime)
<pango> nope
zmdkrbou has joined #ocaml
<middayc> aha
<middayc> what do you use ocaml for pango?
<pango> jan 05 13:27:59 <pango> benchmarks, statistics, simulations, utilities,...
<pango> jan 05 13:33:59 <pango> (r&d, mainly on large storage problems)
<middayc> uh :)
<middayc> you have good memeory ...
<pango> and good logs ;)
<middayc> beter than me ... I remember you once said it would be cool if you could use something like ocaml instead of php -- I think
blackdog has quit [Read error: 110 (Connection timed out)]
<middayc> I was asking before why the two of you are considering python because I used it a lot few years back and am new to ocaml.. and so far ocaml seems to me sort of like python on triple steroids.. but as I saind I am very new at ocaml
<bluestorm> i don't really see the link between python and ocaml
ita has joined #ocaml
* pango wonders who are "the two of you"
<Smerdyakov> bluestorm, compared to traditional mainstream languages, both involve almost no types written in programs.
<Smerdyakov> That is, both have usage modes with that property.
<Smerdyakov> Good, modular OCaml code has many types written out. :-)
<bluestorm> hm
<middayc> I think flux and another person said above that are thinking of switching to python for something
<bluestorm> as type aliases, interfaces, or plain constraint in the code Smerdyakov ?
<Smerdyakov> I'm thinking of types appearing almost entirely in signatures and .mli files.
<pango> * Yoric[DT] prefers OCaml.
<pango> <flux> what a curious coincidence, so do I!
<bluestorm> pango historite strikes again :-'
<pango> middayc: seems you misread them
<middayc> :) uh I didn't saw that Yoric's line , sorry
<pango> ic
<middayc> by python on triple steroids I meant mainly that ocaml has the similar basic structures as python has (list, tuple, dict..) and you could write imperative code that would not look that different than pythons .. only that here you can do so much more, and are faster, and errors get noticed at compile time... etc
<bluestorm> actually i think that python data structures are quite different from OCaml's ones
<bluestorm> as many other scripting langages (PHP and iirc Ruby), lists are not lists, for example
<bluestorm> but rather a list-deque-array thingy
<Yoric[DT]> Well, they're hash tables.
<bluestorm> (and a bit of hashtables maybe)
<middayc> yes I know ... lists at python are more like arrays ..
<Yoric[DT]> It would be quite easy to write a syntax extension to make hash-tables appear like arrays in OCaml.
<Yoric[DT]> I remember seeing one somewhere, actually.
<Smerdyakov> You can use infix operators to get most all of the benefit.
<Smerdyakov> (with no camlp4)
<cygnus_> can you define unary operators in ocaml?
<bluestorm> you can rebind (!) for example
<cygnus_> does that mean i can't use it for references then ?
<bluestorm> yes it does
<bluestorm> but you can use !!
<cygnus_> will that be unary?
<bluestorm> prefix-symbol ::= (! ∣ ? ∣ ~) { operator-char }
<Smerdyakov> cygnus_, the OCaml manual gives the rule for mapping operators to fixity. It's purely textual.
<bluestorm> (where operator chars are all the symbols allowed in ocaml operators)
<Yoric[DT]> Smerdyakov: what grammar would you give to the table update ?
<cygnus_> Smerdyakov: does that mean it depends what char i use?
<bluestorm> cygnus_: yes it odes
<cygnus_> whats the best reference on ocaml's advanced features? i can't understand the stuff in chapter 3 of the reference manual
<bluestorm> that last pages gives the associativity and prority for operators
<bluestorm> pango: dead homepage :p
<pango> bluestorm: yes, and web archive is giving me access denied for months
<Smerdyakov> Yoric[DT], you can make the 2nd argument a pair.
<Yoric[DT]> my_table *= (my_key, my_new_value) ?
<Smerdyakov> Yoric[DT], that would work.
<Yoric[DT]> Not very nice.
<bluestorm> a little googling gave the guy's new page
<Yoric[DT]> Well, not that bad, actually.
<Yoric[DT]> But could be better :)
<bluestorm> Yoric[DT]: i was thinking of a funny symmetrical thing
<bluestorm> tbl --> key for access
<Smerdyakov> cygnus_, I wouldn't call objects an "advanced feature".... there's at least another echelon of advanced-ness beyond that. :)
<bluestorm> and tbl <-- key val for update
<Smerdyakov> cygnus_, besides, don't use objects! :D
<cygnus_> what is more advanced in ocaml?
<pango> bluestorm: ah, good
<Yoric[DT]> Polymorphic variants, functors.
<Yoric[DT]> Camlp4.
<Smerdyakov> cygnus_, I was thinking of those features documented in the chapter "Language extensions."
<Yoric[DT]> etc.
<flux> I would call objects an advanced feature, with their structural typing..
<cygnus_> this in chapter 3 too
<bluestorm> pango: http://upsilon.cc/~zack/hacking/software/ says "(for 2003 OCaml, no way it will even compile with CamlP4 >= 3.10)"
<Yoric[DT]> I might adapt it at some point.
<Yoric[DT]> It would look well in a comprehension extension, after all :)
<Yoric[DT]> If anybody has a favorite syntax, feel free to tell me.
<Yoric[DT]> (bluestorm's input duly noted)
<bluestorm> hm
<bluestorm> the problem is that ternary functions don't work when infix
<bluestorm> you have to write (tbl <-- key) value
<middayc> (hmm.. you are all too advanced for me)
<bluestorm> so using a tuple instead is not a bad idea
<bluestorm> cygnus_: are you learning from the plain manual ?
<cygnus_> well i read other things to learn the basics, but i wanted to start learning the features in chapter 3 so i tried reading that but i couldn't understand mutch
<bluestorm> hum
<bluestorm> you mean "objets in OCaml" ?
<bluestorm> +c
<Smerdyakov> cygnus_, what is the first thing you don't understand?
hsuh has joined #ocaml
<bluestorm> cygnus_: i first learned oo-ocaml with http://caml.inria.fr/pub/docs/oreilly-book/html/book-ora138.html (if that may help)
<cygnus_> i get confused around 3.6
<cygnus_> but maybe even before that
<cygnus_> ok ty
<bluestorm> btw, i don't think learning oo-ocaml is necessary, given the quite moderate usage of object oriented code in the ocaml community
<bluestorm> i you find it too difficult or useless, i think you may just let it go for a while, and wait to feel a need/motivation for it
<Smerdyakov> cygnus_, can you be more specific about the first paragraph that loses you?
Morphous has joined #ocaml
<cygnus_> ok
<cygnus_> what is object(self) doing ?
<cygnus_> and also below method virtual move : _
<cygnus_> then further along object (self : < move : _; ..> )
<Smerdyakov> cygnus_, did you read 3.3?
<cygnus_> yes
<Smerdyakov> cygnus_, that explains the object(...) syntax.
<cygnus_> since we don't have move method defined
<cygnus_> how can it reference itself ?
<Smerdyakov> Were the three lines you references meant to be one question or three questions?
<cygnus_> yeah its different problems i have
<Smerdyakov> Now that I reminded you of 3.3, do you understand the first problem?
<cygnus_> yes ty
<cygnus_> what is this one though: object (self : < move : _; ..> )
<Smerdyakov> Does reminding you of 3.5 solve your problem about a virtual method?
<Smerdyakov> Do you understand that < move : _; ..> is a type?
<cygnus_> hat does the _ do for the virtual one?
<cygnus_> it don't care what return type it has ?
<Smerdyakov> The return type is inferred from context, I believe.
<cygnus_> it's all very tricky
<Smerdyakov> That isn't a problem, since you shouldn't be using objects.
<bluestorm> :D
<cygnus_> yes i don't think i will use it
Amorphous has quit [Connection timed out]
hsuh has left #ocaml []
<middayc> can I ask something not ocaml related , but more algoritms related.. beacuse you seem more like higher educated programmers not just practitioners like I am or like I meet on channels of imperative languages..
<middayc> question is.. how hard would it be to make a solver that would help me find card setups that are solvable in this game
<Smerdyakov> Probably pretty easy, if it's "a game for kids."
<middayc> it's sort of solitaire for kids and has a a lot less cards and colors so it's quicker to solve
<middayc> :)
marmottine has joined #ocaml
<Smerdyakov> Maybe even the most naive brute force search would work on modern machines.
<middayc> I tried one time but I basically "lost myself" and didn't manage to do anything..
filp has quit ["Bye"]
<Smerdyakov> You didn't manage to write a brute force solver, regardless of if it ran quickly enough?
<middayc> I didn't know how to know what combinations I have already tried and what not .. but I don't have any background knowledge on this and maybe there is a known way of doing this
<middayc> yes .. it can be slow
<Smerdyakov> Then it's definitely worth learning how to do this.
<Smerdyakov> Have you taken any university course on programming?
<middayc> what topic (keywords) would this be in.. if I want to learn about it
<middayc> no .. I was not at computer uni.
<middayc> (and didn't finish it anyway)
<Smerdyakov> You probably want a text used in a sophomore data structures course.
<middayc> sophomore? this even sound complicated
<middayc> ok thanks ... I will google for sophomore data structures
<middayc> hmm.. sophomore means "A second-year student in a U.S. college." ... I thought it was a name of the datastructures .. I am not eng. native speaker
<middayc> I found some papers on this so thanks
<flux> you're confusing it with semaphore, no?
<flux> (looking back some context: maybe you weren't mixing it with anything..)
madroach has joined #ocaml
ozzloy has quit ["leaving"]
ozzloy has joined #ocaml
piggybox has joined #ocaml
Smerdyakov has quit [Remote closed the connection]
Smerdyakov has joined #ocaml
piggybox has quit ["Leaving"]
piggybox has joined #ocaml
thermoplyae has joined #ocaml
Snark has quit ["Ex-Chat"]
asmanur has quit [Remote closed the connection]
madroach has quit [Read error: 113 (No route to host)]
madroach has joined #ocaml
Mr_Awesome has quit [Read error: 110 (Connection timed out)]
ttamttam has left #ocaml []
mwc has joined #ocaml
thermoplyae has quit ["daddy's in space"]
thermoplyae has joined #ocaml
middayc has quit []
ita is now known as ita|zzz
Smerdyakov has quit [Remote closed the connection]
Smerdyakov has joined #ocaml
<flux> hm, I wonder if this is supposed to be available (linked from reddit): http://www.cs.caltech.edu/courses/cs134/cs134b/book.pdf - a new ocaml book (draft)
piggybox_ has joined #ocaml
<flux> well, the link is atleast about 5 months old, so I suppose it'd be pulled if it wasn't ok :)
<bluestorm> flux: seems to be mostly an improvement over http://www.nuprl.org/documents/Hickey/02caltech-ocaml.pdf
<bluestorm> (wich seems easier to redistirbute and so on)
piggybox has quit [Connection timed out]
buluca has joined #ocaml
ita|zzz has quit [Read error: 110 (Connection timed out)]
Associat0r has joined #ocaml
cyrilRomain has quit ["zZz"]
Smerdyakov has quit [Remote closed the connection]
Smerdyakov has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
AxleLonghorn has joined #ocaml
jlouis has quit [Remote closed the connection]
jlouis has joined #ocaml
AxleLonghorn has left #ocaml []
seafood_ has joined #ocaml
hkBst has quit ["Konversation terminated!"]
jlouis has quit ["leaving"]
jlouis has joined #ocaml
bluestorm has quit ["Konversation terminated!"]
thermoplyae has quit ["daddy's in space"]
marmottine has quit ["Quitte"]
jderque has quit [Read error: 113 (No route to host)]
love-pingoo has quit ["Connection reset by pear"]
middayc has joined #ocaml