mfp changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.11.2 released | Inscription for OCaml Meeting 2010 is opened http://wiki.cocan.org/events/europe/ocamlmeetingparis2010
<dark> also, for some reason i think the program logic is not ocaml-ish. that if a = b then exit 0 else ..
<sc30317> bluestorm, then it says that lr_matrix is an unbound value when I clearly have it defined earlier
<sc30317> whats up dark?
<bluestorm> hm, where did you declare lr_matrix ?
<sc30317> duh
<sc30317> lr_vecctor
pimmhogeling has joined #ocaml
<bluestorm> you know
<bluestorm> when the ocaml compiler reports an error
<bluestorm> you're usually the one wrong
<bluestorm> :-p
<sc30317> haha thats true
<dark> hahahaha
* dark usually don't understand 'up', 'out', .. expressions, such as 'whats up'
<sc30317> whats up = how are you doing
<sc30317> going out = going to bars/clubs/etc
<dark> i'm fine :-P
<sc30317> bluestorm, now it seems to be working
<dark> someone once tried to explain me the general meaning of <something> up, <something> out, <something> off.. it seems to be somewhat random
<sc30317> except for the fact that it says current_class within the finish loop is unused
<bluestorm> well, it is unused
<sc30317> well how do I make is_finished use that as a parameter?
<bluestorm> it is not the same current_class variable you're referring to
<sc30317> so I have 2 current_class es?
<bluestorm> is_finished use the current_class variable defined after the "CREATE THE CURRENT CLASS" comment
<dark> sc30317, when pasting snippets of code, try to paste something semantically closed, i mean, something that can be ran without external dependencies. it's hard to tell what your code does if someone don't know what compare_vc_current_class does
<sc30317> sorry dark
pimmhogeling has quit [Ping timeout: 256 seconds]
<bluestorm> your "let current_class = cur_class ..." in the finish () declaration does not overwrite that definition
<sc30317> it doesn't?
<bluestorm> it creates a new current_class variable wich can be used in a further expression
<bluestorm> in your case, the "finish ()" expression just after that declaration
<sc30317> is there a way I can get it to overwrite that definition?
<bluestorm> you could use references
<bluestorm> but you don't need to here
<sc30317> ok
<bluestorm> you just need to pass current_class and w_current as parameters to the "finish" recursive function
<bluestorm> let rec finish current_class w_current = ... in finish current_class w_current
<sc30317> I think that worked
<sc30317> but now I get this
<sc30317> let current_class = cur_class_vect trainData w_current in
<sc30317> Error: This expression has type unit but an expression was expected of type
<sc30317> float list
<sc30317> is this what I need to fix with the
<sc30317> if finish() = [] then failwith "no"
<sc30317> else .....
<sc30317> ?
ski_ has joined #ocaml
rbancrof1 has joined #ocaml
<dark> it looks like finish will not accept an ()
<dark> but instead 3 arguments of unknown (for me) type
<dark> is the first argument an ()? [that's pointless]
patronus_ has joined #ocaml
<sc30317> not anymore
<dark> if yes, the result can't be a list
<dark> ah
<bluestorm> you have to fix your "finish" declaration so that it really returns a list
<sc30317> yes, how do I do that?
<bluestorm> and you probably shouldn't test for finish returning a [], just return its result directly
<bluestorm> hm
<sc30317> how would I go about doing so?
<dark> sc30317, [] is a float list, ok?
<sc30317> ok
<dark> it's an 'a list for all 'a
<sc30317> excuse me?
<sc30317> bluestorm, how would I return its result directly instead of testing for a []
<bluestorm> well
<bluestorm> just write the expression "finish current_class w_current"
<bluestorm> after the declaration of the "finish" function
<bluestorm> that expression will call the finish function with those two parameters, and return its value
<bluestorm> (if it looks stangely simple, it's because it is)
<sc30317> haha ok
karuza has quit [Quit: ...]
<sc30317> hold on, ill test this
ski has quit [*.net *.split]
rbancroft has quit [*.net *.split]
patronus has quit [*.net *.split]
<drewbert> bluestorm: do you have an example of concatenating a list of lists somewhere?
<sc30317> bluestorm, what should I put instead of the exit 0?
<dark> List.flatten?
<bluestorm> sc30317: you should put the value you want to return
<sc30317> drewbert, just do it once and do a List.map
<sc30317> which would be w_current
<drewbert> none of this is making any sense to me
<drewbert> maybe I should take a break
<dark> drewbert, http://caml.inria.fr/pub/docs/manual-ocaml/libref/List.html List.concat or flatten, if you want to look the implementation you can see the source @.@'
slash_ has quit [Quit: Lost terminal]
<dark> i think it is List.rev_append with fold and in the end, a List.rev
<bluestorm> drewbert: what are you trying to do ?
<bluestorm> List.concat [[1;2;3]; [4;5]; [6]] is [1;2;3;4;5;6]
<drewbert> [[[1,2,3]][[4,5,6]]] -> [[1,2,3],[4,5,6]]
<drewbert> i'll look at the source for list.concat
<bluestorm> sc30317: is it better ?
<sc30317> bluestorm, yes!
<sc30317> I am now extremely close
<dark> sc30317, i was going to look for a polymorphism doc for you at google
<dark> but i found instead http://sds.podval.org/ocaml-sucks.html
<dark> :(
<sc30317> haha
<sc30317> i've read that
<sc30317> its pretty funny
<dark> the other results seems pretty good, http://www.google.com/search?q=ocaml+polymorphism (but actually i was trying to find a link to the manual.. maybe http://caml.inria.fr/pub/docs/manual-ocaml/manual003.html ?)
bluestorm has quit [Quit: Leaving]
lokydor has quit [Ping timeout: 260 seconds]
tmaedaZ is now known as tmaeda
Amorphous has quit [Ping timeout: 246 seconds]
* drewbert sighs.
tmaeda is now known as tmaedaZ
Amorphous has joined #ocaml
<dark> drewbert, express yourself :P
<dark> what's your problem?
<drewbert> RAWWRRRRRRR I don't understand. I'm trying to implement what is basically flatten.
<dark> class assignment?
<drewbert> yes
<dark> "basically"? with some minor differences?
<dark> drewbert, where are you from?
<drewbert> same in terms of input and output
<drewbert> maryland
<dark> 'in terms of input and output'? i can't understand
<drewbert> the same as flatten
<dark> you need to receive a list of lists at input, and output it flattened?
<dark> what is the syntax of the input, and of the output?
<drewbert> but if it were say a list of lists of lists as input, it would return a list of lists
<drewbert> Examples: concat_lists [[1;2];[7];[5;4;3]] => [1;2;7;5;4;3] and concat_lists [[[1;2;3];[2]];[[7]]] => [[1;2;3];[2];[7]]
<dark> it's still flatten
<dark> o.o'
<drewbert> okay, so I need to reimplement flatten
<dark> what you mean by input/
<dark> nothing to do with i/o?
<drewbert> no no
<dark> drewbert, can you use some library functions? or just bare recursion?
<drewbert> no library functions
<drewbert> we have a version of map and fold available to us
<dark> a clever way of cheating is writing fold as an .. wow
<dark> flatten is very nice with fold
<dark> fold = create an arbitrary data structure from a list
<drewbert> i started off with fold, confused myself, switched to map, confused myself, switched to basic recursion, confused myself and threw the temper tantrum you see before you
<dark> aahahhahahahaha
<dark> map will not do the job afaik
<dark> drewbert, you concat does not really need to be efficient, right? i think that a simple fold, maybe with a "reverse list" (you can write it as an auxiliary function).. will do the job nicely
<dark> can you use @?
<dark> or you must concatenate two lists manually?
<drewbert> I think manually
<drewbert> I've yet to see a @ in lecture.
<dark> let concat_lists list_of_lists = List.fold_left (fun acc el -> acc @ el) [] list_of_lists
<dark> do this works?
Yoric has quit [Quit: Yoric]
<dark> if yes, you need to use your own fold, and reimplement the @ as an auxiliary function
<drewbert> let me see
<dark> you know that fold receives an accumulator and the top of the list, and return an accumulator, right?
<drewbert> we covered fold, but in the "here's how you add up all the numbers in a list" sense
<dark> this accumulator is a "temporary" variable to hold the "current" concatenation of the first N lists.. its initial value is [] (passed to the fold), and it will be returned when the list_of_lists is exhausted
<dark> ... :)
<dark> but you know that in this example of adding numbers, the first argument is holding the "sum of previous numbers", and the second is the "next number", right?
<dark> like List.fold_left (fun previous next -> previous + next) 0 numbers
<dark> previous accumulates the value of previous iterations
<dark> next is the top of the current processing list, i.e the "next" value to be computed
<dark> the return value of (fun previous next -> previous + next) is of same type as previous, because it will be passed again to this function if necessary
<dark> but the type of next isn't necessarily equal to this; it's the type of the "first value" (i.e. 0 in this case)
<drewbert> i see
<dark> don't you think this is beautiful? :(
<dark> when you finally
<dark> understand this :( :(
<dark> :~
<drewbert> hrmmm
<dark> hm
<dark> acc @ el is wrong i think
<dark> maybe acc @ [el] ?
<dark> @_@'
<dark> i don't have an ocaml interpreter here :~
<drewbert> l::r -> l @ flatten r
<dark> hmm yes you can do that
<dark> i.. think
<dark> o.O
<drewbert> i don't totally understand what @ is
<dark> hmm my university has a server with ssh and ocaml, hmm
<dark> # [1; 2; 3] @ [4; 5; 6];;
<dark> - : int list = [1; 2; 3; 4; 5; 6]
<dark> this is @ o.o'
<dark> # let concat_lists list_of_lists = List.fold_left (fun acc el -> acc @ el) [] list_of_lists;;
<dark> val concat_lists : 'a list list -> 'a list = <fun>
<dark> # concat_lists [[1; 2; 3]; [4; 5; 6]; [7]];;
<dark> - : int list = [1; 2; 3; 4; 5; 6; 7]
<drewbert> so @ is concat two lists operator
<dark> yes, it's List.concat
<drewbert> lists.concat = lists.flatten
<dark> it works.. i'm constantly amazed with ocaml. i usually can't program in C or Java or C++ and expect it to run in the first time
<dark> nope
<dark> ahh
<dark> hmm
<dark> yeah, it's not list.concat
<drewbert> let rec flatten = function
<drewbert> [] -> []
<drewbert> | l::r -> l @ flatten r
<drewbert> let concat = flatten
<dark> it's List.append
<dark> Hm @.@
<dark> it works?
<drewbert> right out of /usr/lib/ocaml/list.ml
<dark> hahahaha
<dark> :)
<drewbert> well hopefully that works, but I'm not allowed to use it
<dark> you can steal this version... use my version with fold..
<dark> both works
<dark> i think after seeing the two versions, it's hard to create a different version
<dark> maybe a tail recursive one?
<dark> drewbert, you can de dishonest and pretend that you found the simple flatten definition by yourself
<dark> be*
<dark> or you can not pretend that, but state that this is the "obvious" definition since you saw it :P
<dark> i think my version, with fold, is tail recursive as long as fold and @ is (with the stdlib, fold is, and @ is not)
<dark> but you probably don't need to write it in this style
<drewbert> let rec concat_lists x = fold((fun(acc, el) -> acc @ el), [], x) works
<drewbert> you've been really helpful dark, thank you so much
<dark> you're welcome
<dark> i feel somewhat guilty
bmp has joined #ocaml
<drewbert> but I need to still replace @ with something else, but I think I know how I will do it
<dark> the real wtf here is that your fold receives a tuple
<drewbert> hahaha, I keep getting that
<dark> do you already know what is a tuple, but not what is currying?
<drewbert> the project was assigned before they taught currying
<dark> it's your professor "style"?
<drewbert> so they just make it take tuples
<dark> o.O
<dark> currying is more elementary than tuple in ocaml
<drewbert> but I guess they decided tuples were easier for people coming from java/c/ruby
<dark> hmmm it's not an freshmen course?
<drewbert> not, it's a 3rd year course
<dark> hm
<dark> 3rd year and you still saw no FP?
<dark> u.u
<drewbert> we've seen function pointers in c, and anonymous classes in java and high order functions in ruby
<dark> i suppose you at least can use this fold in, say, ruby (it's reduce there)
<dark> high order functions? hmm..
<dark> your teachers used ruby? nice :)
<drewbert> personally i think it was a bad decision on the part of the instructor, because everywhere I look for help I have to explain it
<dark> explain what?
<dark> bad decision: to use ruby?
<drewbert> explain why I'm using tuples instead of currying
<drewbert> bad decision: tuples instead of currying
<dark> yes i think so too. because then the "natural" functions, let f a b = .. instead of let f (a, b) = .. will look "unnatural" for the alumni
<drewbert> ruby is not a bad decision, I had a great time with ruby. I like scripting languages.\
<dark> int q (int a, int b); is a function that receives 2 parameters in C, but let f (a, b) = .. receives only one in ocaml (a tuple)
<dark> i am loving ruby too, i'm learning it :)
<dark> i know nothing about anonymous classes, but function pointers don't really make functional programming: in C, it's unnatural and undesirable (most of time) program in functional paradigm. by functional here i mean without explicit state (like mutable variables)
<drewbert> I like C, and ruby, and with a moderate amount of shame, PHP
<dark> hahahaha
<dark> i liked php in past
<dark> at about same time, mirc scripting was my favorite language on windows
<dark> two braindead languages :( i still remember most of their quirks :(
<drewbert> python is nice too, but I've had onlythe few scripts I had to write for work in it
<dark> ruby has a nice functional programming support, with high order functions, closures, etc.. (without high order functions, FP is really painful, but possible), but it does not have (usually) tail call elimination
<dark> so with some recursive functions you can easily have a stack overflow
<drewbert> Javascript is fun until you try to support IE.
<dark> (in ocaml, if you have "tail recursive" functions, it will be translated into a 'loop', and will not grow the stack)
<dark> i don't know much of javascript, but it is interesting
<dark> i like lua too :t
<drewbert> I have no idea what lua even looks like.
sepp2k has quit [Quit: Leaving.]
<dark> it's minimalistic. do you know scheme?
<drewbert> I know some ada?
<dark> it's like scheme (in minimalistic design), but with a syntax less arcane
<dark> ada is nothing like scheme
<dark> drewbert, with lua, there is just a data structure: hash tables. they are used to implement arrays, objects, ..
<drewbert> ah, then no
<dark> you can do some syntax sugar with ruby for 'feeling' some lua features
<dark> a.b in lua is just a["b"]
<drewbert> in javascript every variable is a hash, but it can also be a number of other things
<dark> so object.method is really a lookup for a string in hash table object
<drewbert> same in javascript
<dark> hm @.@
<drewbert> except there are prototypes
<drewbert> there are different levels to the hash table
<dark> in lua you can do "if a value is not found in this hash table, search this other hash table"
<dark> i.e. inheritance
<drewbert> and it looks first in the local hash table, and then goes up to the global scope
<drewbert> dark: yayyyy! http://pastebin.ca/1847699
<dark> :)
<dark> you don't need the ;;, right?
<dark> ;; is used only in the top level interpreter (and hmm it is needed in some ugly .ml programs)
<drewbert> yeah, the ;; is just there so that any errors I make don't pop up in lines later on
<drewbert> so I know where my errors are
<dark> hmmmmmmm it really does this? o.o''
<dark> if you don't put bare expressions in your program, then you will be fine
<dark> i.e. instead of print_endline "a" or let a = "b" in print_endline a, something like let _ = print_endline "a" or let () = let a = "b" in print_endline a
SEcki has quit [Remote host closed the connection]
zhijie has quit [Read error: Connection reset by peer]
zhijie has joined #ocaml
zhijie has quit [Read error: Connection reset by peer]
zhijie has joined #ocaml
zhijie has quit [Read error: Connection reset by peer]
zhijie has joined #ocaml
zhijie has quit [Read error: Connection reset by peer]
maskd has quit [Quit: leaving]
zhijie has joined #ocaml
<sc30317> dark, you here?
<dark> yes
<sc30317> I have this line
<sc30317> if is_finished = true || !count = maxiterations then w_current
<sc30317> how could I add in that I want to set count back to 0?
<sc30317> let count = ref 0;; is what I did initially out of the loop
<sc30317> then I called count from within the loop
<sc30317> I tried this
<sc30317> if is_finished = true || !count = maxiterations then begin !count = 0; w_current end
<sc30317> but it didn't like that
<sc30317> :(
<dark> do you know this is not the usual ocaml style, right?
<dark> if you want C, do this:
<dark> let (++) c = c := !c + 1
<dark> then, count++
<dark> hmm
<sc30317> ok
<dark> ++count
<sc30317> but I just want to set it back to 0 when is_finished is true
<dark> but anyway, you shouldn't design your system like this! :o but okay, you are still learning
<sc30317> yea
<sc30317> this is true :D
<dark> having "mutable state" is "imperative programming"
<dark> i.e., a variable you change thought your code
<sc30317> well I want to shy away from imperitive programming
<sc30317> how would you do this if you didn't want to use any imperitive?
<sc30317> because you would still need something to print which iteration you are on?
<dark> you can write all this kind of code with recursive functions
<dark> give me the whole function and i give you a recursive version of it
<sc30317> I am using a recursive function
<dark> ... o.o
<sc30317> dark, ok
<dark> okay, give the function :D
ulfdoz has quit [Ping timeout: 246 seconds]
<dark> sc30317, "mutable state" = variables that you change by assignment (a := b, etc)
<dark> how to eliminate mutable state: pass the state as a parameter to all functions that need it
<dark> if you need to change the state, call the function again with the new state
ulfdoz has joined #ocaml
<dark> then, you change the state in the "new" calls, but the old calls will continue to use the old state
<dark> sc30317, why does you receive a tuple as parameter?
<sc30317> which are you talking about?
<dark> let a(b, c, d) = .. is not a multi parameter function
<drewbert> can someone tell me how i can get "let pos_of_xy(x, y, s) = ((x * find_board_size(s)) + y)" to return an int?
<dark> it receives just one parameter, a tuple (in this case, a triple)
<sc30317> which function?
<dark> drewbert, drewbert x * (find_board_size s) + y
<dark> sc30317, sde3
<dark> sc30317, why are you are using ; instead of in? o.o'
<sc30317> because that is what I am supposed to pass to sde3
<sc30317> and I am using ; instead of in because that's how it worked?
<dark> a; b means do a, then do b
<drewbert> dark, that did it, thanks, I need to remember that
<dark> where count is defined, sc30317? it's a.. global variable?
<sc30317> yea
<dark> if you want to change a global variable,you are automatically programming in imperative style
<sc30317> let count = ref 0;;
<sc30317> oh
<dark> in functional programming, you would just return the new value of count
<sc30317> well I would like to avoid that
<dark> along with other values
<sc30317> ok
<dark> sc30317, i guess this is really hard for someone that never studied FP before :(
<sc30317> dark, definitely
<sc30317> what would I have to change in my sde3 to make it functional?
<dark> first thing, you need to design the flow of the program in a different style
<sc30317> ok....
<dark> instead of calling a function that will change a global var (and then checking for this var), you must call a function that will return what it usually returns, plus the new value of the external variable
<dark> and then use this new value in the rest of program
<dark> something like
<dark> let new_value_of_count, other_things_returned = function_call .. in ..
<sc30317> where would I put this in the code?
<dark> in the code that will call sde3
<dark> if you have let f a = (1 - a, 2 + a)
<dark> you can do let q, w = f 2
<dark> then q is -1, w is 0
<dark> then f returned two things (in reality a tuple)
<sc30317> well then how would you print out the number in the loop
<sc30317> for example, here is what my output of the current program is
<dark> print?
<dark> maybe print_int new_value_of_count?
<dark> Print.printf "%d\n" ..?
<sc30317> I need to keep that same structure
enthymeme has quit [Quit: rcirc on GNU Emacs 23.1.1]
<dark> also, it is usually recommended for you to make sde3 to actually receive 3 parameters (with let sde3 trainData lr maxinterations(it ought to be interactions..) wint = .. instead of the (, , ,).. unless the tuple is actually just one variable
<sc30317> the tuple is just 1 variable (a list)
<dark> no, not a list
<dark> but ok, if the tuple is just one var you can use this style
<sc30317> well l have to pass it just as shown in the pastebin
<dark> but hey
<dark> this count variable, is used just inside your function?!
<dark> omg, :)
<sc30317> yes
<dark> finish must receive count as parameter
<sc30317> ok
<dark> it changes count inside it, right? instead that, you send the new value of count to finish
<sc30317> yes, finish changes count inside it
<sc30317> that is the only place count is used
<dark> this is the essence of imperative programming
<sc30317> so I could just change my finish function
<sc30317> and make it all imperitive
<dark> functional programming does exactly the same thing by passing the state as parameter
<sc30317> what would I need to change in the finish function?
<dark> well it is already too imperative for the usual ocaml practice
<dark> let rec finish w_current current_class new_mult new_vect error_vect count =
<dark> it already receives count as parameter, but this count is a reference, right?
<sc30317> yes
<dark> make this count be just a int
<sc30317> count is from 0 to maxiterations
<dark> and then call in the recursion: finish w_current current_class new_mult new_vect error_vect new_value_of_count
<dark> got it?
<sc30317> no
<sc30317> I don't understand
<dark> call finish w_current current_class new_mult new_vect error_vect 0
<dark> then inside it, call in the recursion maybe finish w_current current_class new_mult new_vect error_vect (count+1)
<dark> and check for count <= maxiterations to decide if you want to go thought recursion
<sc30317> but if I call 0 in finish w_current current_class new_mult new_vect error_vect 0
<dark> hm?
<sc30317> then how will it know in the recursion?
<dark> it will receive count as 0, right?
<sc30317> I'm trying to get rid of the imperitive stuff
<dark> then you do (count +1) for the next value of count
<dark> this is the way of getting rid of it o.o
<sc30317> I just want to get rid of the global var count right?
<sc30317> I want to make my program non iterative
<dark> you want to get rid of mutable state
<sc30317> yes
<dark> hmm o.o
drewbert has quit [Read error: Connection reset by peer]
<dark> your function is tail recursive
<sc30317> yes
<dark> all tail recursive functions describe iterative processes
<dark> this is how you achieve iterations with fp, so yes, you want it to be 'iterative', but functional
<sc30317> correct
<dark> also, if you do an let a = b in , don't increase the indentation
<sc30317> ok, I wont
<sc30317> so how would I do that?
<dark> !count = maxiterations then w_current , first you change this to count = maxiterations then w_current
<dark> incr count; then you get rid of this
<dark> then you change finish w_current current_class new_mult new_vect error_vect count into finish w_current current_class new_mult new_vect error_vect (succ count)
<dark> instead of succ count you can put count + 1
<dark> then you call it as finish w_current current_class new_mult new_vect error_vect 0
<sc30317> ok
<dark> also, try to indent your code with 2 spaces (i sometimes use tabs when indenting ocaml code, from C... but this is contrary to all other ocaml code out there)
<sc30317> ok
<dark> emacs helps with that
<sc30317> let me know if this is correct ->
<dark> no
<sc30317> what did I mess up?
<sc30317> I was trying to follow what you said-> it was sort of tricky
<dark> you didn't understood the concept i think, it would be http://pastebin.com/BvijYWZt
<dark> i will try to code something in functional style using C for you
<sc30317> dark, when I do what you just said:
<sc30317> it give me
<sc30317> Error: This expression has type int ref
<sc30317> but an expression was expected of type int
<sc30317> on this line
<sc30317> finish w_current current_class new_mult new_vect error_vect (count+1)
<dark> hmmm int ref? remove your old let count = ref 0 and try again
<dark> and see the actual error
<dark> seems like a name clash
bmp has quit [Quit: bmp]
<dark> sc30317, i havent tested, but http://pastebin.com/PU97Euf1
<sc30317> I did remove the let count = ref 0
<sc30317> dark, I think you were supposed to send that pastebin to someone else
<sc30317> it is definitely an error within that loop
<dark> ok, int array is an error
<dark> syntactical
<dark> but this is the general idea
<dark> Printf.printf "at At iter: %d current weights are: " !count;
<sc30317> what?
<dark> here is the error
<sc30317> oh
<sc30317> should it just be count?
<dark> change to Printf.printf "at At iter: %d current weights are: " count;
<dark> yes, it is not a reference anymore
<sc30317> oh ok
<sc30317> gotcha!
<sc30317> that makes sense
<dark> http://pastebin.com/HzbA6qg4 will this compile?
<dark> it's the old "for", in functional style
<sc30317> yea that worked
<sc30317> after I included the libraries
<dark> no idea why it also printed a garbage value, lol
<dark> ah
<dark> <= size
<sc30317> dark, is there an equivalent of a break in ocaml?
<dark> sc30317, you are evil :D
<sc30317> hah
<sc30317> never mind
<dark> sc30317, i think there is a break, for "for" and "while"
<sc30317> gotcha
<dark> for recursions you maybe want exceptions
<dark> ahhh, there is no break, but there is a macro for it
<dark> 'The macros implement these statements as exceptions'
<sc30317> this is trivial, but:
<sc30317> right now my output is this
<sc30317> # sde3(anddata, 0.25, 10, [-0.147805932376010363; -0.0597686816135509225; -0.0093318500789426051]);;
<sc30317> at At iter: 0 current weights are: -0.147806 -0.059769 -0.009332
<sc30317> at At iter: 1 current weights are: 0.102194 0.190231 0.240668
<sc30317> at At iter: 2 current weights are: -0.397806 0.190231 0.240668
<sc30317> - : float list =
<sc30317> [-0.397805932376010363; 0.190231318386449078; 0.240668149921057395]
<sc30317> I don't want it to show iter: 2 because its the same as the float list
<dark> hmm
<dark> you could print before the if
<dark> printf ..; if ..
<sc30317> if I do that, it prints 3 iterations!
<sc30317> that was what I thought too
<sc30317> but here is what happens if you put the printf before the if
<sc30317> # sde3(anddata, 0.25, 10, [-0.147805932376010363; -0.0597686816135509225; -0.0093318500789426051]);;
<sc30317> at At iter: 0 current weights are: -0.147806 -0.059769 -0.009332
<sc30317> at At iter: 1 current weights are: 0.102194 0.190231 0.240668
<sc30317> at At iter: 2 current weights are: -0.397806 0.190231 0.240668
<sc30317> at At iter: 3 current weights are: -0.397806 0.190231 0.240668
<sc30317> - : float list =
<sc30317> [-0.397805932376010363; 0.190231318386449078; 0.240668149921057395]
<dark> interesting
<sc30317> yea
<sc30317> any other ideas?
mutewit has quit [Read error: Connection reset by peer]
<dark> what about returning ()?
<dark> then you have the result just as an output
<sc30317> oh ok
<dark> or, returning a list of all values
<dark> and in the end printing the list
<sc30317> how do you mean?
<dark> a list which last element is [-0.397805932376010363; 0.190231318386449078; 0.240668149921057395]
<sc30317> so instead of then w_current, just put then ()?
<dark> if you want this approach, yes
<dark> the most "clean" approach is:
<sc30317> that just returns a unit
<dark> yes o.o
<sc30317> what is the most clean approach?
mutewit has joined #ocaml
<dark> http://pastebin.com/NVEhqypR you can use this as an auxiliar function
<dark> to print a list with all results
<dark> hmm no, syntax error
<dark> http://pastebin.com/kWTqtYXN maybe this? :P
<sc30317> where would I call that?
<dark> so if you return a list with all those results, you can then (hopefully) print this list with this function
<dark> you would call this on the result of finish
<dark> or maybe the result of sde3
<sc30317> idk
<dark> maybe print_results ( finish ..) on the bottom of sde3
<dark> or maybe let results = finish ... in print_results results
<sc30317> there has to be an easier way to handle this
<dark> but then finish need to return the whole data
<dark> ah hehe
<dark> i said cleanest
<sc30317> haha
<sc30317> im all for dirty if it works
<sc30317> :D
<dark> because that way, finish is truly functional
<dark> hmm @.@
<sc30317> this is the absolute last thing I have to implement in this program
<dark> :)
<sc30317> yea tell me about it
<dark> the problem is: it matters if you call finish one or two times
<dark> if you call it twice, you get the results printed twice
<dark> so it has side-effects
<sc30317> yea
<sc30317> are you talking about how my code is working right now?
<sc30317> how I call finish 2x at the end?
<dark> the idea of functional programming is isolating side-effects from your program logic
<dark> no
<dark> no, i'm talking about the general issues of fp
<sc30317> gotcha
<dark> finish implement program "logic", it shouldn't do I/O by itself (with FP)
<dark> but well
<dark> :D
<sc30317> hahah
<sc30317> so any other ideas?
<dark> no :)
<sc30317> what if I started with 1
<sc30317> and printed count -1
<dark> ? o.o'
<dark> well the printfs is debugging, or production?
<sc30317> production
<dark> the job of this function is to print or to return floats?
<sc30317> both
<sc30317> here is what I have now
<dark> this is poor design
<sc30317> # sde3(anddata, 0.25, 10, [-0.147805932376010363; -0.0597686816135509225; -0.0093318500789426051]);;
<sc30317> at At iter: 0 current weights are: -0.147806 -0.059769 -0.009332
<sc30317> at At iter: 1 current weights are: 0.102194 0.190231 0.240668
<sc30317> at At iter: 2 current weights are: -0.397806 0.190231 0.240668
<sc30317> - : float list =
<sc30317> [-0.397805932376010363; 0.190231318386449078; 0.240668149921057395]
<sc30317> #
<dark> your boss designed it to print and return floats, or yourself?
<sc30317> this is what I want
<sc30317> # sde3(anddata, 0.25, 10, [-0.147805932376010363; -0.0597686816135509225; -0.0093318500789426051]);;
<sc30317> at At iter: 0 current weights are: -0.147806 -0.059769 -0.009332
<sc30317> at At iter: 1 current weights are: 0.102194 0.190231 0.240668
<sc30317> # sde3(anddata, 0.25, 10, [-0.147805932376010363; -0.0597686816135509225; -0.0093318500789426051]);;
<sc30317> at At iter: 0 current weights are: -0.147806 -0.059769 -0.009332
<sc30317> at At iter: 1 current weights are: 0.102194 0.190231 0.240668
<sc30317> boss
<sc30317> - : float list =
<sc30317> [-0.397805932376010363; 0.190231318386449078; 0.240668149921057395]
<dark> hm o.o
<dark> hmm the problem is the 'is_finished' part
<dark> what you want is: to print all, but refuse to print the last
<sc30317> yea
<sc30317> correct
<dark> so you need to know in advance if you are just before the last
<dark> you can know with the count logic, but the is_finished logic is more complex
<sc30317> and then the w_current is given at the end as - : float list =
drk-sd has quit [Quit: night]
<sc30317> yea
<sc30317> this is true
<dark> you need to look the compare_vc.. function and see if you can infer this from that
<dark> if not, you can't rely on the finish function for printing it the way you want, unless you want some junk code
<dark> such as passing to finish, as parameter, the value of "previous" call
<sc30317> I am looking at the compare vc code
<sc30317> it just compares 2 inputs
<dark> and printing it, instead of printing the "current" call
bmp has joined #ocaml
<sc30317> here is the compare_vc_current_class
<sc30317> (*Compares 2 vectors: if correct = true then bool = "true" *)
<sc30317> let compare_vc_current_class input1 input2 = List.for_all2 (fun x y -> x > 0.0 && y > 0.0 || x < 0.0 && y < 0.0) input1 input2
<dark> you can put the if logic in the end, maybe
<dark> just before the recursion
<dark> couldn't you?
<sc30317> I could try that
<dark> but well this is just what i was saying and didn't worked
<dark> well this is not my style of ocaml code :( this code is too complex
<sc30317> nope, that does the same thing
<sc30317> I think this is the easier part of my code?
<dark> i don't find complex to throw some folds at the problem, but getting a loop with ifs right is cumbersome
<dark> very error-prone for me
<sc30317> thats where we differ dark
<sc30317> :D
<dark> I think that that's why naive C programmers have so many subtle errors.. and even experienced ones find difficult to write bug-free C code
<sc30317> its true
<sc30317> I am just wondering why if I put the print before the if statement it doesn't work
bmp has quit [Client Quit]
<dark> buffer overflow, etc, etc, all instances of this same problem (most of time). "does the index of the loop go to n or n-1?" etc
<dark> i don't know, i am bad with this kind of logic :(
<sc30317> yea, I had to take a security class in college where we learned about buffer overflow
<dark> :)
<sc30317> I would even take junk code at this point dark
<sc30317> this is all that is holding me back
<sc30317> any even junk code ideas?
<dark> omg
<sc30317> what?
joewilliams_away is now known as joewilliams
<dark> it's really a problem just returning a list of all results? then print all but the one you want to return
<sc30317> is that not what we are doing?
<dark> no
<dark> you are returning just the last result
<dark> that happens to be a list, but it's the result
<dark> and you are printing the intermediate values
<dark> you can just return all of them
<dark> a list of lists
<sc30317> how?
<dark> hmmm.. first, something
<dark> w_current current_class new_mult new_vect error_vect
<dark> why are you passing this as parameter if this will not change?
<dark> make this local lets
<dark> then, you can pass to finish just two things: a) the count variable, b) an accumulator that will hold all lists that were processed
zhijie has quit [Read error: Connection reset by peer]
<sc30317> ok... still confused
<dark> hm o.o
bmp has joined #ocaml
<dark> but well, printing before the if should work!
zhijie has joined #ocaml
<dark> paste a code with it printing before the if :P
<sc30317> yea, i knnow
<sc30317> ok
<dark> and oh, you *are* changing the values, but keeping the same name! omg!
<dark> please don't hide variables with let!
<sc30317> # sde3(anddata, 0.25, 10, [-0.147805932376010363; -0.0597686816135509225; -0.0093318500789426051]);;
<sc30317> at At iter: 0 current weights are: -0.147806 -0.059769 -0.009332
<sc30317> at At iter: 1 current weights are: 0.102194 0.190231 0.240668
<sc30317> at At iter: 2 current weights are: -0.397806 0.190231 0.240668
<sc30317> at At iter: 3 current weights are: -0.397806 0.190231 0.240668
<sc30317> - : float list =
<sc30317> [-0.397805932376010363; 0.190231318386449078; 0.240668149921057395]
<dark> for the sake of your own sanity after some days :P
<sc30317> haha, I will do
zhijie has quit [Read error: Connection reset by peer]
<sc30317> well I passed them so I could use them recursively
<sc30317> that last test run was if the Print statement is before the if
<dark> errrm but you don't need to keep the same name
<dark> sc30317, but paste the code
<sc30317> ok
<sc30317> ok
<sc30317> that is the code
joewilliams is now known as joewilliams_away
zhijie has joined #ocaml
zhijie has quit [Read error: Connection reset by peer]
<dark> i think i know where the error is, but first i'm fixing your indentation.... [yes that's odd]
bmp has quit [Quit: bmp]
<sc30317> its cool
<dark> also, fixing the variable names..... to actually reflect usual ocaml practice...
<dark> i'm kind of a programming style nazi
<sc30317> haha, thats a good think dark
<dark> http://pastebin.com/6Y2MeK0P see if this works
<dark> i changed all "new values" of variable to variable'
<sc30317> syntax error
<dark> where?
<dark> and started tracking down if you are using the new or the old value
<sc30317> at the end
<dark> ah
<dark> i ommited the in ... part
<dark> you can put it of course
<dark> if this is the style of your code :)
zhijie has joined #ocaml
<sc30317> that still prints all 3 iterations
<dark> really? o.o
<sc30317> yea
zhijie has quit [Read error: Connection reset by peer]
<dark> ok, you probably can use something like that: a function that receives a parameter, stores it in a place, and whenever you call it with another parameter, it prints the previous value, and update it with the new value
<dark> seems like a valid approach
<sc30317> excuse me?
<sc30317> what do you mean?
zhijie has joined #ocaml
<dark> hmmm.. i mean exactly what i said, o.o i can give you a proof of concept, hold on
<sc30317> thanks dark
zhijie has quit [Read error: Connection reset by peer]
zhijie has joined #ocaml
<dark> http://pastebin.com/TXjYrEDe i haven't tested, so there may be errors, but the general idea is
zhijie has quit [Read error: Connection reset by peer]
<sc30317> unbound constrictor Value
<dark> ops
<dark> Some value
<dark> suppose you have a function print_my_values for printing values of type A. you can then create a delayed function, called print_my_values_in_a_delayed_fashion, like this: let print_my_values_in_a_delayed_fashion = make_delayed_printer print_my_values
<dark> (the descriptive names are just for making it more obvious)
<sc30317> now where would I add this delayed into my function?
<dark> in some place, out of this sde3 function
<sc30317> ok then where would I call it?
zhijie has joined #ocaml
<dark> then you create a function out of sde3 function too, that will print a w_current
<dark> but is delayed
<dark> like:
_unK has quit [Remote host closed the connection]
<dark> then in your code, to print, you just call print_it_delayed count w_current
<dark> o.o'
<sc30317> where do I call that?
<sc30317> where I was calling w_current?
<dark> it will receive a value.. cache it.. in the next call, it will print the cached value, and substitute the cache with the new parameter
<dark> you call it where you were calling this printfs
<sc30317> ok
<sc30317> so instead of the printfs
<dark> in finish, in the block of printfs, maybe inside the else?
<dark> but i think you have to go back to your old design
<sc30317> it gives me an error trying to print w_current in
<sc30317> if is_finished = true || count = maxiterations then w_current
<dark> there is a type of called 'a option, that can be either None or Some x. None here means "nothing is stored", Some x means "x is stored"
<dark> hmmm? no, you print it with print_it_delayed count w_current
<sc30317> so I do
<dark> ok, paste your modified function
<sc30317> ok
<dark> you need a ; after the print
<dark> just like you needed with printfs
<sc30317> just what I thought
<sc30317> that prints just the float list
<sc30317> and none of the iterations?
<dark> really? o.o the float list in the end isn't really a print
<sc30317> yea
<sc30317> here h/o
<sc30317> nope, that STILL prints out 3 lists XD
<sc30317> # sde3(anddata, 0.25, 10, [-0.147805932376010363; -0.0597686816135509225; -0.0093318500789426051]);;
<sc30317> at At iter: 0 current weights are: -0.147806 -0.059769 -0.009332
<sc30317> at At iter: 1 current weights are: 0.102194 0.190231 0.240668
<sc30317> at At iter: 2 current weights are: -0.397806 0.190231 0.240668
<sc30317> - : float list =
<sc30317> [-0.397805932376010363; 0.190231318386449078; 0.240668149921057395]
<sc30317> #
<sc30317> here is the code
<sc30317> same thing happens if you put it before the if statement
<dark> but, but.. try this: let pint = delayed_print (Printf.printf "%d\n")
<dark> call pint 10;; then pint 11;;
<dark> pint 10 should do nothing, pint 11 should print 10
<dark> ah...
<dark> sc30317, remove your printf from there...
<dark> or call print_it_delayed, or the printfs, not both..
<sc30317> so like
<sc30317> List.iter (Printf.printf "%f ") print_it_delayed count w_current;
<sc30317> like that?
<dark> no
<dark> just print_it_delayed count w_current;
<dark> if you look my code, you will see i already call List.iter
<dark> i just copied and pasted your code into there (but i'm not sure it's working..)
<sc30317> sorry, didn't see that
<sc30317> # sde3(anddata, 0.25, 10, [-0.147805932376010363; -0.0597686816135509225; -0.0093318500789426051]);;
<sc30317> - : float list =
<sc30317> [-0.397805932376010363; 0.190231318386449078; 0.240668149921057395]
<sc30317> #
<sc30317> thats what happens
<sc30317> it doesn't ever print the iterations
<sc30317> it just prints the output
<sc30317> (that is with just using print_it_delayed count w_current;
<dark> i don't have your entire code to test, but it's working here: http://pastebin.com/JnKGStB6
<sc30317> could it be because that you are using an int, and I am using a list of floats?
<dark> http://pastebin.com/dAE0SfZL it's refusing to print the "last" element
<dark> no, make_delayed_printer is polymorphic
<sc30317> gotcha
<sc30317> then why wouldn't it be printing out the iterations?
<dark> i maybe screwed the definition of the function for handling your list of floats
<sc30317> within which function?
* dark will test
<dark> the print_it_delayed
<sc30317> ok
<dark> you could test it too
<sc30317> would it be easier if I gave you the whole code and a test case?
<dark> print_it_delayed 10 [1.0; 2.0]
<dark> you don't need to
<dark> i don't have ocaml here too; i'm accessing a server on my uni with ssh..
<sc30317> oh ok
<sc30317> where would the print_it_delayed be messed up so that it wouldn't print the iterations?
<dark> ok, print_it_delayed is not working :D
<sc30317> haha
<dark> but the general mechanism is
<sc30317> any other ideas why it wouldn't be working?
* dark trying to understand
<dark> ah
<dark> duh
<dark> omg
<sc30317> whats up?
<sc30317> dark, ?
<dark> http://pastebin.com/AfQFjPck and then you use print_it_delayed(count, w_current)
<dark> i was testing :P
<dark> omg = the logic of my function was totally wrong
<dark> then i decided to put the non-delayed printer in the outside
<dark> and tested it all :P
<dark> i was creating a new "printer queue" object each new function call
<dark> what i should do is to create it, and reuse it every new call
<sc30317> that gives me errors
<dark> such as?
<sc30317> Error: This expression has type float list -> int * float list
<sc30317> but an expression was expected of type int
<dark> you need to use print_it_delayed (count, w_current)
<dark> with (a, b) not without (yes there is a difference)
<sc30317> yea
<sc30317> :(
<sc30317> still prints all the iterations
<dark> ? o.o
<sc30317> yea tell me about it
bmp has joined #ocaml
<sc30317> have you ever used screen before?
<dark> screen? yes
<sc30317> here is the whole thing
<dark> http://pastebin.com/BQqyXVFK "here it is working"
<sc30317> thats the whole program
<dark> put the print inside the if
<dark> you want to do the whole old logic
<dark> the delayed printer is a hack for getting rid of the "last"
<dark> the last will be sent to the printer, but will not be printed
<sc30317> :D :D :D
<sc30317> got it
<sc30317> I <3 you dark
<dark> ... but you can't reuse the print_it_delayed for another call, right?
<dark> you can define it as being local to sde3
<dark> so that you build a new "delayed printer" object each call of it
<dark> (you can define it in the top, with let print_it_delayed = make_delayed_printer print_one_entry in)
<sc30317> how would you define it local to sde3? just add it within sde3?
<dark> yes, but with in at the end
<dark> it would be: let sde3(trainData, lr, maxiterations, winit)= let print_it_delayed = make_delayed_printer print_one_entry in <... rest of definition >
<dark> with appropriate identation and line breaks etc
<sc30317> dark, you are awesome man
<dark> thank you
<sc30317> no problem
<dark> it's fun to help with such problems, but hey
<dark> you shouldn't try to fool your boss, because he can verify some of the code wasn't from yourself
<dark> i think
<sc30317> definitely
<sc30317> I will tell him I got help for sure
<dark> that 'make_delayed_printer' is the kind of thing you would find if you searched google for ocaml snippets and such
<sc30317> ok
<dark> functional programming is full of such things :)
<sc30317> gotcha
bmp has quit [Quit: bmp]
<dark> let make_counter () = let i = ref 0 in let counter () = i := !i + 1; !i in counter
<dark> then let c, d = make_counter(), make_counter()
<dark> c and d are two independent counters
<dark> c() is 1, then 2, then 3..
<dark> [ in fact this is imperative, but it's a somewhat common style in ocaml ]
<dark> [ it's not common with, say, c, because it does not have lexical scope ]
<sc30317> gotcha
drewbert has joined #ocaml
<drewbert> hey dark, this is ridiculous, it was working, then it stopped. what was your answer to getting "let pos_of_xy(x, y, s) = ((x * (find_board_size(s))) + y)" to return an int?
<dark> o.o''
<dark> let pos_of_xy (x, y, s) = x * (find_board_size s) + y
<dark> don't overuse parenthesis
<drewbert> let pos_of_xy(x, y, s) = x * (find_board_size s) + y doesn't work either
<dark> then find_board_size s is not returning an int,
<dark> or x is not an int
<dark> or y is not an int
<dark> o.o'
<dark> also it's a (b, c) not a(b, c) in my style :P to emphasis that (b, c) is a single parameter
<drewbert> thanks, I'll take all the style tips I can get
<dark> ^^
<dark> check the type of find_board_size, it's something -> int?
<drewbert> let find_board_size b = int_of_float(sqrt(float_of_int(length(b))))
<dark> you can also paste the type error here
<dark> @.@
<dark> the last length(b) should be written as length b
<dark> int_of_float (sqrt (float_of_int (length b)))
<dark> ok, then paste the type error :P
<drewbert> File "testPuzzle1.ml", line 19, characters 19-26:
<drewbert> Error: This expression has type int * int * int
<drewbert> but an expression was expected of type int * int * 'a list
<drewbert> testpuzzle.ml line 19 is File "testPuzzle1.ml", line 19, characters 19-26:
<drewbert> Error: This expression has type int * int * int
<drewbert> but an expression was expected of type int * int * 'a list
<drewbert> oops
<drewbert> sorry
<dark> which expression?
<dark> is s a list?
<drewbert> testpuzzle.ml, line 19 is "prt_int (pos_of_xy (0,0,2)) ;;"
<dark> what is length..?
<dark> you did open List, didn't you?
<drewbert> let length x = fold ((fun (a,y) -> a+1), 0, x)
<dark> ah.........
<dark> okay, then length s will suppose that s is a list
<drewbert> no, not allowed to use anything outside pervasives
<dark> then you can't really call pos_of_xy (0, 0, 2)
<dark> you need to call pos_of_xy (0, 0, a list)
<dark> or else create another function,that does not call length on the third argument
<drewbert> alright, dude, I'd order you a box of cookies a box of cookies if you'd let me
<dark> hahahahaha
<drewbert> whoah, didn't mean to type that twice
<dark> :)
<drewbert> my brain is in recursive mode right now I guess
<dark> lol
<dark> i was thinking something along those lines
<dark> drewbert, sometimes i hang out in the undergrad lab.. because people usually call me when they got compiler errors (it's specially amusing with C++, two pages of errors and usually one needs only the line number to fix it...)
<dark> i think it is fun =p
<dark> hmm not 'because'
<drewbert> c++ errors are so ridiculous. to be honest I don't really have the stomach for c++, it's too messy. c is the best lower-level language I've dealt with.
<dark> i don't actually enjoy c++, but i will not like java either
<dark> i like c
<dark> i am in a phase that 'all software sucks' is starting to make sense :(
<drewbert> hah
<drewbert> Once you have a good framework going a project is fun for me.
<drewbert> I don't like java simply because it's too bulky. Its behaviors for inheritance, classes, templates, and all that are great, but it is too much work to perform basic operations.
<dark> "You'll never find a programming language that frees you from the burden of clarifying your ideas" i like this quote
<dark> i'm enjoying sinatra currently
<dark> i have no problem with it for web development, but well i am no web developer =p
<drewbert> I'm desperately trying to work my way out of the web development world.
<dark> "out"?
<dark> you don't enjoy it?
<dark> well, i like to make web programs for myself... my own browser, my own needs
<drewbert> Not the aspect in which I'm involved.
<dark> but well i like to make quick shell scripts too :P
<dark> you mentioned IE earlier, didn't you?
<drewbert> I did.
<dark> *this* is not pleasurable
<dark> i once saw a haskell lib for writing javascript.. it compiles into js. i don't know how well it performs, but the whole idea is nice: if you don't find a technology bearable, it's often productive to write tools that will automatize your contact with it
<dark> maybe there are libs that will solve most IE quirks in a platform-agnostic way
<dark> in fact, the challenge of writing a lib for getting rid of IE problems (maybe a template lib that will be compiled into quirked html + quirked css?) is more fun than writing <!--[if IE 6]> many times in each app your write. but it is indeed more difficult :P
<drewbert> well there's jquery
<drewbert> which I donated to
<drewbert> since it made my life significantly easier
<dark> hmm nice :)
<drewbert> but ie still breaks stuff all the time. and it is *SO* much slower than firefox or chrome.
<drewbert> and the biggest problem is that people refuse to upgrade. I would be annoyed with support ie8, but I have to support ie 6, 7, 8, and firefox
<drewbert> webkit browsers are unfortunately ignored most of the time. we have a lot of code that goes if(ie) dosomethingforie(); else dosomethingforfirefox();
<dark> hmm, but why should people upgrade? for the non-geek, computers are like tvs or freezer
<dark> hmm yes
<drewbert> well, those people we work with are government organizations with IT departments that work in the traffic responder sector.
<dark> if ie still breaks stuff all the time, the "browser-agnostic" abstraction is broken. if it does not work in safari (or in lynx, or in speech-synthesizers) it's indeed broken
<dark> drewbert, ah, you have some serious clients then
<drewbert> and ie6 is not safe, so we shouldn't be sending people's traffic accident dta over to insecure browsers
<drewbert> data*
<dark> hm o.o
<dark> you have a strong case for blocking ie6 then
<dark> you can bring this issues to your clients
<dark> not the compatibility part, but the security one
<drewbert> haha we have. they refuse to upgrade for "security reasons" which I think means laziness. they are using ssh 1.0 too! for "security reasons"
<dark> but i would say that firefox isn't much better :(
<dark> and i'm a free software guy
<drewbert> really? I've never had a security issue with firefox in windows or linux.
<dark> they appear all the time, o.o
<drewbert> other than downloading and then independently executing malicious content through it
<dark> you didn't "had" issues, but you surely used a compromised firefox for some time, without knowing it, o.o
<drewbert> they do appear, but people with firefox tend to update faster
<drewbert> dark: you are correct.
<drewbert> I cannot argue with that statement.
<dark> but maybe my wording wasn't very good; it is somewhat better
<drewbert> i know nobody using firefox 2.0. I know lots of people using ie6
<dark> hmm yes. also mozilla actually solve security issues faster
<dark> and really, to argue that security issues is preventing someone upgrading from ie6 is something i would expect to see in thedailywtf.com :P
<dark> drewbert, are you a freelancer? and also a undergrad student?
<drewbert> I am an undergrad. I used to freelance, but now I have two jobs and a girlfriend.
<dark> i know a freelancer that thought in abandoning university.. but now he is back, trying to finish it quick
<dark> wow
<drewbert> I know, i have been on spring break for the past week, and have pulled several all-nighters during spring break trying to get everything done.
<dark> i can hardly manage to go to sleep in the right time, and go to the classes in time too.. i have a wildly random sleep cycle :P i have time for basically nothing
<drewbert> but you're a grad student, it's expected
<drewbert> Once of my jobs is web application for displaying traffic data, and the other is a really cool reading images to build 3d models of things.
<dark> well i'm a undergrad student
<drewbert> oh you are
<dark> hmm
<drewbert> what university?
<dark> ufrn (natal, brazil)
<drewbert> I hear brazil is hopping right now.
<dark> hopping?
<drewbert> there is a lot going on in that country
<drewbert> like china
<dark> hmmm @.@ what do you mean? @.@
<dark> where are you from? (maybe i already asked..)
<drewbert> I am from the United States.
<dark> curiously, i have Java and C classes this semester, but when I am back to home, or have some free time, I do small things in ruby or haskell. i really want to get rid of my current classes as quick as possible, they all suck :(
<dark> there is a lot of things happening in USA too, o.o
<dark> =)
<drewbert> people are all so angry and crazy here though
<dark> it's more common for us receiving US news than the opposite
<drewbert> almost 20% of the country thinks barack obama is evil and trying to destroy the country
<dark> the obama healthcare plan is news here, o.O
<dark> 20%?
<dark> destroy with..? new healthcare system?
zhijie has quit [Quit: Leaving.]
<drewbert> they think that socialism is the end of the world and that he is destroying capitalism.
<dark> hmmm.. i thought he would be acclaimed as the leader that pulled up US from the recession
<drewbert> I mean approximately 40-60% of the country is opposed to him. and that's okay. you can not like his policy. I'm not trying to make a political argument here. but there are a lot of people that really think he is crazy evil
<dark> but to think about it, roosvelt was called communist with his 'new deal' too
<drewbert> we are not out of the recession yet.
<dark> i just think that more than 20% thought that bush were crazy, evil, and was trying to destroy usa
<dark> so a) all US presidents are like that or b) it's okay and normal people to think that sort of thing
<dark> i'd go with b), it's like this here too o.o
<drewbert> I am young, but I think it is a relatively new thing. The country did not used to be this polarized.
zhijie has joined #ocaml
<drewbert> but
<drewbert> we are offtopic
<dark> it is not off topic if nobody is watching :D
<drewbert> You make good sense.
<dark> drewbert, i think the presidential system is polarized, just like this. it was worse in the past maybe (lincoln, etc)
<dark> the nation must make a definite, binary choice, when it could make a fuzzy one
<drewbert> it was worse around the time of lincoln, but around the time of lincoln was the bloodiest war in american history. things need to be done for anything gets that bad.
<dark> drewbert, here the public university is free
<dark> public health is free too. in basic levels it has poor quality and is too full. but with complex things like organ transplant and the aids program, it's working very nice (in both cases, 100% free)
<dark> but brazilian public system isn't really an example. too much corruption etc
M| has quit [Ping timeout: 246 seconds]
yakischloba has quit [Quit: Leaving.]
<drewbert> dark: in america we have our own form of corruption, but it is called "waste"
oc13 has joined #ocaml
drewbert has left #ocaml []
zhijie has quit [Quit: Leaving.]
ygrek has joined #ocaml
tmaedaZ is now known as tmaeda
ttamttam has joined #ocaml
zhijie has joined #ocaml
|Jedai| has joined #ocaml
Jedai has quit [Ping timeout: 248 seconds]
bluestorm has joined #ocaml
slash_ has joined #ocaml
thelema_ has joined #ocaml
thelema has quit [Read error: Connection reset by peer]
dark has quit [Ping timeout: 240 seconds]
ulfdoz has quit [Ping timeout: 276 seconds]
pimmhogeling has joined #ocaml
zhijie has quit [Quit: Leaving.]
bluestorm has quit [Read error: No route to host]
ikaros has joined #ocaml
demitar has quit [Quit: ChatSpace]
findum has joined #ocaml
derdon has joined #ocaml
tmaeda is now known as tmaedaZ
ttamttam has quit [Quit: Leaving.]
sepp2k has joined #ocaml
albacker has joined #ocaml
<albacker> is there a do.. while in ocaml?
<derdon> nope
<derdon> albacker: but you could write a function which acts like it ;)
<derdon> let do_while func cond = ...
<derdon> let do_while func args cond = ...
<Camarade_Tux> why "args"?
<albacker> derdon, yes of course
Leonidas_ is now known as Leonidas
<derdon> Camarade_Tux: cuz the arguments of the function have to be known?!
<albacker> i think it only needs a bool
<derdon> right
<albacker> i think i can go here without the need of a do..while, i can convert this into a while.. do..
sepp2k has quit [Ping timeout: 245 seconds]
sepp2k has joined #ocaml
tmaedaZ is now known as tmaeda
eni_ has joined #ocaml
albacker has quit [Disconnected by services]
eni_ has left #ocaml []
albacker has joined #ocaml
<albacker> any idea why this isn't working : http://pastebin.org/119234
<albacker> it's a bubble sort implementation
<albacker> # bubble_sort [|3;2;1|];;
<albacker> - : int array = [|2; 1; 3|]
<albacker> it goes through the code once,
<Camarade_Tux> "if arr.(i) > arr.(1+1) then" ?
<Camarade_Tux> 1+1 or i+1 ?
<albacker> oh
<Camarade_Tux> also, "while !swapped=true do", "while !swapped do" is cleaner ;-)
<albacker> thanks.
<albacker> bubble sort on lists should suck i think.
ski_ is now known as ski
pimmhogeling has quit [Ping timeout: 245 seconds]
ztfw has joined #ocaml
_zack has joined #ocaml
Riwor has joined #ocaml
M| has joined #ocaml
<flux> albacker, i doubt it would suck any more than the array version.. although it would produce a lot of garbage.
<albacker> suck as in slowness.
<albacker> i dont see how swaping would be done in lists better than in arrays.
<Camarade_Tux> well, if you want speed you probably won't wan to use bubble sort anyway
<albacker> Camarade_Tux, yes of course, i was just implementing it anyways.
<Camarade_Tux> but I don't think it's going to especially slowly for list
<Camarade_Tux> s
<albacker> unless i create a list of refs of ints, or just convert list to array at the beginning and use this algo.
<albacker> i dont see another way :/
<albacker> plus, to use the i-nth element in a list you have to run throught the i first elements, not like in arrays.
spearalot has joined #ocaml
<Camarade_Tux> 'int ref list' *may* perform worse actually ;-) (no guarantee, not benchmarked)
<Camarade_Tux> ah, for that, but you move linearly in the list so it's not a big concern
<Camarade_Tux> you shouldn't use List.nth of course ;-)
<albacker> :)
_zack has quit [Ping timeout: 246 seconds]
_zack has joined #ocaml
maskd has joined #ocaml
bzzbzz has joined #ocaml
albacker has quit [Ping timeout: 246 seconds]
slash_ has quit [Quit: leaving]
slash_ has joined #ocaml
CcSsNET has joined #ocaml
_zack has quit [Quit: Leaving.]
krankkatze has joined #ocaml
CcSsNET has quit [Quit: User disconnected]
CcSsNET has joined #ocaml
drk-sd has joined #ocaml
Yoric has joined #ocaml
Yoric has quit [Client Quit]
_unK has joined #ocaml
Yoric has joined #ocaml
Yoric has quit [Client Quit]
oc131 has joined #ocaml
sc30317 has quit [Quit: Leaving]
smimou has quit [Ping timeout: 246 seconds]
smimou has joined #ocaml
oc13 has quit [Ping timeout: 268 seconds]
Associat0r has joined #ocaml
Associat0r has quit [Client Quit]
_zack has joined #ocaml
struktured has joined #ocaml
mikeX has joined #ocaml
spearalot has quit [Quit: -arividerchi]
ttamttam has joined #ocaml
dark has joined #ocaml
dark has quit [Read error: Connection reset by peer]
Asmadeus has quit [Ping timeout: 260 seconds]
Asmadeus has joined #ocaml
Asmadeus has quit [Changing host]
Asmadeus has joined #ocaml
thieusoai has joined #ocaml
thieusoai has quit [Read error: Connection reset by peer]
yakischloba has joined #ocaml
<flux> I sense a blog-article here.. "performance characteristics comparison of bubble sort on mutable arrays and functional lists"
schmx has quit [Ping timeout: 240 seconds]
schmx has joined #ocaml
<flux> nah, not blog-article but a whitepaper for FunML Seminar 2k!
<flux> (just made up the name)
thieusoai has joined #ocaml
<Camarade_Tux> bah, for the ocaml meeting ;p
<derdon> how does OCaml handle unicode and non-ASCII characters in ocaml files?
<derdon> what about special characters like ä and ß in comments or strings? can they be used as characters?
sepp2k has quit [Quit: Leaving.]
thelema_ has left #ocaml []
thelema has joined #ocaml
<thelema> derdon: source files are treated as latin-1 by the ocaml compiler
<derdon> thelema: oh, right. forgot it
ygrek has quit [Remote host closed the connection]
<thelema> batteries has some pre-processing that it can do to handle UTF-8 literal strings better.
ygrek has joined #ocaml
<derdon> thelema: but I cannot assume that all OCaml users always use the batteries in every ocaml file, can I?
<derdon> thelema: I am writing an ocaml plugin for an editor
<thelema> Then you should use latin-1 as the encoding for source files.
<thelema> what editor?
<thelema> (I lost my channel history to make my comment.)
<derdon> thelema: the editor is called PIDA
<derdon> thelema: because of GTK I have to encode the file's content to utf-8
smimou has quit [Ping timeout: 246 seconds]
smimou has joined #ocaml
<thelema> well, in my world, few people outside france actually use the latin-1 ability
smimou has quit [Ping timeout: 246 seconds]
<derdon> thelema: yeah, but I have to reckon with it
<derdon> thelema: it *could* be that someone uses ``let umlauts = "öäü";;`` in one of his *ml files
<derdon> *.ml
<thelema> so you'll encode the latin-1 as utf8, and decode it on save?
smimou has joined #ocaml
smimou has quit [Changing host]
smimou has joined #ocaml
boscop_ has joined #ocaml
derdon has quit [Quit: derdon]
boscop has quit [Ping timeout: 246 seconds]
peper has quit [Ping timeout: 265 seconds]
peper has joined #ocaml
peper has quit [Remote host closed the connection]
peper has joined #ocaml
mfp has quit [Read error: Connection reset by peer]
_zack has quit [Quit: Leaving.]
struktured_ has joined #ocaml
struktured has quit [Ping timeout: 276 seconds]
mfp has joined #ocaml
derdon has joined #ocaml
bzzbzz has quit [Quit: leaving]
smimou has quit [Ping timeout: 246 seconds]
smimou has joined #ocaml
struktured_ has left #ocaml []
struktured has joined #ocaml
tmaeda is now known as tmaedaZ
rwmjones has quit [Ping timeout: 256 seconds]
enthymeme has joined #ocaml
rwmjones has joined #ocaml
ulfdoz has joined #ocaml
ttamttam has quit [Quit: Leaving.]
thrasibule has joined #ocaml
_zack has joined #ocaml
thrasibule has quit [Ping timeout: 264 seconds]
boscop_ has left #ocaml []
boscop has joined #ocaml
thrasibule has joined #ocaml
yakischloba has quit [Quit: Leaving.]
yakischloba has joined #ocaml
smimou has quit [Ping timeout: 246 seconds]
smimou has joined #ocaml
yakischloba has quit [Ping timeout: 258 seconds]
ulfdoz has quit [Ping timeout: 256 seconds]
Riwor has quit [Quit: Bubbles!]
maattd has joined #ocaml
matthieu has quit [Read error: Operation timed out]
valross has joined #ocaml
Alpounet has joined #ocaml
kriko has joined #ocaml
<kriko> how do I do proper list merge with sort: http://pastebin.com/KirPdBeu
<kriko> this is what I've come up with so far
<kriko> however that List.sort ruins everything
<Camarade_Tux> you need to compare the heads of each list
<Camarade_Tux> but well, there's more
<Camarade_Tux> bah, have troubles writing, too tired
<kriko> ok, I'll try from scratch
<Camarade_Tux> well, you're missing several things: how are you learning merge sort?
pimmhogeling has joined #ocaml
<kriko> hm, how can I compare hd from first list to the other? http://pastebin.com/ALLXYfi3
<kriko> oh, wait I have to rewrite match statement
<Camarade_Tux> you can use 'match s1, s2 with | h1::q1, h2::q2 -> ... | ...'
_zack has quit [Quit: Leaving.]
<kriko> :: concatenates?
<flux> match [1; 2; 3] with a::b -> (* a contains 1, b contains [2; 3] *)
<Camarade_Tux> in my example, h1 stands for head1 and q1 stands for queue1 and it should have been called t1 for tail1
<flux> :: in an expression is the 'cons'-operation of lists, in a pattern it is the matching operator in a similar fashion
<Camarade_Tux> need sleep =)
<kriko> Camarade_Tux: night :>
<kriko> ok, I kinda understand now
yakischloba has joined #ocaml
slash_ has quit [Quit: Lost terminal]
enthymeme has quit [Quit: rcirc on GNU Emacs 23.1.1]
mattam has quit [*.net *.split]
mattam has joined #ocaml
kriko has quit [Remote host closed the connection]