<caseyjames>
Hi, I'm getting an error: has type 'a -> 'b but an expression was expected of type int * int * int * int * int with a curried function that should be taking a tuple an ideas? List.fold [] encoded ~f:(fun x -> extract_features [Down] Length 1 x)
malc_ has joined #ocaml
zpe has joined #ocaml
struktured has quit [Remote host closed the connection]
struktured has joined #ocaml
zpe has quit [Ping timeout: 248 seconds]
malc_ has quit [Quit: leaving]
nikki93 has joined #ocaml
derek_c has joined #ocaml
<caseyjames>
Anyone know why this isn't working - List.fold [] [(1, 60, 3, 3, 62); (4, 50, 4, 7, 80)] ~f:(fun x -> x)
Drup has quit [Quit: Leaving.]
shinnya has joined #ocaml
talzeus has joined #ocaml
csakatoku has joined #ocaml
ben_zen has quit [Read error: Connection reset by peer]
ben_zen has joined #ocaml
shinnya has quit [Ping timeout: 264 seconds]
levi` has joined #ocaml
zpe has joined #ocaml
shinnya has joined #ocaml
levi has quit [Ping timeout: 264 seconds]
shinnya has quit [Ping timeout: 241 seconds]
<bernardofpc>
caseyjames: the function in fold takes 2 arguments
zpe has quit [Ping timeout: 240 seconds]
<bernardofpc>
The basic example is product mylist = List.fold 1 list ~f:(fun current_product nextelem -> current_product*nextelem)
<bernardofpc>
(probably, most people would write (fun acc x -> acc*x) for "accumulator"
<bernardofpc>
and not really care to give a pretty name for the element, so "x" is good enough)
<caseyjames>
Hmm, i didn't realize that. Is there a difference between List.fold and List.fold_left?
<bernardofpc>
I don't know List.fold
<bernardofpc>
but I guess you're using Core (because of the ~f)
<bernardofpc>
in the stdlibrary, it's fold_left, with the behaviour I just described
<bernardofpc>
(wit a different order of arguments, moreover)
<caseyjames>
Ths is still acting up, is there something else wrong? List.fold_left [] [(1, 60, 3, 3, 62); (4, 50, 4, 7, 80)] ~f:(fun acc x -> x::acc)
<bernardofpc>
so I don't know about their interface List
<caseyjames>
I see. There doesn't see to be much discussion on it or much of anything on google
madroach has quit [Ping timeout: 264 seconds]
madroach has joined #ocaml
ygrek has joined #ocaml
kizzx2 has joined #ocaml
struktured has quit [Ping timeout: 260 seconds]
q66 has quit [Quit: Leaving]
zpe has joined #ocaml
<bernardofpc>
caseyjames: you coded (I guess) the identity function on lists
oriba has quit [Quit: oriba]
<bernardofpc>
or, rather, the reversal of the list
<caseyjames>
I noticed the reversal aspect in my real function. Where is the common practice location to reverse the list back, or is there one? Do people tend to build that into the function?
struktured has joined #ocaml
<bernardofpc>
really depends if you care...
<bernardofpc>
I wrote today a function to generate permutations of a list in no particular order...
<bernardofpc>
but I guess you should inform if what you're doing reversees or not the list
ocp1 has quit [Quit: Leaving.]
zpe has quit [Ping timeout: 260 seconds]
struktured has quit [Remote host closed the connection]
derek_c has quit [Ping timeout: 264 seconds]
manizzle has quit [Ping timeout: 248 seconds]
zpe has joined #ocaml
yacks has quit [Ping timeout: 256 seconds]
zpe has quit [Ping timeout: 264 seconds]
derek_c has joined #ocaml
yacks has joined #ocaml
cesar_ has joined #ocaml
cesar_ is now known as Guest99886
derek_c has quit [Ping timeout: 264 seconds]
Kelet has quit [Quit: bbl]
derek_c has joined #ocaml
zpe has joined #ocaml
mcclurmc has quit [Ping timeout: 252 seconds]
mcclurmc has joined #ocaml
zpe has quit [Ping timeout: 260 seconds]
manizzle has joined #ocaml
gour has joined #ocaml
manizzle has quit [Remote host closed the connection]
zpe has joined #ocaml
zpe has quit [Ping timeout: 248 seconds]
Guest99886 has quit [Remote host closed the connection]
zpe has joined #ocaml
derek_c has quit [Ping timeout: 260 seconds]
cesar_ has joined #ocaml
cesar_ is now known as Guest60382
derek_c has joined #ocaml
yacks has quit [Quit: Leaving]
zpe has quit [Ping timeout: 248 seconds]
kizzx2 has quit [Quit: Leaving.]
ben_zen has quit [Ping timeout: 264 seconds]
zpe has joined #ocaml
Snark has joined #ocaml
zpe has quit [Ping timeout: 264 seconds]
manizzle has joined #ocaml
csakatok_ has joined #ocaml
csakatoku has quit [Ping timeout: 256 seconds]
zpe has joined #ocaml
zpe has quit [Ping timeout: 252 seconds]
weie_ has joined #ocaml
weie has quit [Ping timeout: 245 seconds]
ulfdoz has joined #ocaml
ggole has joined #ocaml
yezariaely has joined #ocaml
ygrek has quit [Ping timeout: 245 seconds]
kizzx2 has joined #ocaml
mcclurmc has quit [Quit: Leaving.]
zpe has joined #ocaml
ttamttam has joined #ocaml
zpe has quit [Ping timeout: 260 seconds]
ulfdoz has quit [Ping timeout: 240 seconds]
nikki93 has quit [Remote host closed the connection]
deavidsedice has joined #ocaml
deavid has quit [Read error: Connection reset by peer]
Cypi has quit [Ping timeout: 264 seconds]
gildor has quit [Ping timeout: 264 seconds]
Cypi has joined #ocaml
gildor has joined #ocaml
dtg has quit [Ping timeout: 245 seconds]
wagle has quit [Ping timeout: 256 seconds]
zpe has joined #ocaml
djcoin has joined #ocaml
ontologiae_ has joined #ocaml
zpe has quit [Ping timeout: 256 seconds]
ontologiae_ has quit [Ping timeout: 257 seconds]
ygrek has joined #ocaml
zpe has joined #ocaml
zpe has quit [Ping timeout: 245 seconds]
ttamttam has quit [Ping timeout: 252 seconds]
Yoric has joined #ocaml
bondar has joined #ocaml
nikki93 has joined #ocaml
nikki93 has quit [Ping timeout: 248 seconds]
derek_c has quit [Quit: Lost terminal]
zpe has joined #ocaml
ontologiae_ has joined #ocaml
tristero has quit [Ping timeout: 246 seconds]
Guest60382 has quit [Remote host closed the connection]
skchrko has quit [Quit: Leaving]
darkf has quit [Read error: Connection reset by peer]
darkf has joined #ocaml
ttamttam has joined #ocaml
Simn has joined #ocaml
ivan\ has quit [Ping timeout: 248 seconds]
Yoric has quit [Ping timeout: 264 seconds]
zpe has quit [Remote host closed the connection]
mort___ has joined #ocaml
mfp has joined #ocaml
manud2 has joined #ocaml
Kakadu has joined #ocaml
kizzx2 has quit [Ping timeout: 252 seconds]
kizzx2 has joined #ocaml
yacks has joined #ocaml
<Simn>
What's the easiest way to get a revision number (e.g. from git describe) into an OCaml compilation?
<flux>
simn, with a Makefile I would have a version.mli and generate version.ml in the Makefile
<flux>
it would result in version.ml being compiled always, but that's probably not a big deal
<companion_cube>
you can also do it with oasis
<ggole>
Hrm, it seems that every time I define something that is iterable, I end up writing an iter, fold, for_all and exists.
<ggole>
Is there a nice way to write one thing and get the rest?
<Simn>
I see, I was afraid these were the straightforward options. Thanks!
skchrko has joined #ocaml
<companion_cube>
with fold, you can write iter very easily
<companion_cube>
but exists and for_all need an exception if you need early return
talzeus has quit [Remote host closed the connection]
darkf has quit [Quit: Leaving]
<yezariaely>
Maybe someone can give me a pointer. I need a mutually recursive definition of a type and a module using this type: http://pastebin.com/yjfwtpA3 so instead of line 3 beeing a list of states, I want it to be a States.t Any hint? I am clueless right now :/
Yoric has joined #ocaml
beckerb has joined #ocaml
Kakadu has quit []
Kakadu has joined #ocaml
ollehar has joined #ocaml
<yezariaely>
hmm as it seems my design is completely broken.
<yezariaely>
never mind. I have to refactor the whole code anyway.
Kakadu has quit []
Drup has joined #ocaml
zpe has joined #ocaml
zpe has quit [Ping timeout: 260 seconds]
ontologiae_ has quit [Ping timeout: 246 seconds]
nikki93 has joined #ocaml
manizzle has quit [Ping timeout: 248 seconds]
kizzx2 has quit [Quit: Leaving.]
nikki93 has quit [Ping timeout: 252 seconds]
<yezariaely>
Is there a deeper reason why BatMap.S is polymorphic in its value?
<flux>
there is no deep reason for it not to be..
<flux>
there is a deep reason for the key to be non-polymorphic
<flux>
I suppose it's bad when you want to have an IntIntMap
<flux>
but good when you want to have IntMap and use that with different kind of values
<flux>
a lot more module names flying aroudn
<flux>
um, I mean less
<yezariaely>
flux: so the assumption is, that the set of possible keys is smaller than the set of possible values I could create a map for. Yes, makes sense to me. Thanks!
<flux>
yezariaely, if it were so that keys were polymorphic, the types of two sets where one would have keys in ascending order and one would have keys in descening order would be the same
<flux>
this would result in trouble when operations between those sets would be performed
<flux>
(oops, I mean maps)
<flux>
but for values there are no constrains defined in map, so it can remain polymorphic
<yezariaely>
flux: I did not question that the types of the keys are predefined. I just wondered why not predefine values.
<yezariaely>
,too.
<flux>
I think we understand each other now :)
<yezariaely>
:) that's nice
q66 has joined #ocaml
talzeus has joined #ocaml
ivan\ has joined #ocaml
<pippijn>
actually
<pippijn>
sometimes it is useful to have IntIntMap
<flux>
it is, and then it gets annyoing :)
ivan\ has quit [Ping timeout: 264 seconds]
ivan\ has joined #ocaml
manud2 has quit [Quit: Leaving]
csakatoku has joined #ocaml
csakatok_ has quit [Read error: Connection reset by peer]
ben_zen has joined #ocaml
nikki93 has joined #ocaml
nikki93 has quit [Ping timeout: 246 seconds]
ygrek has quit [Ping timeout: 240 seconds]
csakatoku has quit [Remote host closed the connection]
_andre has joined #ocaml
cdidd has quit [Remote host closed the connection]
talzeus has quit [Remote host closed the connection]
talzeus has joined #ocaml
Kakadu has joined #ocaml
zpe has joined #ocaml
breakds has joined #ocaml
ontologiae_ has joined #ocaml
Kakadu has quit [Ping timeout: 264 seconds]
q66_ has joined #ocaml
q66 has quit [Ping timeout: 252 seconds]
ollehar has quit [Ping timeout: 273 seconds]
octet8 has joined #ocaml
bondar has quit []
<yezariaely>
BatMap.modify_def says: modify_def v0 k f m replaces the previous binding for k with f applied to that value. If k is unbound in m or Not_found is raised during the search, f v0 is inserted (as if the value found were v0). But why adding f v0 when the element is not found?! I thought f is the merge function that combines old and new element and then f v0 is inserted as new element?!
<yezariaely>
why not simply inserting v0?
bondar has joined #ocaml
biloute has joined #ocaml
bondar has quit []
bondar has joined #ocaml
ben_zen has quit [Ping timeout: 240 seconds]
biloute has quit [Quit: Leaving]
cdidd has joined #ocaml
yacks has quit [Quit: Leaving]
<ggole>
Write side effecting recursive function, forget to call it within itself, spend ten minutes debugging why it doesn't work. Sigh.
<companion_cube>
:D
<companion_cube>
maybe OCaml should warn when "let rec" is not used
<ggole>
Yeah, maybe
Qrntz has joined #ocaml
Qrntz has quit [Changing host]
Qrntz has joined #ocaml
breakds has quit [Quit: Konversation terminated!]
asmanur has quit [Ping timeout: 268 seconds]
asmanur has joined #ocaml
mcclurmc has joined #ocaml
q66_ is now known as q66
yezariaely has quit [Quit: Leaving.]
Yoric has quit [Ping timeout: 246 seconds]
bondar has quit [Ping timeout: 240 seconds]
gour has quit [Quit: WeeChat 0.4.1]
Yoric has joined #ocaml
gour has joined #ocaml
Yoric has quit [Ping timeout: 240 seconds]
shinnya has joined #ocaml
asmanur has quit [Ping timeout: 252 seconds]
asmanur has joined #ocaml
<ggole>
Values do not match: val equal : t -> t -> bool is not included in val equal : t -> t -> bool
<ggole>
Um.
<ggole>
Never mind, I'm a retard
mcclurmc has quit [Quit: Leaving.]
<ggole>
(Did the type alias = t trick to avoid shadowing in a functor, forgot the = t part.)
iZsh has quit [Quit: Coyote finally caught me]
iZsh has joined #ocaml
iZsh has quit [Excess Flood]
iZsh has joined #ocaml
Kakadu has joined #ocaml
thomasga has joined #ocaml
Yoric has joined #ocaml
skchrko has quit [Quit: Leaving]
ygrek has joined #ocaml
ontologiae_ has quit [Ping timeout: 248 seconds]
Yoric has quit [Ping timeout: 240 seconds]
zpe has quit [Remote host closed the connection]
mort___ has quit [Quit: Leaving.]
troydm has quit [Quit: What is hope? That all of your wishes and all of your dreams come true? (C) Rau Le Creuset]
talzeus has quit [Remote host closed the connection]
troydm has joined #ocaml
wagle has joined #ocaml
Simn has quit [Ping timeout: 240 seconds]
ccasin has joined #ocaml
Simn has joined #ocaml
Yoric has joined #ocaml
<technomancy>
I'm mildly baffled about when the toplevel is able to find libraries installed by opam or not
<technomancy>
opam lists core and async as installed
<technomancy>
when I run utop in ~, I can't open Core.Std or Async.Std
<technomancy>
when I run utop inside my project dir (which uses core and async just fine) I can open Core.Std but not Async.Std
<Drup>
technomancy: did you do the whole opam eval thingy ?
<technomancy>
Drup: yeah
<technomancy>
"ocamlbuild -use-ocamlfind ..." finds both of them just fine
<ggole>
Oh, it's in whichever one of batteries and core you aren't using.
<Drup>
this, very unfortunatly, not in the standard library
<technomancy>
heh; right. I've got core
Kakadu has quit []
* ggole
has written option_map a few times now
<technomancy>
if it's the price you pay for not getting repeatedly battered with monad tutorials when you first put your foot in the door maybe I'm OK with that
<ggole>
Something something burrito
Drup has quit [Ping timeout: 264 seconds]
zpe has joined #ocaml
nikki93 has quit [Remote host closed the connection]
q66 has quit [Read error: Connection reset by peer]
q66_ is now known as q66
tane has joined #ocaml
<levi>
technomancy: That looks to me more like what Haskell would call a Functor rather than a full Monad. Basically it only provides a 'map' function for the type that applies its functional parameter "evenly"/"composably" to the members of the type. So, a generalization of List.map to other types. You'd use an Option Monad if you wanted to compose a bunch of operations that return Option values and have the entire thing return None without
<levi>
trying the subsequent operations as soon as one returned None.
<technomancy>
gotcha; so it'd be overkill for a single function
<levi>
So making a Monad around Option would be a good idea if you often need to chain together pipelines of possibly-failing operations without explicitly checking for failures, and you don't want to use exceptions.
<ggole>
It's Lisp's or, but principled.
<technomancy>
in clojure it's called -?>
<levi>
In haskell Monads and Functors and whatnot are everywhere and syntactically cheap to use, so they get used for little things that you might solve other ways in other languages.
<technomancy>
or nil-safe-thread-first if you're not into the whole brevity thing
<technomancy>
well, the full chain. I guess the single call is like or
Ori_B has joined #ocaml
Ori_B has left #ocaml []
<technomancy>
huh; just got the connection between List.map and Option.map
ollehar has joined #ocaml
<ggole>
iter, fold, for_all and some others also make sense (although the names aren't quite right).
<technomancy>
right; iter implies a collection
<levi>
OCaml makes you be explicit about the specializations of module signatures you're using, so trying to write Haskell-style code in OCaml can sometimes be awkward. On the other hand, OCaml provides more flexibility in that you can have multiple versions of the modules in play at the same time without the 'newtype' workarounds Haskell requires for that.
<technomancy>
is that what you meann?
<ggole>
Yeah, more or less.
<technomancy>
how would fold be distinct from map on a single value?
<ggole>
Empty case.
<technomancy>
oh, of course
<levi>
Robert Harper presented some interesting ideas for evolving ML at one of the functional programming conferences this year... I can't remember which one, though. CUFP, I think?
<Drup>
levi: there is also a syntax extension using ppx that introduce a lightweith do notation
beckerb has quit [Ping timeout: 245 seconds]
<levi>
Drup: Right, but the do notation is just part of the difference between Haskell and OCaml when it comes to writing monadic code.
<Drup>
sure, but the implicit aspect of it is a big one
<levi>
I'm not fully familiar with the syntax extension you're talking about, so I'm not sure what gaps between the language it bridges.
<levi>
The difference between that and how you'd write it in Haskell is that in OCaml you have to explicitly tell what monad your code gets its definition of bind, return, and fail from. That lets you write two different Monads for List that have different (bind,return,fail) implementations, but makes it a bit awkward to use both a List monad and an Option monad in the same block, for example.
zpe has joined #ocaml
<Drup>
agreed :)
Yoric1 has joined #ocaml
<levi>
Basically, both Haskell's type class system and the ML family's module/functor system are awesome, but no one has figured out and implemented a way to combine them yet without breaking the nice properties of one or the other. At least not that I know of.
Yoric has quit [Ping timeout: 245 seconds]
<rks`>
levi: have you looked at Coq?
<rks`>
:)
<levi>
I have not studied it deeply, but I've worked through a few chapters of Software Foundations.
<adrien>
ML modules are simple :P
caseyjames has quit [Ping timeout: 250 seconds]
<levi>
Nobody said they weren't.
thomasga has quit [Quit: Leaving.]
<rks`>
anyway
<adrien>
levi: I was answering "Coq" ;p
<rks`>
Coq has "caml"'s modules/functors
<rks`>
and typeclasses
<rks`>
(which I am assuming work as the one you would find in haskell, but I never used them, so don't take my word for it)
<rks`>
adrien: well, from the point of view of the user, Coq module system is the same as ocaml's
<rks`>
(imho)
Yoric1 has quit [Ping timeout: 245 seconds]
<adrien>
yeah, I was trolling a bit (even though I'm a few hours early) but mostly meant that coq, as a whole, was not as simple as ml modules :)
Ori_B has joined #ocaml
yacks has joined #ocaml
nikki93 has joined #ocaml
<levi>
Heh, I just read the chapter on type classes in Coq's manual. I followed most of it, but I am not sure of all the implications of how it works.
Yoric has joined #ocaml
Ori_B has left #ocaml []
nikki93 has quit [Remote host closed the connection]
Breadmonster has joined #ocaml
<Breadmonster>
How do I go ahead and learn OCaml?
<Breadmonster>
I can't find a book about actual application development, instead of a toploop.
<Breadmonster>
I'm waiting for Real World OCaml to come out, but I guess I've gotta wait until December for it.
<jpdeplaix>
Breadmonster: RWO is already accessible
<Drup>
you gotta start by trying to fiddle with the toploop anyway to get the basics.
<gour>
Breadmonster: RWO is available online
<Breadmonster>
Okay, fine.
<ggole>
There's a fat pdf on systems programming in OCaml too, although it is a bit dated.
<Breadmonster>
Okay.
<Breadmonster>
I really want to learn the langauge.
<Breadmonster>
Haskell is a bit harder for these kind of things, and I hear that Jane Street's Core is really making new strides.
<gour>
anyone was present at the ocaml workshop few days ago?
<Drup>
I quite liked "Developing Applications With OCaml" when I was learning, It's a bit old but it shouldn't be outdated since the core of ocaml didn't move that much.
<gour>
Drup: how do you like RWO?
<Drup>
didn't read it. Does it still nead to link your github account ?
dtg has joined #ocaml
<Drup>
adrien asked me to say it, so : "Too much core" :]
* Drup
blame adrien.
<gour>
i believe it does not
<adrien>
blame*s*
<adrien>
gour: well, it definitely has a fair amount of Core :)
<gour>
heh, it would be nice to standardize those things, iow. fill the gaps missing in standard lib and make it standard
<Drup>
ahahahah
<gour>
now, there is standard, batteries & core, right?
<Drup>
nice try, can you do some other jokes like that and put them on the ML ?
<Drup>
yes, mostly
<gour>
heh, vaccine for NIH is needed :-)
<adrien>
gour: Core and Batteries do things in pretty different ways
<Drup>
adrien : they both claim to "replace and enhance the standard library"
<gour>
ahh
<adrien>
do they have something else in common? :P
<Drup>
not really.
<gour>
otoh, putting stuff under ocaml.org subdoamin looks good
<adrien>
I'm a bit annoyed because the updates don't seem to be plentiful
darkf has joined #ocaml
<gour>
updates for which one?
<adrien>
ocaml.org
<adrien>
I don't know if it's because noone has updated the website and sent a pull request in the last two weeks or another reason
* gour
was thinking about some 'standard' lib :-)
<adrien>
ah
<gour>
have you seen proposal for new version of the site?
<Drup>
I really need to take the time to do bug report about it. :/
<adrien>
gour: that's about the design and I'm concerned about the content
<gour>
adrien: correct...mine was just side point, although i noticed it changes how some content is promoted more to the front-end in comparison with the current one
buddyholly has joined #ocaml
<ggole>
match match foo with <many cases> with None -> () | Some x -> process x
<ggole>
I don't really want to construct the option at all :/
<whitequark>
call process directly then?
<ggole>
For about half the cases I want to just do nothing, for the other half I want to calc a value and then process that
gour has quit [Disconnected by services]
<ggole>
Perhaps I should be working harder to split things up.
gour_ has joined #ocaml
willy_ has joined #ocaml
ikudrautsau has joined #ocaml
ikudrautsau has quit [Max SendQ exceeded]
ikudrautsau has joined #ocaml
ikudrautsau has quit [Max SendQ exceeded]
ikudrautsau has joined #ocaml
ikudrautsau has quit [Max SendQ exceeded]
ikudrautsau has joined #ocaml
ikudrautsau has quit [Max SendQ exceeded]
ikudrautsau has joined #ocaml
ikudrautsau has quit [Max SendQ exceeded]
ikudrautsau has joined #ocaml
ikudrautsau has quit [Max SendQ exceeded]
ontologiae_ has joined #ocaml
Breadmonster has quit [Ping timeout: 250 seconds]
ikudrautsau has joined #ocaml
ikudrautsau has quit [Max SendQ exceeded]
ikudrautsau has joined #ocaml
ikudrautsau has quit [Max SendQ exceeded]
ikudrautsau has joined #ocaml
Snark has quit [Quit: leaving]
nicoo has quit [Ping timeout: 248 seconds]
_andre has quit [Quit: leaving]
mcclurmc has joined #ocaml
Kakadu has joined #ocaml
ggole has quit []
<adrien>
gildor: hi! in ocaml-fileutils, line 919 of FileUtil.ml, "stat()" is used but I believe that "*l*stat()" should be used instead; otherwise this skips any symlink with a non-existent target (and this doesn't match the find(1) tool)
<adrien>
gildor: what do you think about changing it?
gour_ has quit [Quit: WeeChat 0.4.1]
<argp>
i am trying to compile a 32-bit version of ocaml 4.01.0 on os x
<argp>
using the configure line from the INSTALL file
<argp>
make world.opt gives the following error:
<argp>
signals_asm.c:213: error: ‘struct __darwin_i386_thread_state’ has no member named ‘__rip’
ikudrautsau has left #ocaml []
ipoulet_ has quit [Quit: leaving]
nikki93 has joined #ocaml
tane has quit [Quit: Verlassend]
demonimin has quit [Ping timeout: 260 seconds]
ontologiae_ has quit [Ping timeout: 246 seconds]
mcclurmc has quit [Quit: Leaving.]
Kakadu has quit []
djcoin has quit [Quit: WeeChat 0.4.1]
zpe has quit [Remote host closed the connection]
nicoo has joined #ocaml
ollehar has quit [Ping timeout: 240 seconds]
weie_ has quit [Quit: Leaving...]
demonimin has joined #ocaml
iZsh has quit [Excess Flood]
iZsh has joined #ocaml
willy_ has quit [Remote host closed the connection]
caseyjames has joined #ocaml
<caseyjames>
can someone tell me what this error is about: [ (Foo, [Ding,Dong,Dee,Dah]); (Bar, [Ding,Dong,Dee,Dah]); (Rah, [Ding,Dong,Dee,Dah]) ] Error: Parse error: currified constructor
<Drup>
huh, the piece of code doesn't raise any parsing error for me
<caseyjames>
AHH! Once again ',' in place of ';' in my lists... I need to set a bunsen burner for a pavlovs dog approach
<mrvn>
xaimus: That doesn't explain the error. Sounds more like one of your constructors expects arguments.
<mrvn>
caseyjames: ^^^
<mrvn>
stupid x is too close to c.
<caseyjames>
after changing that particular error went away, or was replaced with another that I'm poking at..
<ng_>
someone can help me finish it? What is wrong?
<kerneis>
ng_: what formula are you trying to write exactly?
<kerneis>
the first one on that page?
<ng_>
b0 =1 b1=1 b2= 1C0 * B0 + 1C1*B1
<kerneis>
in any case, OCaml is probably *not* the best language to do that kind of computation (except if this is an exercise on recursivity)
<Drup>
ng_: why don't you use the regular recursive formula ? it's more suited
<Drup>
(the one in the wikipedia page you show yesterday)
<ng_>
Drup, but it is not going well?
<kerneis>
well, trying to get an exact integer result using a formula with infinite sums and exponentials in OCaml (or anything with floating-point arithmetic really) is *never* going to end well
<kerneis>
any formula operating purely on integers would be better
<Drup>
kerneis: there is a simple recursive formula on integer
<Drup>
ng_: as kerneis said, this formula is really not the one you should try to use
<kerneis>
ng_: so you first need to implement (n k) in ocaml
<Drup>
kerneis: Gabriel's Minds Confederated :]
<CissWit>
the triangle scheme looks nice too to implement this
<mrvn>
trying to implement a recursive formula goes so much better if you actualy start from a recursive formula.
<kerneis>
what, CissWit is on #ocaml too?
<CissWit>
looks like i am !
<kerneis>
guys, could you please stop being on exactly the same channels as I do
<kerneis>
I feel so unoriginal
<CissWit>
sorry to hurt your hipster side
<CissWit>
^^
<ng_>
ok, I'm completely lost, what can I do? I can only try to finish this and then did the other way?
<mrvn>
kerneis: don't join channels we are already on then
<Drup>
ng_: did you do the fibonacci function first, as an exercise, as I told you yesterday ?
<kerneis>
it's just that the intersection between #regardscitoyens, #weboob and #ocaml is much too big, although they seem to have very little in common, it's disturbing
<kerneis>
(ok, community of french hackers is a common denominator)</off topic>
BiDOrD has joined #ocaml
<ng_>
Drup, +-, but my reasoning is wrong?
mcclurmc has joined #ocaml
<Drup>
what reasoning ?
<Drup>
the piece of code you posted is not correct at all, if that's the question, but the problem is more conceptual than anything. Don't try to do something complicated dirrectly and take the time to do simple stuff first.
kay__ has quit [Remote host closed the connection]