cjeris changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/
pango has quit [Remote closed the connection]
pango has joined #ocaml
_blackdog has quit [Read error: 104 (Connection reset by peer)]
mikeX has quit ["leaving"]
_blackdog has joined #ocaml
pango has quit [Remote closed the connection]
pango has joined #ocaml
hsfb has joined #ocaml
hsfb has left #ocaml []
<mshlimov> is there a switch/case in ocaml ?
<Smerdyakov> Now, be honest: have you read the first part of the tutorial? :P
<mshlimov> nope :)
<mshlimov> not recently at least
<mshlimov> will look now
<Smerdyakov> It would be a worthwhile investment.
<mrvn> Isn't that about the first thing you ever learn about ocaml?
<mshlimov> so i think i've used match in this way before
<mshlimov> sorry for the naive questions
<mrvn> A switch/case is the simplest use of match. :)
<mshlimov> without any unbound variables or _'s it operates like a switch/case ?
<mrvn> It always operates like siwtch/case. It just has far more powerfull case statements I would say.
<mshlimov> so for example
<mshlimov> match fname with
<mshlimov> | "free" ->
<mshlimov> would be legit?
<mshlimov> where fname is a string
<mrvn> hmm, ok. Not like switch/case.
<mrvn> match fname with x when x = "free" ->
<mshlimov> match fname with x when x = "free" -> (...) when x = "malloc" -> (...)
<mshlimov> just like that
<mshlimov> when instead of |
<mrvn> no, on top of it.
<mshlimov> match fname with x | when x = "free" -> (...) | when x = "malloc" -> (...)
<mshlimov> like that ?
<mrvn> But why don't you define type fname = Free | Malloc
<mrvn> ?
<mrvn> match fname with x when x = "free" -> (...) | x when x = "malloc" -> (...)
<Smerdyakov> mrvn, huh? String constants are patterns.
<mrvn> Are they? well, then never mind.
<mshlimov> so i can do | "free" ->
<mshlimov> like i asked earlier ?
<mrvn> yes
<mshlimov> the string constant can be any possible c function name
<mrvn> # let f x = match x with "free" -> x | _ -> x;;
<mshlimov> that's why i don't define types
<mrvn> val f : string -> string = <fun>
<mshlimov> rather -- the variable can contain any string -- it is user supplied
<mrvn> what you might need is this though: match fname with "free" -> ... | "malloc" -> ... | x when is_custom_function(x) -> ....
<mrvn> So you handle the known C function names specificaly and still cope with the self defined ones.
<mrvn> + | _ -> error
<mshlimov> but i need to handle several known C functions differently
<mshlimov> but what you wrote makes sense
screwt8 has quit [Read error: 104 (Connection reset by peer)]
_blackdog has quit [Remote closed the connection]
<mshlimov> without parens a | is associated with the inner most match, right .
<mshlimov> ?
screwt8 has joined #ocaml
<flux> mshlimov, how about (Hashtbl.find funcs fname) () ?
<Smerdyakov> mshlimov, yes.
<mshlimov> thanks Smerdyakov. flux: that's pretty elegant...
<mshlimov> an scalable... but in this case there's only 5 or so functions that i'm looking for, so i will just use a match. thought i do like your proposal, and shows some of the elegance of first order functions.
<mshlimov> or first class functions -- that's the proper terminology, isn't it
<Smerdyakov> Yes. "First-order" would generally be taken as a limitation, not an awesome feature. ;)
<mshlimov> sure in c you could use function pointers, but this is cleaner and more elegant
<mshlimov> i am working with someone elses ocaml code, and it's interesting how not understanding the features of the language results in very hard to read code :)
<mshlimov> maybe not interesting... but painful... :)
<mshlimov> i myself don't understand it so well, but i am using some of the functional constructs instead of writing code that looks like it's been converted from C.
<mshlimov> is it true that the nature of OCAML results in more polymorphism ?
<mshlimov> match makes it easy to write functions that operate on all kinds of types
<Smerdyakov> First, it's proper to capitalize as OCaml.
<mshlimov> :)
<Smerdyakov> Second, "polymorphism" is such an overloaded term that I don't know what you mean.
<mshlimov> Good point.
<mrvn> Actualy you can't write polymorphic functions at all. Only polymorphic types.
<mrvn> As in you can't write a function ( + ) that works for ints and floats.
<mshlimov> why not?
<mrvn> How would the type inference know what type you have?
<Smerdyakov> mrvn, that's not a very good answer. Even a fully-annotated program couldn't define such a function.
<mshlimov> couldn't you just match | Int -> | Float ->
<mrvn> Then you have a type foo = Int of int | Float of float
<mrvn> You couldn't do 1+1 and 1.+1.
<mshlimov> and compare them you mean ?
<mrvn> no, just add them
<mshlimov> you mean 1 + 1 would not equal 1.+1. ?
<mshlimov> why not ?
<mshlimov> just have different addition code for each type using match
<mrvn> Because + can only have type int -> int -> int or float -> float -> float but not both.
<Smerdyakov> All type information is erased at compile time in OCaml.
<mshlimov> oh right
<mshlimov> unless they were a subtype of number
<Smerdyakov> OCaml has no automatic subtype coercions.
<mshlimov> Smerdyakov: just like in java and c++ right ?
<Smerdyakov> No. Both have automatic coercions.
<mshlimov> by automatic you mean at run time ?
<mrvn> But c++ has polymorphic functions though.
<mrvn> and runtime types.
<Smerdyakov> No, like this
<Smerdyakov> Integer n = new Integer(7);
<Smerdyakov> Object o = n;
<Smerdyakov> No explicit (Object) was needed.
<Smerdyakov> OCaml has no such features.
<mrvn> Ocaml needs (>Object) there, right?
<mshlimov> so you just need to cast it explicitly -- there is no implicit type casting
<mshlimov> is what you're saying?
<mrvn> yes
<mshlimov> what's the difference between type casting and "coercion"
<mshlimov> coercion just strips stuff off / disregards part of the vtable, while casting may involve some kind of function to "convert" types ?
<Smerdyakov> I don't consider there to be any difference.
<mshlimov> | "malloc" -> | "xmalloc" -> (...)
<mshlimov> is this legit to do the same thing for two different values ?
<flux> it goes like | "malloc" | "xmalloc" -> ..
<mshlimov> flux: thanks.
<flux> the manual section describing the ocaml syntax and especially the pattern syntax can be enlightening; it was for me
<mshlimov> i need to read it, and i will
<mshlimov> but right now i'm trying to get the project done asap :)
<mshlimov> please let me know if you would like me to stop flooding the channel with annoying newbie questions and i will respect that.
<Smerdyakov> Well, don't expect help when you aren't willing to help yourself!
mshlimov is now known as tik
tik is now known as tik1
tik1 is now known as tikitik
<tikitik> uh oh
<tikitik> i think i swallowed 1cm of a plastic fork piece
<tikitik> is that harmful ?
<tikitik> can't be that harmful, or they prob wouldn't make forks like this..
<mrvn> If you start to bleed you will know.
<tikitik> # let il = [] in il <- [] @ il ;;
<tikitik> Unbound instance variable il
<tikitik> why is that ?
<Smerdyakov> Commencing silent treatment, as it is soooo clear you have spent about 5 seconds reading any introduction to OCaml. ;-)
<tikitik> :)
<tikitik> i have a feeling it's because only references can be modified and not variables
<tikitik> going to read.
screwt8 has quit [Read error: 104 (Connection reset by peer)]
skal has joined #ocaml
screwt8 has joined #ocaml
<mrvn> that is so wrong on so many levels.
<tikitik> variables can be mutable apparently
<tikitik> and references are different types with mutable records
<tikitik> correct ?
skal_ has joined #ocaml
<ulfdoz> jo
<mrvn> The tutorial explains that
<Nutssh> tikitik: bindings (eg, let, or function arguments) are always immutable. They may point or refer to mutable objects (strings, arrays, etc.)
<Nutssh> Try the tutorial.
<tikitik> reading ocaml-tutorial.org/ now
<tikitik> hmm... type inference is interesting...
skal has quit [Connection timed out]
<tikitik> good call... reading the tutorial is wonderful :)
pstickne has joined #ocaml
Smerdyakov has quit ["Leaving"]
pstickne has quit ["Leaving"]
<flux> hmm.. is defining let (@@) a b = a b and let (@@) a = a? (infact, external let (@@) : 'a -> 'a = "%identity")
smimou has joined #ocaml
jlouis has quit [Remote closed the connection]
<flux> missing term: "equal in practice"?
<flux> intended use: like the $-operator
Mr_Awesome has quit ["...and the Awesome level drops"]
smimou has quit [Remote closed the connection]
<flux> hmh, (static) web pages that lie about their modification time are annoying
* flux is looking at the progress of FrGui - not much to see there
<flux> fun thing: let p s = Printf.printf "%s\n%!" s let f = fun () -> p "f1"; fun () -> p "f2"; fun () -> p "f3" let _ = f (p "a1") (p "a2") (p "a3");;
<flux> one could perhaps expect a1 f1 a2 f2 a3 f3, but the output is a3 a2 a1 f1 f2 f3
<flux> it works more naturally with value bindings, of course
<flux> (let a = f (p "a1") in a (p "a2") ..)
Sparkles has joined #ocaml
Zzompp has joined #ocaml
tree_ is now known as tree
joshcryer has quit [Connection timed out]
Sparkles has quit [Read error: 110 (Connection timed out)]
malc_ has joined #ocaml
tikitik has quit [Read error: 110 (Connection timed out)]
ita|afk is now known as ita
_blackdog has joined #ocaml
Sparkles has joined #ocaml
ikaros has joined #ocaml
ikaros has quit ["segfault"]
mqtt has quit ["Quitte"]
ygrek has joined #ocaml
ygrek has quit [Remote closed the connection]
romanoffi has left #ocaml []
ygrek has joined #ocaml
ygrek_ has joined #ocaml
ygrek has quit [Remote closed the connection]
pango has quit [Remote closed the connection]
pedro_soc has joined #ocaml
jlouis has joined #ocaml
jlouis has quit [Remote closed the connection]
jlouis has joined #ocaml
FlavioG has joined #ocaml
pango has joined #ocaml
FlavioG has quit ["Kopete 0.12.3 : http://kopete.kde.org"]
Sparkles has quit []
cjeris has joined #ocaml
LeCamarade has joined #ocaml
<LeCamarade> I can't seem to link more than one .cmx into my compilation. And now I need unix.cma and another (custom-made). Comment?
<mrvn> not enough info
<LeCamarade> mrvn: Can you write out the correct version of this one:
<ita> LeCamarade: ???
<LeCamarade> ocamlc unix.cma mywon.cmx -o compd compd.ml
<LeCamarade> ita: There.
<mrvn> and the error?
Smerdyakov has joined #ocaml
<LeCamarade> mrvn: Don't know what to do with myown.cmx, and then the fat dump of the help.
<LeCamarade> mrvn: Don't know what to do with myown.cmx, and then the fat dump of the help.
<LeCamarade> That's is the error.
<mrvn> cmx is an native object file. Not a bytecode library.
<mrvn> You need a cmo or cma.
<mrvn> Or use the native compiler and unix.cmxa
<LeCamarade> mrvn: So, I should compile myown to a cma and then use it in that way?
* LeCamarade knoweth not how to compile a cma - he's only gone as far as cmx.
<flux> lecamarade, cmo and cma go together, cmx and cmxa go together. ones on the other group never go with ones in the other group.
<ita> ocamlopt unix.cmxa mywon.cmx -o compd comptd.ml
* LeCamarade feels this compilations stuff is the hardest bit about OCaml.
<ita> it is not that complicated
<LeCamarade> It worketh!
<ita> too bad ocamlc cannot figure out dependencies like mcs does
Demitar has joined #ocaml
<LeCamarade> So there is actually a difference between ocamlopt and ocamlc that really matters that much? Nobody said ...
<LeCamarade> ita: So it is safe to say I should always use ocamlopt?
<Smerdyakov> The manual sure says.
<mrvn> That is why there is an OCamlMakefile
<ita> LeCamarade: you read the manual upside down
<ita> LeCamarade: if you need speed use ocamlopt, else ocamlc
<mrvn> Some archs don't have native code but native code is somewhat faster.
ygrek_ has quit []
* LeCamarade is guilty of having prefered ocaml-tutorial to the manual. And he's not an old Camel Trader, anyway.
<mrvn> .oO( The tutorial is the manual )
<mrvn> I never read anything but the tutorial.
<mrvn> except the source.
<LeCamarade> ocaml-tutorial.org
<LeCamarade> That one.
<Smerdyakov> LeCamarade, and you're also too lame to read BitchX.doc.
<Smerdyakov> Man, whatever happened to that message. It used to say "to lame."
malc__ has joined #ocaml
<LeCamarade> Smerdyakov: Is that one of the things BitchX says? Funny sign-off messages.
<Smerdyakov> LeCamarade, no, it's the value in your realname field.
<mrvn> All you need to learn ocaml.
<LeCamarade> :oO
* ita suggests ocaml+twt to LeCamarade to prevent hair loss
bluestorm_ has joined #ocaml
LeCamarade has quit [SendQ exceeded]
LeCamarade has joined #ocaml
malc_ has quit [Read error: 110 (Connection timed out)]
romanoffi has joined #ocaml
mikeX has joined #ocaml
smimou has joined #ocaml
<ita> cool, a library for graphs and graph colouring
<ita> ocamlgraph
<ita> looks neat
ygrek has joined #ocaml
smimou has quit [Remote closed the connection]
smimou has joined #ocaml
pango has quit [Remote closed the connection]
pango has joined #ocaml
desertbot has joined #ocaml
<LeCamarade> Camel Traders. I am working on a minimalist bot for our channel. It is logged in, right now. As desertbot. If you feel the name sucks, come up with something. :oD
<LeCamarade> desertbot: Hi, desertbot.
<LeCamarade> desertbot: You are inspired by (envy for) lambdabot of #haskell.
* LeCamarade thinks they will like the bot when it works ... :oD
desertbot has quit [Remote closed the connection]
malc__ has quit ["leaving"]
Submarine has joined #ocaml
benny99 has joined #ocaml
benny99 has left #ocaml []
ygrek has quit []
pango has quit [Remote closed the connection]
pango has joined #ocaml
postalchris has joined #ocaml
bluestorm_ has quit ["Konversation terminated!"]
benny_ has joined #ocaml
Submarine has quit ["Leaving"]
benny has quit [Read error: 145 (Connection timed out)]
romanoffi has quit [Remote closed the connection]
<hcarty> Does anyone here have some pointers on finding a special value (min, max, whatever) within an array of arbitrary dimensions?
<hcarty> Specifically I'm looking to find max and min values in a Bigarray .. so the program will know the dimensions at run time but not compile time
<hcarty> It's getting late and my head isn't wrapping around this problem very effectively.
mrvn has quit [Read error: 104 (Connection reset by peer)]
mrvn has joined #ocaml
<hcarty> I could reshape it to a 1D bigarray, but it's wrapped in a variant type so that could become very verbose
LeCamarade has quit [""Merde!""]
malc_ has joined #ocaml
LeCamarade has joined #ocaml
desertbot has joined #ocaml
<LeCamarade> @slap
<LeCamarade> I'm testing a bot. Will continue tomorrow. He'll be our OCaml bot.
desertbot has quit [Remote closed the connection]
desertbot has joined #ocaml
<LeCamarade> Does anyone have any cute names?
<LeCamarade> @
desertbot has quit [Remote closed the connection]
desertbot has joined #ocaml
<LeCamarade> To test the bot ... @
<LeCamarade> Hmm. Should respond to every line with @
<LeCamarade> @!
<LeCamarade> @
desertbot has quit [Remote closed the connection]
<mbishop> You should probably make a testing channel
desertbot has joined #ocaml
<LeCamarade> Yeah, I have moved to a testing channel. #testing. Sorry. One last thing ...
<LeCamarade> Didn't work. Merde. Gotta go home. See ya!
LeCamarade has quit [""Camels! They are everywhere!""]
desertbot has quit [Remote closed the connection]
<pango> hcarty: what's the question ? :)
dark_light has joined #ocaml
<pango> hcarty: unless you know properties about the values in your array, the only way I know to find min and max values is to scan the whole array, keeping smallest and biggest values as you go...
tikitik has joined #ocaml
<hcarty> pango: Sorry, yeah - I suppose that wasn't very clear :-) Just wondering about a recursive fold_left-like approach.
<pango> what's special with it ?
<hcarty> pango: The values will be ints or floats
<hcarty> I don't mind having separate functions for ints vs floats. I'm just trying to work out the logic and it's more than my brain wants to tackle this evening it seems.
<pango> if they can be floats, in OCaml nothing will beat (performance wise) a very imperative implementation with for loops
<pango> one should check to be sure, but I don't think OCaml can keep floats unboxed across function calls
<malc_> pango: it can't
<hcarty> malc_: pango: Both, thanks
<hcarty> The function I'm using at the moment is http://rafb.net/p/34pVbG67.html
m3ga has joined #ocaml
m3ga has quit [Read error: 131 (Connection reset by peer)]
_JusSx_ has joined #ocaml
<pango> hcarty: I guess Hdf.get checks the constructor of its first argument ? That must kill performance
<pango> worse than using functors ;)
<pango> (have you considered using them instead ?=
<hcarty> pango: I have, but to be honest they're still a bit opaque to me
<hcarty> I wouldn't mind using them, but I'm not sure how I would since the data type isn't known until it's read from disk
<hcarty> This is all for and related to the HDF library, which is a library for reading/writing large binary files.
<hcarty> Satellite data sets in my case
<malc_> hcarty: one day redefinition of @ will bite you
postalchris has quit [Read error: 110 (Connection timed out)]
<hcarty> That match ... command in the paste shows the file types that are currently usable.
<malc_> then again, i wouldn't morn the loss.. after all people who use "Pasted as C++" deserve it
<hcarty> malc_: Yes :-) That's just a temporary placeholder. I used it, then realized that it's already defined elsewhere.
dark_light has quit [Operation timed out]
<hcarty> Drop-down menu selections are overrated
dark_light has joined #ocaml
<hcarty> Thanks for the elitism over a silly mistake though
<malc_> That aint no elitism, that's arrogance
<hcarty> Now that I can respect!
<hcarty> I do appreciate the tips. I'm still quite new to OCaml.
* mbishop wonders when his book will arrive
<pango> hcarty: the use of functors won't make your sum type go away
<mrvn> hcarty: Bigarray has a function to ask for the number of dimension and so on and with that you can easily write an bigarray_fold
<mrvn> Since you don't knbow the data type you can't have it inside the function. Instead you pass it a function handling the type.
<malc_> hcarty: btw. i wonder why you need all this tagging (in light of Bigarray.X.kind)?
<mrvn> Like (fun acc x -> if x > acc then x else acc)
<hcarty> malc_: My plan is to make it possible to have a generic data reading function which picks the appropriate type depending on which field is read from the file
<hcarty> I may be missing something, but I haven't found a way to make that generic without the method I'm using
pango is now known as pangoafk
<mrvn> hcarty: Doesn't the calling side know the type?
<malc_> hcarty: erm.. you interrogate your original array with Bigarray.Genarray.kind and use that afterwards
<hcarty> malc_: mrvn: The type may not be known until run-time
<malc_> i fail to see how you can have an array inside an ADT without knowing it
<hcarty> For example, one current use is aggregation of a few data sets. A section of every data entry in each HDF file is pulled and written to a new tile.
<mrvn> hcarty: What is the problem with the code you pasted?
<mrvn> the let new_a?
<hcarty> mrvn: Nothing. I was just looking for some ideas on a possibly better way of implementing it.
<hcarty> mrvn: let new_a = ... is just to reshape the Bigarray to 1D from nD.
<mrvn> hcarty: The Hdf.Int8 (or whatever) has to match the Bigarray kind. Isn't that stored in the Bigarray?
<mrvn> In C you would use Bigarray_val(v)->flags & BIGARRAY_KIND_MASK kind of array elements
<hcarty> mrvn: It is. But the bigarray has to be created at some point.
<hcarty> mrvn: Can that be checked in OCaml then? How would I represent that in the interface?
<hcarty> The HDF C library tells me (via some integer constant) what type the data has. I use that to allocate a Bigarray of the proper type and size.
<mrvn> hcarty: Then passing the Bigarray on should be enough. No need for the Hdf type anymore.
<mrvn> Bigarray.Genarray.kind should give you the type.
<mrvn> I hate that there is no fold for arrays predefined.
pangoafk is now known as pango
<hcarty> mrvn: Would I have to allocate the Bigarray in the C-portion of the library to do this?
<mrvn> hcarty: That is what I would do. How else would you pass the values to ocaml?
<mrvn> Why do you need the find to have a generic 'f' by the way? Doesn't the caller know what type it searches? You have to know for the test_val anyway.
<hcarty> This has been put together piece by piece and in quite a rush up to this point, so I was passing a string ("INT8", "FLOAT32", etc) back to OCaml and then matching that to a Bigarray type
<mrvn> hcarty: and the contents of the bigarray?
<hcarty> mrvn: re: f - I used that so I could pass in min or max for this case
<hcarty> mrvn: re: contents - After creating the bigarray, I pass that back to C-land and then pass its data pointer to the appropriate HDF library function
<hcarty> It's a round-about way of doing things, but as I said it was done in a rush and while I was learning OCaml.
<mrvn> hcarty: Why not an find ('d -> 'a -> 'd) -> 'd -> ('a, 'b, 'c) Bigarray.Genarray.t -> 'd?
<hcarty> I'm trying to clean it all up now and do things more cleanly and properly
<mrvn> So the function f has to match the array you pass.
<hcarty> mrvn: Nice, thanks. I'll give that a shot.
<mrvn> Or is the type truely random, like read from a file at runtime?
<hcarty> mrvn: It depends
<hcarty> I'd like to support both
<hcarty> If it has to be in separate interfaces then that's ok with me
_JusSx_ has quit ["leaving"]
<hcarty> But for some instances the type really won't be known until runtime
<hcarty> When the data is read from the file on dis
<hcarty> k
<mrvn> Then I guess you have to keep your Hdf.<type> around the genarray.
<hcarty> mrvn: That's what I thought. I struggled with this for a long while trying to find a prettier way.
postalchris has joined #ocaml
<mrvn> hcarty: Thet "match a with" is really ugly but I can't think of an ocaml way to do this without matching.
<mrvn> Obj.magic excluded.
<hcarty> mrvn: Yes, I don't like the constant matching over all of those types.
<mrvn> hcarty: Define a Hdf.apply : ('a Hdf.t -> 'b Hdf.t) -> 'a Hdf.t -> 'b Hdf.t
<mrvn> That one would have the match against various types. Then you can call "Hdf.apply reshare a"
<hcarty> mrvn: How would I apply the Hdf.t type for that? I can paste my current definition.
<mrvn> Define a 'Hdf.apply : ('a -> 'b) -> 'a Hdf.t -> 'b Hdf.t' I ment.
<hcarty> mrvn: Sorry, I meant define not apply
<mrvn> The apply would be the same as the "match a with" just with the function passed as argument instead fo reshape.
<mrvn> hcarty: looks ok
<mrvn> ugly but neccessary I guess
<mrvn> How does ocaml check the ('a, 'b) kind to be a valid combination?
<mrvn> What stops one from defining a (int, Bigarray.float32_elt, Bigarray.c_layout) Bigarray.Genarray.t?
<hcarty> mrvn: To my knowledge, nothing. But I haven't tried.
<hcarty> mrvn: Hdf.apply of that kind gives a type error. Unless I've misread something
<hcarty> mrvn: Hdf.apply of that kind gives a type error. Unless I've misread something
<hcarty> Oops, sorry
<hcarty> http://rafb.net/p/By84mZ84.html - the code + error
<hcarty> But oddly enough, if f is defined within apply then the problem goes away
<mrvn> let apply (f : ('a, 'b, 'c) Bigarray.Genarray.t -> ('d, 'e, 'f) Bigarray.Genarray.t) a = ...?
<hcarty> I get the same error
<postalchris> hcarty: I've bumped into this problem recently too. OCaml can't deal with parameterized types across a match like this. What is your version that works?
<hcarty> postalchris: I don't have a generic apply which works, sadly
<postalchris> This is really annoying. The solution I came up with (my type has far fewer constructors) is "apply (f1,f2,f3) a = match a with C1 x -> f1 x | C2 x -> f2 x"
<hcarty> postalchris: Here's a snippet of what I've used: http://rafb.net/p/shdgLa95.html
<postalchris> And so on... where the call becomes "apply (f,f,f) a)"
<hcarty> postalchris: Cool. I'll give that a shot. It would clean things up greatly, even if it it's not completely ideal
<postalchris> That was my judgment too. But looking at that code irks me!
<postalchris> My code, I mean, not yours.
<mrvn> I don't get it. Telling ocaml that f is a polymorphic function should let one use it on different arrays.
<postalchris> Yeah, in your examples, the way you define f in the let binding allows OCaml to infer a general type. Somehow, when a match is involved, OCaml want to make the type too specific to start with.
<mrvn> Even "let apply (f : 'a -> 'a) a =" should do.
<hcarty> mrvn: I don't understand it either. I've been struggling with it and finally gave in to lots of ugly matches
<mrvn> You have the matches.
<hcarty> postalchris: Thanks! Your apply works for my case as well. Not ideal, but better.
<mrvn> hcarty: can you add an "let apply f = apply (f,f,f,f,f,f,f,f,f)" below that?
<postalchris> mrvn: No!
<hcarty> mrvn: No, the inferred type is the same then
<hcarty> Across all f's
<hcarty> or, fs. Whatever is the proper plural there.
<mrvn> I know there is something in the manual about telling the type inference to not infere too much but I can't find it.
<hcarty> The last thing I heard about that was that you can only push the type inferencing to be more restrictive, not less. But I don't remember the source, so I don't know its accuracy.
smimou has quit [Remote closed the connection]
<postalchris> hcarty: I just sent this out to the caml-list. It seems we can all agree this behavior is too weird not to seek out an explanation.
<hcarty> postalchris: Thanks, I was thinking of doing the same
<pango> what's weird in there ?
<postalchris> pango to the rescue?
<mrvn> Worst case you have to write a C function for it. That would really suck.
<postalchris> mrvn: That is unthinkable.
<pango> I think you should put your algorithms in functorized modules parametrized with module(s) of the same type as Bigarray.Genarray, then instanciate it once for each specific type in your main match(es)
<pango> my functors are a bit rusty, but I think it's the way to go to avoid testing constructors all over the place
<mrvn> A functor will only work for compile time types.
<pango> there's only a finite set of types
<pango> 7 in the case of hcarty, if I count well
<mbishop> Anyone here read "Ocaml for Scientists"?
<pango> so 7 instanciations should do
<mrvn> pango: then you still have the matching and again the same problem.
<pango> mrvn: you need matching at entry point, obviously. That can't be avoided
<pango> still, you wouldn't need tests in functorized code
<hcarty> pango: Do you have any pointers to examples? Implementing functors has been a difficult hurdle for me.
<mrvn> pango: At best you move the problem upwards in the code. But you can't get it to accept a function "f" and apply it to whatever type it is.
<pango> mrvn: correct
<mrvn> So the question remains: How do you get the type inference to not infere the type so much?
<hcarty> pango: Is the idea behind the functor approach to keep the matches when you don't know the type at compile time, but be able to clean them up for cases where you do?
<pango> it's not type inference I think, it's static typing
<pango> hcarty: functors are function in the module space (= functions that take module(s) and return a module)
<mrvn> The type we want is 'a -> 'a for f but it inferes more.
<hcarty> I'm heading home for the day. Thank you all for your help and time!
<pango> hcarty: they're often used where templates would be used in some other languages (but they rely on polymorphism)
<hcarty> pango: I'll have to read that section of the manual 3 or 4 more times and toy with small example problems.
<mrvn> type t = Int of int | Float of float
<mrvn> let apply f a = match a with Int x -> Int (f x) | Float x -> Float (f x)
<pango> mrvn: that's not true, you want dependant types between the arguments of your apply function, and that's not supported in ML languages
<mrvn> Simplest example I can make.
<pango> well, even that is not very accurate
<mrvn> pango: why? apply : ('a -> 'a) -> t -> t
<mrvn> Perfect type for me.
<pango> since the "array" argument has a known type; it's rather a dependancy between the type of f and the constructor of the array...
<pango> mrvn: but you can't have any 'a for any 't
<mrvn> Right, it has to be every 'a.
<pango> a functor will help express those type dependancies
<mrvn> There should be a way to specify an any type. Saying the function must not care what type it is.
<mrvn> Like "let id x = x" does not care.
<pango> because it does nothing to its argument, just pass it around
<pango> the only counter example I know are comparison operators, but they're "magical"
<mrvn> neither does Bigarray.reshape (to the kind of array)
tikitik has quit ["BitchX-1.0c19 -- just do it."]
david_koontz has joined #ocaml
malc_ has quit ["leaving"]
skal_ has quit [Read error: 104 (Connection reset by peer)]