flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | Grab OCaml 3.10.2 from http://caml.inria.fr/ocaml/release.html (featuring new camlp4 and more!)
struktured has joined #ocaml
christo_m has joined #ocaml
<christo_m> how can i take the third root of a double float in ocaml
<christo_m> is it in some library?
<thermoplyae> **: float -> float -> float corresponds to float exponentiation
<thermoplyae> and the nth root of something is its 1/nth power
<christo_m> thermoplyae: names familiar, you frequent physics a lot?
<christo_m> or #math?
<thermoplyae> #math, yeah
<christo_m> ok
<Smerdyakov> christo_m, OCaml only has one floating type, [float], so it's just confusing to talk about "double floats."
<christo_m> my bad
<christo_m> Smerdyakov: the prof had two parts of the assignment, the requirements were laid out and then im to program it in C and ocaml
<christo_m> i did C first because i actually know it, ocaml is very new to me
<christo_m> so is it just, char, string, bool float and int types?
<christo_m> i know the operators must be followed with a . when dealing with float operands
Adeline has joined #ocaml
<thermoplyae> more or less (forgetting things like large integers), though the importance of variant types can't really be understated
<christo_m> oh you mean bignums
<christo_m> like in lisp
<thermoplyae> yeah
<Smerdyakov> christo_m, you might want to read the manual.
<christo_m> im doing that
<christo_m> quick question: is there a function in ocaml to return the absolute number
<christo_m> something similar to fabs() in C
<Smerdyakov> You really should read through the manual.
<Smerdyakov> Library documentation in particular, for a question like this.
<thermoplyae> maybe even just having a link to http://caml.inria.fr/pub/docs/manual-ocaml/libref/ would help
<thermoplyae> your question lies in Pervasives
<christo_m> thank you
<christo_m> something more helpful then "read through the manual"
<Smerdyakov> "Read through the manual" is the most helpful answer.
<thermoplyae> no, i completely agree with him, read the manual
<ozy`> Smerdyakov: what a clever yet highly suspicious nick
<Smerdyakov> You should read skim every page to form a mental map of what's there.
<Smerdyakov> s/read skim/skim
<Smerdyakov> ozy`, new to the channel, eh? :)
<ozy`> yes
<ozy`> I only started learning OCaml last week
<ozy`> and lurked a bit
<Smerdyakov> Rochester, eh? Are you learning as part of a course?
<christo_m> ozy`: hah i started last week too
Adeline has quit ["Bone of the father, unknowingly given, you will renew your son. Flesh of the servant, willing given, you will revive your mas]
ozzloy has quit [Remote closed the connection]
ozzloy has joined #ocaml
coucou747 has joined #ocaml
<coucou747> hi
<coucou747> i'm searchin the list of ocaml operators on google
<coucou747> but i've not found
<Smerdyakov> Don't use Google for that. Use the manual.
<coucou747> i search, but...
<coucou747> Smerdyakov, and I don't know why we can't use our own operator...
<coucou747> in ocaml, we have to use their names...
<coucou747> we can make let (..) a b = ...
<coucou747> to have 1..5 = [1;2;3;4;5]
<Smerdyakov> Are you saying you don't know where the OCaml manual is?
<coucou747> http://www.google.fr/search?q=operator+site:http://caml.inria.fr/&start=100
<Smerdyakov> Is that supposed to be an answer to my question?
<Smerdyakov> That isn't the manual, no.
<coucou747> ok
<coucou747> so ?
<coucou747> i've seen these page
<coucou747> but this is not on the core language
christo_m has quit ["leaving"]
<Smerdyakov> You want to read about lexing.
<Smerdyakov> It also sounds like you are looking for answers in Part I.
<Smerdyakov> Never do that. Part I is a tutorial. The rest of the manual is for reference.
<coucou747> i don't make a lexer
<coucou747> i just use ocaml
<Smerdyakov> You should skim every page of the manual before asking any further questions here. Form a mental map of what's available.
<Smerdyakov> I'm talking about the lexical rules for the OCaml language, not writing your own lexer.
DroneZilla has joined #ocaml
Mr_Awesome has joined #ocaml
<coucou747> hum...
Proteus has quit [Read error: 113 (No route to host)]
seafood has quit []
seafood has joined #ocaml
<coucou747> Smerdyakov, I've not seen...
Proteus has joined #ocaml
<coucou747> but i've made my programm :D
<coucou747> let rec ($) a b = if a = b then [a] else a::( (a+1) $ b);;
<coucou747> let rec (!) = function ...
<coucou747> Smerdyakov, and then : ! (1 $ 5);;
<coucou747> it returns the list of the permutations of [1;2;3;4;5]
<coucou747> I wanted the documentation of the operator to delete the braces
<coucou747> and to have better than $
DroneZilla has quit []
jeddhaberstro has quit []
coucou747 has quit ["bye ca veut dire tchao en anglais"]
seafood_ has joined #ocaml
seafood has quit [Read error: 110 (Connection timed out)]
seafood has joined #ocaml
seafood_ has quit [Read error: 110 (Connection timed out)]
thelema has joined #ocaml
<palomer> two different record types can't contain the same field name, right?
Demitar has joined #ocaml
<thelema> in the same module, yes.
seafood_ has joined #ocaml
seafood_ has quit [Read error: 104 (Connection reset by peer)]
seafood_ has joined #ocaml
seafood has quit [Read error: 110 (Connection timed out)]
thermoplyae has left #ocaml []
mishok13 has joined #ocaml
gdmfsob has joined #ocaml
<palomer> polymorphic variants rock!
Associat0r has quit []
mishok13 has quit [Read error: 110 (Connection timed out)]
<palomer> 84 line error messages should be illegal.
<palomer> seriously.
<mattam> Error at line 6 character 3-10: <REDACTED>
shortc|desk has quit [Remote closed the connection]
Yoric[DT] has joined #ocaml
filp has joined #ocaml
<palomer> woot!
<palomer> I was scared to make a major change to my code
<palomer> but I did it!
<palomer> ocamlwc gives me 6000 lines
<palomer> ugh.
seafood_ has quit [Read error: 110 (Connection timed out)]
rmns has joined #ocaml
<Yoric[DT]> palomer: congratulations :)
<flux> ocamlwc?
<flux> I've found static typing extremely comforting when making large refactorings to code :)
<flux> hm, s/comforting/comfortable/, perhaps
Associat0r has joined #ocaml
* Yoric[DT] concurs.
Yoric[DT] has quit ["Ex-Chat"]
electronx has joined #ocaml
electronx has quit []
rmns has left #ocaml []
m3ga has joined #ocaml
petchema has quit [Read error: 110 (Connection timed out)]
OChameau has joined #ocaml
Axioplase_ is now known as Axioplase
Asmadeus_ has joined #ocaml
Asmadeus_ has quit [Client Quit]
petchema has joined #ocaml
mfp has joined #ocaml
hsuh has joined #ocaml
GustNG has joined #ocaml
hsuh has quit [Read error: 104 (Connection reset by peer)]
m3ga has quit ["disappearing into the sunset"]
sporkmonger has quit []
sporkmonger has joined #ocaml
sporkmonger_ has joined #ocaml
SanguineV has quit []
sporkmonger has quit [Read error: 110 (Connection timed out)]
sporkmonger has joined #ocaml
rwmjones has joined #ocaml
sporkmonger_ has quit [Connection timed out]
ozy` has quit []
DroneZilla has joined #ocaml
rwmjones has quit ["Closed connection"]
mlh has joined #ocaml
Associat0r has quit []
gdmfsob has quit [Read error: 110 (Connection timed out)]
sporkmonger has quit []
rmns has joined #ocaml
Axioplase is now known as Axioplase_
guillem_ has joined #ocaml
DroneZilla has quit [Read error: 113 (No route to host)]
struktured has quit [Read error: 110 (Connection timed out)]
Linktim has joined #ocaml
marmotine has joined #ocaml
DroneZilla has joined #ocaml
filp has quit ["Bye"]
Linktim_ has joined #ocaml
Linktim has quit [Read error: 113 (No route to host)]
sporkmonger has joined #ocaml
guillem_ has quit [Remote closed the connection]
Yoric[DT] has joined #ocaml
jlouis has joined #ocaml
ozy` has joined #ocaml
OChameau has quit ["Leaving"]
<Yoric[DT]> ertai: ping
Snark has joined #ocaml
<ertai> Yoric[DT]: pong
<Yoric[DT]> Hi.
<ertai> Yoric[DT]: Hello
<Yoric[DT]> I'm trying to write a OCamlBuild plug-in to automatically generate the .mli corresponding to a .mlpack (for documentation purposes).
<Yoric[DT]> I've written a [rule] which lets me depend a .mli on the corresponding .mlpack .
<Yoric[DT]> From the .mlpack, I can obtain the list of modules.
<Yoric[DT]> Now, I need to read the .depends of each of these modules.
<Yoric[DT]> This causes two problems:
<Yoric[DT]> 1) the .depends are obviously generated after my rule
<Yoric[DT]> (so I can't read them, obviously)
<Yoric[DT]> 2) I have the name of the modules, not that of the source files
<Yoric[DT]> (which may or may not be moduleWithoutCap.mli, depending on things such as, well, the presence of other .mlpack)
<Yoric[DT]> What should I do?
<flux> write to the mailing list, obviously :)
sixty8k has joined #ocaml
<flux> I have a feeling that ocamlbuild isn't a tool that is well-known by many..
<Yoric[DT]> Which is why I'm asking ertai :)
<flux> oh, right, missed the hand-shake
Submarine has joined #ocaml
<Yoric[DT]> ertai: ?
<flux> yoric[dt], maybe you should upgrade to four-way handshake
<Yoric[DT]> African-style?
<flux> mm, I don't think I get that reference..
<Yoric[DT]> No, I've just heard that referenced as the African double handshake, that's it.
<Yoric[DT]> ertai: ping?
DroneZilla has quit []
struktured has joined #ocaml
<Yoric[DT]> :(
* Yoric[DT] should have tried something even stronger than the four-hands handshake.
GustNG has quit [Read error: 104 (Connection reset by peer)]
jeddhaberstro has joined #ocaml
jeddhaberstro_ has joined #ocaml
tomh has joined #ocaml
vixey has joined #ocaml
Snark has quit ["Ex-Chat"]
jeddhaberstro has quit [Read error: 110 (Connection timed out)]
Linktim has joined #ocaml
tomh has quit ["http://www.mibbit.com ajax IRC Client"]
<Yoric[DT]> ertai: ping
<palomer> hrmph
<palomer> gtk's combo suggestion widget is ugly and impractical
sbok_ has joined #ocaml
Asmadeus_ has joined #ocaml
Asmadeus has quit [Broken pipe]
sbok has quit [Broken pipe]
Linktim_ has quit [Read error: 113 (No route to host)]
fremo has joined #ocaml
Amorphous has quit [Connection timed out]
Amorphous has joined #ocaml
Jedai has quit [Read error: 104 (Connection reset by peer)]
Jedai has joined #ocaml
hkBst has joined #ocaml
Submarine has quit [Read error: 110 (Connection timed out)]
Linktim has quit ["Quitte"]
rmns has left #ocaml []
sporkmonger has quit [Read error: 110 (Connection timed out)]
jeddhaberstro_ has quit []
sporkmonger has joined #ocaml
sixty8k_ has joined #ocaml
sixty8k_ has quit [Client Quit]
sporkmonger has quit []
sporkmonger has joined #ocaml
marmotine has quit [Remote closed the connection]
jeddhaberstro has joined #ocaml
jeddhaberstro has quit [Client Quit]
sixty8k has quit [Connection timed out]
sporkmonger has quit []
jlouis has quit ["Leaving"]
struktured has quit [Connection timed out]
Yoric[DT] has quit ["Ex-Chat"]
vixey has quit [Read error: 113 (No route to host)]
hkBst has quit [Read error: 104 (Connection reset by peer)]
struktured has joined #ocaml
bohanlon has joined #ocaml
snhmib has joined #ocaml
<snhmib> hello
<snhmib> could someone help me with ocaml object system? i have one file (tokens.mli) that starts with
<snhmib> module type TOKENS =
<snhmib> sig
<snhmib> and then tokens.ml which starts with: module Tokens : TOKENS =
<snhmib> struct
<snhmib> and then i compile the .mli first with ocamlc -c
<snhmib> but when i try to compile the .ml file (ocamlc -c tokens.ml) it errors with
<snhmib> File "tokens.ml", line 1, characters 16-22:
<snhmib> Unbound module type TOKENS
<snhmib> and i'm a bit stuck :(
<Smerdyakov> This has nothing to do with OCaml objects.
<Smerdyakov> You meant to ask about "the module system."
<snhmib> ah sorry
<Smerdyakov> You are also confusing modules and module types.
<Smerdyakov> They are two different things.
<Smerdyakov> Your signature says there will be a module type, but your implementation only defines a module.
<snhmib> oh
<Smerdyakov> You should probably re-read the documentation on .mli and .ml files.
<Smerdyakov> I think you misunderstand what they mean.
<snhmib> i didn't get that from the book.. (the type)
<Smerdyakov> What book?
<snhmib> developping applications with ocaml (pdf from oreilly)
<snhmib> but maybe i skimmed over it :)
<Smerdyakov> I can only vouch for the OCaml manual, not that book.
<snhmib> oh
<snhmib> thanks it works now :)