gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.1 http://bit.ly/nNVIVH
dnolen has quit [Quit: dnolen]
oriba has quit [Quit: oriba]
rgrinberg has joined #ocaml
Anarchos has quit [Quit: Vision[0.9.7-H-090423]: i've been blurred!]
rgrinberg has quit [Ping timeout: 244 seconds]
ecc has joined #ocaml
fullofcars has joined #ocaml
<fullofcars> what does the ocaml community think of F#?
sebz has quit [Quit: Computer has gone to sleep.]
pheredhel has quit [Ping timeout: 252 seconds]
pheredhel has joined #ocaml
dnolen has joined #ocaml
grettke has joined #ocaml
grettke has left #ocaml []
sebz has joined #ocaml
beginner has quit [Quit: This computer has gone to sleep]
mehdid has quit [Ping timeout: 252 seconds]
mehdid has joined #ocaml
scrappy_doo_ is now known as Drakken
<Drakken> fullofcars you'll get more responses in the morning
emmanuelux has quit [Remote host closed the connection]
dnolen has quit [Quit: dnolen]
dnolen has joined #ocaml
roconnor has quit [Ping timeout: 252 seconds]
<fullofcars> ok :)
fullofcars has left #ocaml []
EmmanuelOga has quit [Ping timeout: 244 seconds]
ulfdoz has joined #ocaml
everyonemines has joined #ocaml
arubin has quit [Quit: arubin]
dnolen has quit [Quit: dnolen]
everyonemines has quit [Quit: Leaving.]
Modius_ has quit [Quit: "Object-oriented design" is an oxymoron]
larhat has joined #ocaml
ulfdoz has quit [Ping timeout: 240 seconds]
Modius has joined #ocaml
<adrien> is there any "first library/application" tutorial around? something that would show some code (maybe with some code organization), the build systems, ocamlfind...
ftrvxmtrx has quit [Quit: This computer has gone to sleep]
<sgnb> thelema: please, don't tell people to use Obj.magic
<sgnb> _habnabit, thelema: use Scanf.format_from_string
edwin has joined #ocaml
ttamttam has joined #ocaml
ygrek has joined #ocaml
bitbckt has quit [Quit: out]
bitbckt has joined #ocaml
oriba has joined #ocaml
avsm1 has joined #ocaml
avsm has quit [Ping timeout: 244 seconds]
avsm1 has quit [Ping timeout: 244 seconds]
rossberg has joined #ocaml
sebz has quit [Quit: Computer has gone to sleep.]
sebz has joined #ocaml
sebz has quit [Client Quit]
reynir has joined #ocaml
bwright has quit [Ping timeout: 244 seconds]
Cyanure has joined #ocaml
bwright has joined #ocaml
raichoo has joined #ocaml
mlh has quit [Ping timeout: 240 seconds]
mlh has joined #ocaml
beginner has joined #ocaml
_andre has joined #ocaml
avsm has joined #ocaml
king-of-spain has quit [Quit: Lost terminal]
ikaros has joined #ocaml
destrius has quit [Quit: Leaving.]
vpalle has joined #ocaml
ftrvxmtrx has joined #ocaml
Snark has joined #ocaml
larhat has quit [Quit: Leaving.]
larhat has joined #ocaml
larhat1 has joined #ocaml
larhat has quit [Read error: Connection reset by peer]
ftrvxmtrx has quit [Quit: Leaving]
ikaros has quit [Quit: Ex-Chat]
oriba has quit [Quit: oriba]
<adrien> gildor: hi, you don't have anything special in order to get stats on the forge web pages? I'm interested in the number of hits a page can get
ikaros has joined #ocaml
ftrvxmtrx has joined #ocaml
yezariaely has joined #ocaml
Kakadu has joined #ocaml
<gildor> adrien: I have the full stats somewhere
<gildor> adrien: but right now, I am sick, so ping me in 2 3 days
<adrien> gildor: ok, no hurry and I hope you get better
ankit9 has joined #ocaml
ygrek has quit [Ping timeout: 248 seconds]
yezariaely has quit [Quit: Leaving.]
<thelema> sgnb: ah, didn't know about format_from_string.
raichoo has quit [Ping timeout: 248 seconds]
raichoo has joined #ocaml
<beginner> hello everyone
emmanuelux has joined #ocaml
<reynir> Hell beginner
<reynir> err, Hello*
<beginner> Today I want to learn to understand the toplevel output
<beginner> as example this one
<beginner> val myfun : (int -> int) -> int -> int -> int = <fun>
<beginner> how I do I read that
<beginner> myfunc is a function that takes a function as an argument?
<adrien> yes
<thelema> beginner: a function and two ints
<adrien> (and two ints and returns an int)
<beginner> I know the one in brace means function
<thelema> beginner: () are just for grouping
<beginner> so what is the rule to interpret them correctly?
<beginner> I mean rules
<thelema> technically, it's (int -> int) -> (int -> (int -> int))
<thelema> -> is right associative
<beginner> I know left is input and right is output
<beginner> but in cases like int -> int -> int
<thelema> right associative, thus int -> (int -> int)
<beginner> so it returns to 2 integers as output?
<beginner> *2
<thelema> no, it returns a function
<beginner> so the one in brace always mean a function then...
sepp2k has joined #ocaml
<thelema> -> always means function, () is just for grouping / prescedence
<thelema> (+) has type int -> int -> int
<beginner> alright I think I understand it ... After thinking for a second, a function basically only take one argument and return a value
<thelema> this is the same as int -> (int -> int)
<thelema> so `(+) 5` is type int -> int
<thelema> beginner: yes, but that value is often another function
<beginner> also in this case: (int -> int) -> (int -> (int -> int))
<beginner> is (int -> int) get evaluated first or (int -> (int -> int))?
<beginner> I guess it's the second one?
<beginner> since it's right associative?
mcclurmc has quit [Excess Flood]
mcclurmc has joined #ocaml
roconnor has joined #ocaml
<beginner> So I was right or wrong?
<reynir> (int -> int) -> (int -> int -> int) is a function f that takes a function f' and returns a function that takes two ints
<reynir> err, where f' is a function that takes one int and returns a int
<beginner> see, that's my problem. You guys see this as an example: val myfun : (int -> int) -> int -> int -> int = <fun>
<thelema> beginner: there's two ways to look at that function
<thelema> beginner: one way is to look at what happens when you give it one argument
<beginner> and know straight away it's a function that takes 1 function and 2 integers
<thelema> the other way is to look at how many arguments are needed to get a non-function value back
<thelema> the way we calculate the "1 function and 2 integers" is by looking at what's before each toplevel arrow
<thelema> so the very first arrow in parentheses isn't a toplevel arrow
<thelema> so we see: arg1 -> arg2 -> arg3 -> ret
<thelema> where arg1 = (int -> int), arg2=arg3=ret=int
<beginner> what do you mean by "is not a toplevel arrow"?
<beginner> so it's not a top level if it is inside a brace?
<beginner> but I think I am starting to understand
<beginner> like this one val myfun2 : ('a -> 'a) -> 'a -> 'a = <fun>
<beginner> means it's a function that takes one function and any type of argument
<beginner> correct?
<beginner> while this one:
<beginner> int -> (int -> int) -> int -> int = <fun>
<beginner> means the first argument is an integer and the second one is a function tha takes an integer and returning an integer
<beginner> and the 3rd argument is an integer
<beginner> and the function returns an integer
<beginner> correct?
<thelema> correct and correct
dnolen has joined #ocaml
<thelema> here's a quick quiz
<thelema> 1) ('a -> unit) -> 'a t -> unit
maufred_ has joined #ocaml
EmmanuelOga has joined #ocaml
<thelema> 2) 'a -> ('a -> 'b) -> 'b
<thelema> 3) ('a -> 'b -> 'c) -> 'b -> 'a -> 'c
<thelema> 4) ('a * 'b -> 'c) -> 'a -> 'b -> 'c
<thelema> 5) ('a -> 'b -> 'c) -> 'a * 'b -> 'c
<thelema> 6) (unit -> unit) -> ('a -> 'b) -> 'a -> 'b
<thelema> end.
maufred has quit [Ping timeout: 244 seconds]
dnolen has quit [Quit: dnolen]
<beginner> 2) is a function that takes 2 arguments, one is 'a type and another one is a function that takes 'a and returning 'b. The function returns 'b
ankit9 has quit [Ping timeout: 240 seconds]
<beginner> 3) is a function that takes 3 arguments, a function that takes 2 arguments a' and 'b returning 'c and two arguments of the type 'b and 'a. The function returns a value of type 'c.
jamii has joined #ocaml
<beginner> 6) is a function that takes 2 functions and one value of type 'a as arguments returning a value of type 'b
<thelema> all correct
<beginner> I don't know if (unit -> unit)
<beginner> means a function that takes no argument and returning not value?
<thelema> yes
<beginner> *no
<beginner> ok cool
<smango> like let f = print_string "hi"
<beginner> and the rest which i didn't answer, it's because I don't know what does `'a t` mean
<beginner> and also the *
<thelema> smango: almost - let f () = print_string "hi"
<thelema> beginner: you should be able to determine number of arguments (called arity) without knowing 'a t and *
<beginner> ah ok, you just wanna see if I know how many arguments
<beginner> anyway, what is *?
<thelema> int * int is a pair of ints
<thelema> int * int * int is a triple of ints
maufred_ has quit [Ping timeout: 252 seconds]
maufred has joined #ocaml
<thelema> int * ('a -> unit) is a pair of an int and a function
<thelema> int * 'a -> unit is a function taking one argument, that argument being a pair
<thelema> 'a -> int * int is a function taking one argument and returning a pair of ints
<beginner> so when I want to call a function, how do I pass the arguments? if let say it takes 2 arguments, one is an int and another one is int * int?
<beginner> myfunc 1 2 3?
<thelema> myfunc 1 (2,3)
<beginner> so it's separated by a comma, cool
<thelema> typelevel tuples use *, value-level tuples use ,
<thelema> `int, 'a -> unit` is not valid
<thelema> myfunc 1 (2*3) is multiplication
<beginner> so when I declare a function it should be something like this `let myfunc b a * a = 1 + b` ?
<thelema> no, you're using values, so `let myfunc a (b,c) = b + a * c`
<beginner> what do you actually means by "type level"?
<beginner> *mean
<thelema> myfunc is `int -> int * int -> int` - this is a type level description
<thelema> myfunc is `fun a (b,c) -> b + a * c` - this is a value-level description
<beginner> so the type level is actually the output that you get be the interpreter
<beginner> *by
<bitbckt> wow. caml-list is on fire...
<thelema> when you give the interpreter a value-level description of a function, it returns the type-level description of that value
<thelema> bitbckt: yes, hornet's nest provoked
<thelema> beginner: actually, when you give the interpreter any value, not just functions, it will describe that value with its type
<bitbckt> everyone's favorite topics: core transparency, stdlib and PR. blech.
* bitbckt mutes
<beginner> alright
<beginner> I understand the meaning now
<thelema> 'a t is a parameterized type - for example `'a list` is a list of values all of which are 'a
ikaros has quit [Quit: Ex-Chat]
<beginner> so how does it look like a value-level?
<thelema> [1; 2; 3] is an int list
raichoo has quit [Quit: leaving]
<beginner> so I pass it like this `myfun a = a;;`
<beginner> and call it like this `myfun [1;2;3]`
<beginner> correct?
<thelema> yes
<beginner> cool, thanks!
<thelema> for lists, one useful thing you can do is prepend to it: let prepend x lst = x :: lst
<beginner> so there is a new symbol here `::`
<thelema> yes, is a builtin that prepends a value to a list.
<thelema> maybe we should start with arrays instead: 'a array is an array of 'a
<beginner> ok
<thelema> let set_five arr i = arr.(i) <- 5
<beginner> ok
ftrvxmtrx has quit [Quit: Leaving]
<thelema> .() indexes into an array
ttamttam` has joined #ocaml
<thelema> .() <- sets the value at an index
ttamttam` has quit [Read error: Connection reset by peer]
ttamttam` has joined #ocaml
ttamttam has quit [Read error: Connection reset by peer]
ttamttam` has quit [Read error: Connection reset by peer]
<beginner> How useful is label?
<thelema> labeled parameters?
<beginner> yup
<thelema> not consistently used
* reynir has never used it
<thelema> They're kind of nice
<beginner> I am reading the introduction to ocaml book, but I see there are many topics like Files I/O etc
<beginner> right now I just wanna focus on the core topics
<thelema> I use them when I want an optional parameter, and sometimes when two arguments can be mixed up, but not that often.
<beginner> that will be enough for me to do some math
<beginner> I mean my goal for now is to learn enough to do some math and play around with it so that I will master all the basic stuff
<thelema> try writing a bisection root finder
<beginner> Do I need to learn about functors etc to reach my first goal?
<thelema> no
ygrek has joined #ocaml
ulfdoz has joined #ocaml
ikaros has joined #ocaml
svenl_ is now known as svenl
raichoo has joined #ocaml
avsm has quit [Quit: Leaving.]
larhat1 has quit [Quit: Leaving.]
sebz has joined #ocaml
ftrvxmtrx has joined #ocaml
sebz has quit [Quit: Computer has gone to sleep.]
<thelema> Numeric root finding library here: https://gist.github.com/1443808
<flux> no mention of license?
<thelema> oops, LGPL2.1 good enough?
<flux> well, depends on who you ask, but that kind of small code that isn't prepackaged as a library is a good candidate for copy/paste integration ;)
<thelema> packaging it as a library is pretty trivial, I just wanted to get it out.
<thelema> bah, 3-clause BSD it is.
roconnor has quit [Ping timeout: 252 seconds]
<pcjoby> Hi, Is there a way I can create a ocaml toplevel as a shared library ? I need to call this from a C program.
ygrek has quit [Ping timeout: 248 seconds]
<pcjoby> The function "main" is in the C program.
<thelema> pcjoby: you want to call a function from your C program and as a result have the ocaml toplevel start interacting with the user on stdin/stdout?
<pcjoby> thelema: yes that's exactly what I want
<thelema> pcjoby: dig in the ocaml source tree in the toplevel/ directory, I don't recall the function that you'll need to call.
<thelema> is there any reason you don't just exec("ocaml")?
<pcjoby> exec is not good, because I need to call access some C objects
<thelema> you want the ocaml toplevel to be able to see some pieces of your C program?
<pcjoby> thelema: that's right
<thelema> I definitely can't help with that.
<pcjoby> thelema: thanks for trying ...... I couldn't get a clue from the manual ...... hence asked on the channel. Thanks anyway.
<thelema> pcjoby: it's not such a recommended thing to do.
<pcjoby> thelema: thanks. see you later.
<tomprince> pcjoby: I think you just need to link with something defining main.
sepp2k1 has joined #ocaml
sepp2k has quit [Ping timeout: 240 seconds]
avsm has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
<beginner> thelema: Would you mind to explain to me about pattern matching?
<thelema> match 'x' with 'z' -> true | _ -> false
<thelema> this is like a case statement (except it's an expression, so it returns a value)
<thelema> the 'x' is what's being matched
<thelema> 'z' is the first case
<thelema> _ is default case
<thelema> cases are separated by |
<thelema> let is_vowel x = match x with 'a' | 'e' | 'i' | 'o' | 'u' -> true | _ -> false
<thelema> so far, so good?
<beginner> yup
<beginner> that looks simple to understand so `true` can be any expression right?
<thelema> yes
<thelema> all expressions in a match must have the same type
<thelema> so no | 'x' -> true | _ -> 5
<thelema> tuples can be matched as well:
<thelema> match x,y with 5,_ -> "x=5" | _,3 -> "y=3" | _ -> "no match"
<thelema> let test_pair p = match p with 5,_ -> "x=5" | _,3 -> "y=3" | x,y -> Printf.sprintf "x=%d,y=%d" x y
<beginner> so it can also work like this `let is_odd x = match x with 1 -> true | 2 -> false | 3 -> true`
<beginner> an expression after every case I mean
<thelema> yes.
<thelema> for is_odd, there's another feature of match that's useful
<beginner> ok
<thelema> let is_odd x = match x with z when z mod 2 = 0 -> "even" | _ -> odd
<thelema> let first_is_odd x = match x with (z,_) when z mod 2 = 0 -> false | _ -> true
<thelema> type sign = Pos | Zero | Neg
<thelema> let sign_to_string x = match x with Pos -> "Positive" | Zero -> "Zero" | Neg -> "Negative"
<thelema> pattern matching is critical for variant types, such as 'sign'
<beginner> Alright I already undetstand the pattern matching part above, but the `type sign`
<beginner> is new for me
<thelema> are you familiar with enumeration types?
<thelema> type weekday = Monday | Tuesday | Wednesday | Thursday | Friday | Saturday | Sunday
<thelema> gotta go now, back in a few hours.
Anarchos has joined #ocaml
<beginner> ok
<bitbckt> pattern matching over variant types like that also triggers exhaustiveness checks.
<bitbckt> so, if you match over a value of type weekday but forget at least one of the options, the compiler will warn.
<beginner> what do you mean by "exhaustiveness checks" and "one of the options"?
<bitbckt> (as long as no default case is given)
<bitbckt> for brevity, I'll use the type sign:
<bitbckt> let sign_to_string x = match x with Pos -> "Pos" | Zero -> "Zero"
<bitbckt> since I left off Neg, if I compile that, ocaml will complain.
<bitbckt> it knows that there is a possible value which isn't handled by that function.
<bitbckt> does that make sense?
<beginner> yup
<bitbckt> types like sign, above, are called variant types (cue Wikipedia search ;-)
<bitbckt> values of that type may be one of several options
<beginner> alright I will take a look at Wikipedia now
<bitbckt> i.e. a value of type sign is Pos OR Neg OR Zero.
<bitbckt> the options are called type constructors
<bitbckt> because they "make" a value of type sign.
<beginner> What are the "options"?
<bitbckt> they are the different constructors in the type: Pos, Neg, and Zero.
<beginner> ah ok
<beginner> so `Pos`, `Neg` and `Zero`
<bitbckt> yes.
<beginner> these are known as the constructors
<beginner> alright, gotcha
<bitbckt> yes.
<bitbckt> the combination of variant types and pattern matching is pervasive in OCaml and extremely powerful.
<bitbckt> A better Wiki article on this topic is "Algebraic Data Type"
<beginner> ok, looking at it now
avsm has quit [Quit: Leaving.]
Anarchos has quit [Quit: Vision[0.9.7-H-090423]: i've been blurred!]
Anarchos has joined #ocaml
<beginner> So bitbckt: sign is also known as the type constructor
<beginner> and the Pos,Zero,Neg
_andre has quit [Quit: leaving]
<beginner> are known as data constructors?
arubin has joined #ocaml
<bitbckt> I usually refer to the "type sign" portion as a type definition, but I think those terms are used that way, yes.
<beginner> yeah just comparing to Haskell, The Real world Haskell book seems to give a better explanation about stuff than wikipedia
<bitbckt> that's a reasonable comparison, I think.
<beginner> alright, I need to off to bed
<beginner> thank you so much for the help, learned a lot of stuff today!!
<beginner> Will continue tomorrow
<bitbckt> no problem.
jamii has quit [Read error: Connection reset by peer]
raichoo has quit [Read error: Operation timed out]
raichoo has joined #ocaml
<adrien> gildor: looks like the forge is down again =/
j2d2j2d2 has left #ocaml []
waern has quit [Ping timeout: 240 seconds]
waern has joined #ocaml
raichoo has quit [Quit: leaving]
ttamttam has joined #ocaml
ttamttam has quit [Remote host closed the connection]
ttamttam has joined #ocaml
eikke has joined #ocaml
<eikke> could someone help me out with a question on the value restriction?
<_habnabit> only if you ask said question
avsm has joined #ocaml
roha has joined #ocaml
<eikke> I understood why, if I let id x = x, the type of 'ref i' would initially be ('_a -> '_a) ref
<eikke> s/ref i/ref id/
<eikke> but not why the type of 'id id' would be '_a -> '_a as well
<eikke> because there's no mutability/side effects/... in 'id id'
<_habnabit> you mean why it's '_a instead of 'a ?
roha has quit [Remote host closed the connection]
<eikke> I understand '_a means 'not universally qualified over 'a, but not sure what '_a should be yet'
<eikke> the type of 'fun x -> (id id) x' is 'a -> 'a
<eikke> but the type of (id id) is '_a -> '_a
<eikke> which I don't get
<_habnabit> okay, so, the answer to my question was 'yes' ?
<eikke> no, I dont understand why it's '_a instead of 'a in the (id id) case
<_habnabit> yes... that's what I asked
fraggle_ has quit [Remote host closed the connection]
ttamttam has quit [Remote host closed the connection]
<_habnabit> it doesn't have anything to do with mutability or side effects though
<eikke> oh? I read the value restriction is there to ensure sound typing in face of side-effects
<_habnabit> well, that might be the reason it exists, but ocaml doesn't do any sort of verification if code has side effects
<eikke> agree
<_habnabit> so, it doesn't have anything to do with mutability or side effects, other than tangentially
<eikke> right
<eikke> even then, I don't get why (id id) can't be infered as 'a -> 'a
<eikke> yet the eta-expanded version can easily (which should infer the type of the (id id) inside it as well, right?)
<bitbckt> eikke: look at the examples on this page in the sections following "A type variable starts with _?:
Kakadu has quit [Quit: Konversation terminated!]
<eikke> right, so the type of an expression is generalized when it's an abstraction, identifier or constant
<eikke> not when it's an application
<eikke> yet, to infer the type of fun x -> (id id) x to 'a -> 'a, the compiler must know (id id) is 'a -> 'a, right?
<eikke> sorry if this should be obvious and I'm just asking dumb :P
Xizor has joined #ocaml
<thelema> eikke the other way around - only things that are explicitly functions are generalized from _a to a
<thelema> the compiler starts by assuming that everything is '_a, and at the end, if it's working with a value that's toplevel declared as a function, it generalizes it to 'a
<eikke> I might be confusing abstraction with application :$
<thelema> things like `let foo x = ...` or `let foo = fun x -> ...` can be generalized
<eikke> ok
<eikke> so the type infered for (id id) at toplevel is different than when used inside 'let foo x = (id id) x'
<thelema> when you "eta-expand" it (the name for putting on the x), it can be fully generalized.
<thelema> This is just the ocaml compiler being safe and lazy
<eikke> hmh
<eikke> am I mistaken by thinking this is the reverse of haskell, where polyphormic types are universally qualified by default, then narrowed down
<thelema> I'm not certain how haskell does it, but assuming that haskell does it the opposite of ocaml, then yes'
roha has joined #ocaml
<eikke> ok ;-)
<thelema> err, then no, you're not mistaken
<eikke> I'm happy I found a simple example why it's necessary today
<roha> question: is there a reason to use the standard library over jane street core/batteries?
<roha> especially for a beginner
<_habnabit> roha, sure: if you're a masochist
<bitbckt> it's always there, I guess.
<eikke> let i x = x in let r = ref i in (r := fun (true | false) -> true; (!r) 0)
sebz has joined #ocaml
<thelema> roha: not much. I restricted myself to not use batteries for odb.ml, because it's intended to be used to install batteries.
<roha> in this case: jane street core or batteries?
<thelema> roha: I'm happy with batteries, but I'm the dev lead.
<thelema> eikke: let f = let args = ref [] in fun x -> args := x :: !args; x
ftrvxmtrx has joined #ocaml
Snark has quit [Quit: Quitte]
<roha> thelema: k, i guess i just try both! thanks @ thelema and habnabit
<eikke> thelema: nice one, thanks
<adrien> if I use module packs, is ocaml(opt) able to only pick the right one?
<adrien> assuming I've packed 3 modules and only use one
<thelema> adrien: IIRC, ocamlopt will link in all modules in a pack.
<adrien> ok, thanks
ulfdoz has quit [Ping timeout: 244 seconds]
<adrien> I'm going to try a new code setup: I have an application with several components and sub-components each; I'm putting an _oasis file for each sub-component (which are libs) and component and I'll install each sub-component locally with findlib
<adrien> currently I'm getting namespace clashes: I can't reuse the module names
<Anarchos> how installed is oasis in the ocaml community ?
<thelema> Anarchos: more and more. It's lost some momentum with gildor being hired by google, but it's workable for many small projects as-is
<Anarchos> thelema i want to be hired by google !
<adrien> development has resumed =)
<thelema> Anarchos: ask gildor how.
<thelema> adrien: my solution for that is simple - just put a prefix ahead of your module names. It's not elegant, but it's some effective.
<adrien> thelema: yeah, I've been doing that but I haven't liked it because the code is well-separated
<adrien> so I'm trying something new
<Anarchos> thelema i prefer to finish my latex/ocaml formal math demonstration verifier (lot of buzzwords, should work !!)
<adrien> I'll put a toplevel _oasis which will also generate a setup.data usable by each sub-module so it should avoid having to run oasis everywhere
<adrien> s/run oasis/run oasis and setup.ml/
<thelema> adrien: I imagine oasis wasn't designed for that.
<thelema> adrien: FWIW, don't spend so much time on your build system - a complex build system isn't a feature.
<adrien> it should be quite simple; I think I could be done in a few minutes actually
<adrien> but there's code which can use lablgtk2 and code that musn't link to it and making sure everything is compiled separately will probably help avoid stupid mistakes
fraggle_ has joined #ocaml
maufred_ has joined #ocaml
maufred_ has quit [Client Quit]
scrappy_doo_ has joined #ocaml
Drakken has quit [Ping timeout: 252 seconds]
sebz has quit [Quit: Computer has gone to sleep.]
edwin has quit [Remote host closed the connection]
ikaros has quit [Quit: Ex-Chat]
roha has quit [Remote host closed the connection]
ikaros has joined #ocaml
ikaros has quit [Client Quit]
ikaros has joined #ocaml
<beginner> could only sleep for like 2 hours. Not able to stop thinking about ocaml lol =(
<thelema> you're just beginning to understand the wonderfulness of ocaml. :)
<beginner> that's what I think, there is something about it that made me really enjoy learning it
thelema has quit [Remote host closed the connection]
thelema has joined #ocaml
<beginner> Anyway, continuing from where did I stop earlier, I have understood the basic idea of pattern matching
<beginner> and type definition
<beginner> but I need a good and easy to understand example that shows why the combination of variant type and pattern matching is really powerful
Morphous has quit [Ping timeout: 240 seconds]
<adrien> thelema: my build system stuff is not complete but seems to be working quite well =)
roconnor has joined #ocaml
<beginner> is variant type and union the same thing in ocaml?
roha has joined #ocaml
<_habnabit> 'union' ?
everyonemines has joined #ocaml
<everyonemines> msl
<beginner> yeah
<beginner> the "Introduction to Objective Caml" doesn't have a chapter on "Variant type"
<beginner> but a chapter on union
<adrien> anyone know how to pass a custom flag through oasis? I need to pass -linkall
<adrien> ah, it's CCOpt and CCLib but it doesn't seem to solve my issue =)
Morphous has joined #ocaml
<adrien> arf, because it's for the C compiler, not for ocaml itself
<adrien> ByteOpt and NativeOpt
sebz_ has joined #ocaml
ikaros_ has joined #ocaml
ikaros has quit [Ping timeout: 255 seconds]
ccasin has quit [Ping timeout: 258 seconds]
ccasin has joined #ocaml
Anarchos has quit [Quit: Vision[0.9.7-H-090423]: i've been blurred!]
reynir has quit [Ping timeout: 252 seconds]
<roha> holy hell, i dont get this.
<roha> question: if i install the jane street package. it builds all the packages including ocaml, jane street core etc. and puts them inside ~/js/
<roha> the toploop seems to load the new packages, but i can't seem to use the new functions from core.
<roha> nvm, i'm just too dumb to realize i have to open Core_list for example. So "List" is still the standard library from inria, even with all the js modules installed?
struktured has quit [Ping timeout: 252 seconds]
<beginner> hai roha, no worries
<beginner> I am very dumb too! So we are alike!!
<roha> :D
<roha> no it doesn't work again.
<beginner> a question though
<beginner> why would you use the library from Jane Street
<beginner> rather than the standard one?
<roha> Before i just simply copied all ml and mli files from the js source dir to the ocaml root dir, and suddenly it worked. there has got to be another way
<roha> aehm, well i missed some functions that i now from haskell, like drop_while, take_while etc.
<roha> Also, someone here said, that only masochists use the standard library :)
<beginner> I think he meant the opposite
<beginner> or maybe that's what he realyl said ^_^
<roha> <roha> question: is there a reason to use the standard library over jane street core/batteries? <roha> especially for a beginner <_habnabit> roha, sure: if you're a masochist
<_habnabit> yes, this is a thing I said
<roha> hehe
<beginner> but isn't that weird, that standard is the bad thing
<beginner> I have always thought standard means being safe
<roha> hmm probably it isn't unsafe, but rather not very big.
sebz_ has quit [Quit: Computer has gone to sleep.]
flapjackery has joined #ocaml
<everyonemines> What was missing from the standard library that you needed?
<_habnabit> enums.
<_habnabit> tail-recursive list methods.
Xizor has quit []
<everyonemines> There's a reason why the list stuff isn't tail recursive: it's faster for small lists.
<everyonemines> You can easily make a tr version with the reverse version + list.reverse
<_habnabit> doesn't matter since I'm using batlist for everything anyway.
<everyonemines> and what's the advantage of enums over sets?
<_habnabit> they do completely different things ?
Cyanure has quit [Ping timeout: 240 seconds]
<_habnabit> enums are lazy iterators
<beginner> can someone explain to me why this wouldn't work:
<beginner> let zero = 0;;
<beginner> let one = 1;;
<beginner> let rec fib i =
<beginner> match i with
<beginner> zero > zero
<everyonemines> I'm not a big fan of lazy stuff I guess.
<beginner> | one > one
<beginner> | j >
<beginner> fib (j 2) + fib (j 1);;
<_habnabit> beginner, don't paste to the channel
<beginner> ops, my apologies
<everyonemines> -> ???
<beginner> sorry ->
flapjackery has quit [Quit: Leaving]
<everyonemines> anyway your match binds i to "zero"
<everyonemines> you want "i when i=zero"
<everyonemines> or just 0
<beginner> it's an example from the book
<beginner> I don't get it, what's the difference between 0 -> 0
<beginner> and zero -> zero
eikke has quit [Ping timeout: 252 seconds]
<everyonemines> zero is the name you're giving to i
<everyonemines> it overwrites the previous bind
<beginner> ah I see
<beginner> get it now
<everyonemines> and it can't be implemented as efficiently when comparing to a variable
<everyonemines> in general
ikaros_ has quit [Quit: Ex-Chat]
<beginner> alright, thanks!
<everyonemines> it does seem kind of weird until you start using matching to break up tuples or lists
dnolen has joined #ocaml
sebz has joined #ocaml
lamawithonel_ has joined #ocaml
<_habnabit> http://i.imgur.com/nIGnb.png (line 3) <- anyone else have this issue with tuareg-mode?
<_habnabit> dunno if it's an issue with color-theme or tuareg-mode
destrius has joined #ocaml
lamawithonel has quit [Ping timeout: 252 seconds]
<beginner> what is a good example where I use name in the pattern?
<beginner> *as a
<roha> like in "match (x,y) with ...."?
<roha> 2 AM O_O, need to get some sleep. bye
<everyonemines> no, wrong way around
<everyonemines> match x with x,y ->
roha has quit [Ping timeout: 268 seconds]
dnolen_ has joined #ocaml