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
<Qrntz> thelema_, ndbm is another thing
<Qrntz> I can find remains of some bdb libraries but none seem to be finished/actual/have a distribution package whatsoever
<wmeyer> right, i am off for today.. see you tomorrow.
tufisi has quit [Ping timeout: 244 seconds]
ulfdoz has quit [Ping timeout: 244 seconds]
ulfdoz has joined #ocaml
<phao> Hi... I have these 2 different ways to write this insert function
<phao> I prefer the first one, but is there any usually preferred one?
<_habnabit> phao, the first one but with a | on the first case and a space before all of your (s
<phao> that first | looks strange =(
<_habnabit> i think it looks _more_ strange without it
<_habnabit> makes it more obvious that's part of the match
<phao> yeah
<phao> it does make
oriba has quit [Quit: oriba]
<phao> _habnabit, sad is that, sometimes, it leads to non exhaustive matches
<phao> at least, as seen by the compiler
<phao> like this http://pastie.org/4035133
<phao> I could ignore the ocaml warning and leave off the last case, but I don't wanna do that.
<phao> or... I could ommit the first case =D (how didn't I see that?)
ftrvxmtrx has quit [Quit: Leaving]
<thelema_> phao: what I usually do is comment out the last "where" - it's still there, but the compiler is able to figure out exhaustiveness
<phao> you comment that line, and the compiler doesn't complain?
<thelema_> | Node (e, _, r) (* when x > e *) -> mem x r
<thelema_> The compiler assumes that when clauses always evaluate false
<phao> so the compiler "reads" comments?
<thelema_> no, the comment is for the user.
<phao> I think I got what you meant
<thelema_> because you already have x=e and x<e, the only remaining possibility is x>e
<thelema_> so the test is redundant and can be removed
<phao> yeah, that when x > e is as useful as when true in that case
<thelema_> allowing the compiler to guarantee matching without a _ case
<phao> or as nothing
<thelema_> exactly.
<phao> so you could just comment it out
emmanuelux has quit [Read error: No route to host]
emmanuelux has joined #ocaml
ftrvxmtrx has joined #ocaml
manu3000 has joined #ocaml
phao_ has joined #ocaml
phao has quit [Disconnected by services]
phao_ has left #ocaml []
wagle_ has joined #ocaml
phao has joined #ocaml
wagle has quit [Remote host closed the connection]
wmeyer` has joined #ocaml
wagle_ is now known as wagle
wmeyer has quit [Ping timeout: 260 seconds]
phao_ has joined #ocaml
phao has quit [Disconnected by services]
phao_ has left #ocaml []
phao has joined #ocaml
emmanuelux has quit [Remote host closed the connection]
manu3000 has quit [Quit: manu3000]
Xizor has joined #ocaml
<flux> seems pretty cool, although I doubt I have use for it :-) http://moca.inria.fr/eng.htm
pango is now known as pangoafk
Submarine has quit [Ping timeout: 245 seconds]
mika1 has joined #ocaml
silver has joined #ocaml
osa1 has quit [Ping timeout: 245 seconds]
mika1 has quit [Read error: Connection reset by peer]
mika1 has joined #ocaml
cago has joined #ocaml
mika1 has quit [Read error: Connection reset by peer]
mika1 has joined #ocaml
djcoin has joined #ocaml
Sablier has joined #ocaml
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
andreypopp has joined #ocaml
kaustuv has quit [Ping timeout: 240 seconds]
mika1 has quit [Ping timeout: 240 seconds]
Yoric has joined #ocaml
mika1 has joined #ocaml
cago has quit [Quit: Leaving.]
mika1 has quit [Ping timeout: 250 seconds]
ankit9 has joined #ocaml
Obfuscate has quit [Ping timeout: 272 seconds]
tmaedaZ has quit [Ping timeout: 250 seconds]
milosn has quit [Ping timeout: 256 seconds]
SanderM has joined #ocaml
tmaedaZ has joined #ocaml
Snark has joined #ocaml
Hussaind has joined #ocaml
Hussaind has left #ocaml []
milosn has joined #ocaml
tufisi has joined #ocaml
letrec has joined #ocaml
benozol has joined #ocaml
ulfdoz_ has joined #ocaml
ulfdoz has quit [Ping timeout: 252 seconds]
ulfdoz_ is now known as ulfdoz
ulfdoz_ has joined #ocaml
ulfdoz has quit [Ping timeout: 244 seconds]
ulfdoz_ has quit [Ping timeout: 244 seconds]
ulfdoz has joined #ocaml
fraggle_ has quit [Ping timeout: 248 seconds]
fraggle_ has joined #ocaml
ulfdoz_ has joined #ocaml
ulfdoz has quit [Ping timeout: 252 seconds]
ulfdoz_ is now known as ulfdoz
avsm has joined #ocaml
<adrien> that's a long release anouncement
_andre has joined #ocaml
Obfuscate has joined #ocaml
Yoric has quit [Ping timeout: 264 seconds]
Yoric has joined #ocaml
cago has joined #ocaml
rossberg has quit [Remote host closed the connection]
rossberg has joined #ocaml
<phao> are high the performance penalties of functional programming due to lots of copies that happen?
<phao> copying*
<Hodapp> copying of what?
<phao> the value usually
<phao> not copyign actually, but the construction of a new value from an old one, which is done instead of assignment, even if most of the value (most of its parts, when it has parts that you can deal with separatedly) is re-usable
<phao> you could do record.field receives 3 with assignment, but in something more functional, you'd generate a new record, having the field's value "updated" to be 3
<phao> it's almost copying sometimes, if your data structure is big, and you wanna update only one field of it
lin has joined #ocaml
<lin> hi all, what am I supposed to handle the following situation
<flux> phao, often values are arranged in tree-like structure in functional languages
<lin> I have two modules, say a.ml and b.ml, and type a is defined in a.ml, type b is defined in b.ml
<flux> phao, because you don't modify existing values, you can easily rebuild a tree and only copy its spine; then the values you don't modify can simply refer to the old version
<phao> flux, what about the process of "copying the spine"
<flux> that's not to say there is no cost involved, but it's small and there are benefits
<phao> isn't that expensive?
<phao> hmm
<phao> are there benchmarks, trying to show how small the cost is?
<flux> maybe the language shootout is
<phao> I could do these, I think, but it's too much work hehe -- and I am really on the flow of the ocaml book I am reading
<flux> of course, you are able to use imperative approaches as well in ocaml
<lin> they are both record types
<phao> yes, I know that; this is more a question I am having again, now
<lin> In module A I want to refer to fields of type b, and in module B I want to refer to fields of type a
<phao> but I really had this doubt back when I was learning scheme (before I had set!) some years ago, and then again last year when checking out haskell
<flux> lin, x.A.fieldname, y.B.fieldname
<phao> but never got to look about it
<flux> phao, there's also another cost related to this that's probably bigger than the copying
<flux> because you create new values and let the old ones die, garbage collection takes some time
<phao> what is it?
<phao> hmm
<phao> got it
<flux> on the other hand typical functional language GCs handle short-lived values well
<flux> btw, as a reminder (related to 'long release announcement') here's a clikable changelog: http://caml.inria.fr/mantis/changelog_page.php
<lin> flux, but when I compile, it seems to report something like "Circular build detected"
<lin> since I refer to module A in module B, and vice versa
<flux> lin, oh, sorry, I didn't read fully and assumed you had the traditional problem :-)
<flux> lin, basically you need to move the dependency to another module that both A and B depend on
<lin> am i supposed to group type defs in a base file like type.ml?
<flux> or, you can introduce it in one file and use recursive modules
<flux> or you can perhaps use polymorphic types to go around it
<flux> but yes, types.ml is one approach I've used as well
<lin> Yeah, It takes me a while to figure this out , because in my daily work , I mainly do C programming
<lin> it's quite natural to include header files mutually
<flux> I had that issue when I started OCaml quite some time ago, but it seems to go away, perhaps by learning to subconciously use the workarounds ;-)
<flux> that's not to say a large project wouldn't bump into that issue, though
<flux> the basic solution is to "write smaller modules, write more independant modules"
<flux> typically that happens with polymorphicity and with the module system
<lin> hmm, good suggestion
<lin> i think i have a long way to go in the ocaml world
<flux> it makes great for reusability as well, easier to pull functionality out
<flux> for example MLDonkey is not a good example of that :(
<flux> I once tried pulling its torrent file handling out of it, and it was painful
<lin> so which project can be a good example?
<flux> good question. I haven't read that much other project's source code..
<lin> recently i am reading janestreet's async library
<lin> maybe i can find some light there
<flux> libraries are a slightly different breed of code than applications, though
<flux> but I have no doubts that's a good read
Ptival has quit [Read error: Connection reset by peer]
Ptival has joined #ocaml
smondet has joined #ocaml
kaustuv has joined #ocaml
<kaustuv> thelema_: did you make this package? http://oasis.ocamlcore.org/dev/view/ocamlgraph/latest
<kaustuv> If so, it seems to have the description from fileutils instead of from ocamlgraph
eni has joined #ocaml
<thelema_> kaustuv: probably; looks like I copied the fileutils _oasis file and forgot to change the description
<thelema_> kaustuv: you can upload an -oasis3 version that fixes it
<thelema_> or maybe I can do it easier
<kaustuv> Awesome! Thanks.
benozol has quit [Read error: Connection reset by peer]
benozol has joined #ocaml
kaustuv has left #ocaml []
<rixed> Is there a way to avoid the "Multiple definition of the module name OCAML__prof_Profiling" error when compiling a module which includes another one with ocamlcp?
<thelema_> rixed: odd, I've never gotten that error even when using include...
ankit9 has quit [Ping timeout: 252 seconds]
<lin> hi all
<lin> I have different types of workers to handle different kind of tasks. Now it seems I am trying to acheive two conflicting goals:
<lin> 1. I want to keep all workers in a hash table. This requires they have a unique type.
<lin> 2. Since different types of workers are for different tasks, their types can't be the same.
<lin> The reason I want to keep all workers in a hash table is because a worker is used to hold a service conversation with a network peer,
<thelema_> lin: the common way to handle this is to expose only a run() function that's unit -> unit and have all the type specific stuff hiding inside
<lin> thus I need to pick out a specific worker according to a packet I receive from the socket.
<thelema_> of course this can be adapted to your specific situation
<thelema_> but clearly you can't have a hashtable of functions of different parameters and expect to request a specific function and pass it the right value
<lin> oh thanks, let me think about it
<lin> it sounds reasonable, but one problem: there seems to be no way to hold intermediate states for every worker
<thelema_> lin: make your workers as closures, with some mutable state hidden inside them
<thelema_> let worker () = let my_state = ref ... in fun () -> ...; ()
<lin> ok, let me think about it
lin has quit [Quit: Leaving]
eni has quit [Remote host closed the connection]
lin has joined #ocaml
<mehdid> thelema_: is the first "()" needed?
<mehdid> (in "let worker () = …")
<thelema_> mehdid: if you want to make multiple workers with independent my_state cells
<mehdid> ah, fair enough
<thelema_> if you just want one worker, then yes, drop the ()
<thelema_> I guess that should be "let make_worker () = ..."
Obfuscate has quit [Ping timeout: 260 seconds]
<mehdid> indeed, avoids ambiguity
lin has quit [Quit: Leaving]
lin has joined #ocaml
<phao> mfp, that ocaml book you recommemd me is really great
<phao> I am finishing chapter 6 here -- cool exercises, and I liked the explanations
<djcoin> phao: which one are you reading ?
<phao> Introduction to Objective Calm
<phao> Jason Hickey
<mfp> AFAIK Hickey's book (draft) is (still) widely considered the best introduction
<mfp> great expectations for this one as a follow-up > http://realworldocaml.org/
<phao> there is that 700pgs one, published by o'reilly
<phao> seems kinds of more "practical" in the sense that it covers more libraries
<phao> haha "real world"
<phao> (have to be careful to comment on this -- better stay quiet)
<phao> looks cool mfp
cago has quit [Quit: Leaving.]
silver has quit [Remote host closed the connection]
Sablier has quit [Read error: Connection reset by peer]
emmanuelux has joined #ocaml
djcoin has quit [Quit: WeeChat 0.3.2]
Submarine has quit [Ping timeout: 248 seconds]
oriba has joined #ocaml
ulfdoz has quit [Ping timeout: 252 seconds]
oriba has quit [Client Quit]
Yoric has quit [Ping timeout: 250 seconds]
andreypopp has quit [Quit: Computer has gone to sleep.]
csmrfx has joined #ocaml
<csmrfx> So, I've never done anything 'real' with ocaml yet.
<csmrfx> But I thought that building a web spider would be cool
<csmrfx> Is there a scraping/http lib or something like that?
<tchell> csmrfx: ocamlnet's http client is great
<tchell> I started with http://projects.camlcity.org/projects/dl/ocamlnet-2.2.9/doc/html-main/Http_client.Convenience.html and have not needed anything more sophisticated so far.
avsm has quit [Quit: Leaving.]
<csmrfx> that sounds very nice, thank you
<csmrfx> What would you use for configuration files? yaml/json or similar easy-for-non-programmers supported by some lib?
<tchell> I think there is a json library but I haven't used it.
<tchell> I use XML, but only because I'm already doing a lot of XML parsing.
<tchell> PXP is a great library, but I think it would be somewhat involved for configuration files unless you have some other reason to figure it out.
<tchell> I think there are also a few s-expression parser/unparsers.
<csmrfx> ok, xml parser
<tchell> most of the stuff on this list http://godi.camlcity.org/godi/packages.html is mature, good software.
<Qrntz> I recall there was a library specifically meant for parsing config files
<Qrntz> not really sophisticated though, mostly of the «name = value» kind
<csmrfx> formats are good, ime
thomasga has joined #ocaml
<Qrntz> oh yes
thomasga has quit [Client Quit]
phao has quit [Ping timeout: 252 seconds]
letrec has quit [Ping timeout: 244 seconds]
<csmrfx> Is there something like cpan or gems that I can start using now?
Sablier has joined #ocaml
eni has joined #ocaml
<thelema_> csmrfx: best so far is oasis-db with odb
<lin> csmrfx: take a look at ocaml-keyfile, a simple library I wrote to parse key value file.
<csmrfx> cool
avsm has joined #ocaml
<thelema_> lin: is there a reason you haven't uploaded a release of keyfile to oasis-db?
<lin> because some small TODOs are on my list, and it's also not fully tested
<f[x]> anybody used flag(tests) from new oasis?
<f[x]> want to see a working _oasis example with this feature
<avsm> so, are you guys all submitting talks to oud.ocaml.org ? Deadline is Friday!
<lin> thelema_: I will do that asap
<csmrfx> whats the ?nnn ~mmm mean in a let?
<thelema_> lin: great
<thelema_> csmrfx: ?foo is an optional argument, ~foo is a labeled argument
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
<csmrfx> hey how do I get history in ocaml repl?
<jonafan> alias oc='rlwrap -r -c -D 2 ocaml'
<jonafan> in your .bashrc
<csmrfx> I see
Obfuscate has joined #ocaml
Anarchos has joined #ocaml
<csmrfx> Whats it mean whan an application is total?
<csmrfx> as in "if an application is total, labels may be omitted. In practice, most applications are total,"
<thelema_> csmrfx: all arguments are given
<thelema_> for example `let f ~x ~y = x + y`
<thelema_> `f 2 3` is a total application, `f 2` is a partial application
<csmrfx> 8)
<thelema_> `f ~x:2` is the proper way to do a partial application (or `f ~y:2`, if you meant y)
<thelema_> `f ~x:2 ~y:3` is the "best" way to do a total application, but `f 2 3` is accepted.
<rwmjones> does anyone know what's in a block tagged with Closure_tag?
<rwmjones> first field seems to be a code pointer
<thelema_> oh, the layout of closures? not sure
* rwmjones has found a block tagged with Closure_tag and size == 20971523 bytes
<rwmjones> definitely memory corruption going on somewhere
<rwmjones> I'm just wondering how big it's supposed to be ..
<thelema_> heh. probably not correct. :)
<rwmjones> I think the high 32 bits of the header word are corrupt
<rwmjones> so the real size is 3
<thelema_> #define Code_val(val) (((code_t *) (val)) [0]) /* Also an l-value. */
<flux> hmm.. does parmap handle the situation of a parmap running parmap properly?
<thelema_> code_t is just an int32*
<csmrfx> is commuting same as the re-ordering of the parameters to definition order?
<thelema_> csmrfx: commuting is just reordering parameters
<flux> I suppose it doesn't. but it's probably still useful.
<csmrfx> does commuting matter unless there are nonlabeled variables?
<csmrfx> uh, parameters
<thelema_> csmrfx: yes, there's rules on when labeled parameters can commute and when they can't.
<rwmjones> gaaa no hardware breakpoints on ppc64, so I can't even trap whatever writes to the header
<csmrfx> so how do I figure out if a parameter is given or not?
<thelema_> csmrfx: can you give an example?
<csmrfx> is there a type check or is it just a booleanish truthy or falsy?
<csmrfx> let to_buffer ?(keep_comments=true) buff group_name t =
<thelema_> ocaml does a complete type check on parameters.
<thelema_> once you've given `buff`, then keep_comments will have a value
<csmrfx> what if: let to_buffer ?keep_comments buff group_name t =
benozol has quit [Quit: Konversation terminated!]
<thelema_> csmrfx: same, except keep_comments might be None or Some x
ulfdoz has joined #ocaml
<csmrfx> how to? let ?huh =\n if huh then huh else false;;
<thelema_> if "\n" then "\n" else false ???
<csmrfx> Oh, made a typo
<thelema_> let f ?huh = match huh with None -> false | Some x -> x
<csmrfx> exactly!
<csmrfx> where does that match live?
<csmrfx> nevermind, found it in expressions
<thelema_> csmrfx: match is a bit of heaven, and it's tough to go back to languages missing it
<csmrfx> is that | evaled in match?
<thelema_> | is a match separator
<csmrfx> no wonder!
<thelema_> match [|] <patt1> -> expr1 | <patt2> -> expr2 ...
<thelema_> usually written
<thelema_> match expression with
jaar has joined #ocaml
<thelema_> | foo -> fooexpr
eni has quit [Ping timeout: 252 seconds]
<thelema_> | bar -> barexpr
<csmrfx> Where does Some live?
<thelema_> anyway, back in a bit
<thelema_> Some is in pervasives, or maybe even before that
<csmrfx> thanks for help, thelema_
<pippijn> probably Pervasives
<thelema_> pippijn: actually, outside pervasives even.
<pippijn> oh, it's not
<thelema_> with list.
<pippijn> it's a built-in type
<thelema_> biab
jaar has quit []
<csmrfx> Possible to have unlabeled optional parameters?
jaar has joined #ocaml
<pippijn> how would you call that?
<csmrfx> I dont even know how to call labeled optional params properly! 8D
lin has quit [Remote host closed the connection]
jaar has quit [Ping timeout: 245 seconds]
<wmeyer`> pippijn: burs seems to be the right choice - i've already started to think how to describe this - Lambda RTL seems to be choice - but undocumented. I have my own ideas though
avsm has quit [Quit: Leaving.]
pangoafk is now known as pango
Tobu has joined #ocaml
Tobu has quit [Changing host]
Tobu has joined #ocaml
<csmrfx> How do I make this accept any type: let foo ?huh = match huh with None -> false | Some x -> x
<thelema_> csmrfx: can't - the return type has to be bool because one branch of the match returns bool
<flux> csmrfx, think what the function type would be in that case
avsm has joined #ocaml
<flux> csmrfx, best make two functions.
<mrvn> or use an exception
<csmrfx> but, I read that a ?param has the optional type None x option = None | Some of x ... or something like that
Kakadu has joined #ocaml
<thelema_> csmrfx: yes, the problem is the `-> false`, which makes the output type have to be bool
<thelema_> csmrfx: and because of `Some x -> x`, the input type must be `bool option`
<Kakadu> http://paste.in.ua/4329/raw/ It is oasis's bug or mine?
<thelema_> Kakadu: I think yours, why don't you have a srcore.mllib?
<thelema_> or a list of modules for ... hmm, you do have one.
<Kakadu> thelema_: I expect that it should be generated...
<thelema_> it should be... maybe you need another plugin
<csmrfx> hmmkay
<Kakadu> thelema_: after 'mkdir core' everything works
<Kakadu> I think it is a bug
<thelema_> Kakadu: you didn't have a core/types.ml file?
<Kakadu> no
<thelema_> then why "Path core"?
<Kakadu> The sources will be there
<csmrfx> ok one more thing on the parameters: does () denote no param?
<thelema_> csmrfx: () denotes the unit value. It's used for functions that take no other param
<mrvn> csmrfx: no, () is a unit
<flux> csmrfx, for example this works: let foo a () b () c = a + b + c
<flux> csmrfx, but a function must haev at least one parameter, and if it really only doesn't need any, () is a nice value to use
<csmrfx> so... are functions 'called' in OCaml?
<thelema_> yes
<csmrfx> or is 'applying' the word?
<thelema_> apply is better
<mrvn> yes
<Anarchos> csmrfx i think both can be used
<Anarchos> csmrfx apply is more standard in lambda calculus
<mrvn> let foo a b = ... foo 1 does not call foo, it only applies the first arg.
<mrvn> but that is basically just nitpicking
<csmrfx> so how to get empty function? ~ let foo () {}
<mrvn> csmrfx: fun () -> ()
<thelema_> csmrfx: let foo () = ()
<thelema_> csmrfx: but since functions are values, there's nothing really special about "empty function"
<mrvn> and it isn't realy empty, it takes a unit and returns a unit
<thelema_> mrvn: yes, it's just the least that can be done in a function; no information in, no information out, no side effects
Tobu has quit [Remote host closed the connection]
<csmrfx> yes, I was wondering is that really a unit -functino
<csmrfx> *function
<mrvn> csmrfx: it is, you can pass it to a function that expects 'a -> 'a
<csmrfx> 8P
<mrvn> which is also why ocaml can't optimize it into something that takes no arguments and returns nothing.
<csmrfx> so there's fun, too
Tobu has joined #ocaml
<mrvn> ocaml has, is and makes fun
<mrvn> ocaml programmer have more fun than any other
<pippijn> it's a fact
<csmrfx> like the shirt that says "lisp has de fun"
<pippijn> scheme took de fun out of lisp
<Hodapp> csmrfx: bahahahahah
<bitbckt> *rimshot*
<Qrntz> scheme took out de fun, but now it's about fine
<csmrfx> or maybe it was "lispers have"
<csmrfx> "ocamlers have MORE fun" =
Nahra has joined #ocaml
<mrvn> type 'a t = Fun of ('a -> 'a);; Fun (fun () -> ());;
<mrvn> A unit of fun
<bitbckt> One (1) International Fun Unit.
<Qrntz> let rec fun' = (fun () -> ()) :: fun' ;;
<Qrntz> an endless amount of fun!
<mrvn> Qrntz: fun y
<csmrfx> thats crazy man!
sgnb has quit [Read error: Connection reset by peer]
<jonafan> does that recursive value thing have any actual use
<bitbckt> it produces fun. what more do you want?
sgnb has joined #ocaml
<jonafan> it's really just the same fun which tends to get boring
<mrvn> List.iter (fun _ -> print_string "fun\n") fun';;
hnrgrgr has joined #ocaml
<csmrfx> is that just fun or are those funs objects?
<mrvn> they aren't objects
<Qrntz> also, showing haskell fans you can have infinite series in eagerly evaluated languages just for fun!
<jonafan> yeah...but it only works in special circumstances
<Qrntz> something like «List.iter (fun fun'' -> fun'' ()) fun'» will work, but, obviously enough, will never terminate
<Qrntz> so, yes, mostly just for fun
<csmrfx> I wonder if these are correct so far http://koti.kapsi.fi/~csmr/anon_coward.html
cdidd has quit [Remote host closed the connection]
<jonafan> there should be a bot that detects people asking about history in the repl because i paste that every few days
<thelema_> csmrfx: match is an expression that is like a case/switch statement in other languages, but more powerful, as each branch uses a pattern to test the structure of the input expression and bind identifiers to parts of that structure.
<thelema_> csmrfx: also, partial application is normally done on the first parameter(s)
<mrvn> csmrfx: unit is the only value used for "no (more) arguments"
<mrvn> And total/partial application is a tricky thing. A function can be fully applied but still return a function.
<mrvn> or in other words partial application can do computations too
<mrvn> or a function might not even know it returns a function because it is polymorphic.
johnnowak has joined #ocaml
andreypopp has joined #ocaml
<tchell> csmrfx: I like the post
sgnb has quit [Read error: Connection reset by peer]
<csmrfx> So I am not mistaken in that partial applied f is a 'new' function? "another" function?
<csmrfx> tchell: 8)
sgnb has joined #ocaml
<thelema_> csmrfx: a function of type `int -> int -> int` can be thought of as taking two integer parameters and returning an integer
<thelema_> it can also be thought of as `int -> (int -> int)`, meaning that it takes one integer parameter and returns a function that takes another integer parameter and returns an int
<thelema_> this is the basis for partial application
<tchell> csmrfx: see also http://en.wikipedia.org/wiki/Currying
<Drakken> If a function returns a function, "fully applied" doesn't really say anything meaningful.
<csmrfx> I kind of think I know what partial application is, never got what is so big about it
<Drakken> because you can make functions easily. like ((+) 1) is an incrementor.
<Drakken> thelema's second answer is better if you really want to understand currying.
sgnb has quit [Read error: Connection reset by peer]
<csmrfx> BTW I hope you dont mind me quoting you
<Drakken> every function takes one argument. If it looks like it takes more arguments, that just means the function returns a function, which returns another function, etc.
<csmrfx> If you want, just msg and I can remove nick or quote even
<csmrfx> It's just notes for myself for later, though
sgnb has joined #ocaml
<thelema_> even though functions take one argument, the compiler does keep track of "arity" or the number of arguments to a function, for optimization purposes, i.e. so that all those intermediate functions don't have to actually be created
johnnowak has left #ocaml []
<thelema_> also, a single argument can be a tuple (1,2,'x') of multiple values together. The compiler tries to optimize this as well so that the tuples aren't actually created every time the function is called.
<csmrfx> Drakken lambda?
bobry has quit [Remote host closed the connection]
lopex has quit [Read error: Connection reset by peer]
joewilliams has quit [Remote host closed the connection]
<Drakken> what about it?
IbnFirnas has quit [Remote host closed the connection]
<csmrfx> what you described, "the function returns a function, which returns another function, etc"
IbnFirnas has joined #ocaml
<Drakken> fun/lambda is a macro/syntax.
<Drakken> it creates a function at compile time.
joewilliams has joined #ocaml
<Drakken> partial evaluation returns a function at run time.
<Drakken> so (( * ) 2) is a function that doubles numbers.
<Drakken> and (List.map (( * ) 2)) is a function that doubles all the elements in a list.
<csmrfx> doesn't return a ref to compiled function?
<Drakken> almost everything is a reference/pointer in ML and Lisp languages.
<Drakken> you don't have to worry about pointers or references.
Sablier_ has joined #ocaml
<csmrfx> true and thats why I want to use ocaml
<csmrfx> was wondering rather superficially
<thelema_> OCaml has things called "ref": 'a ref, which is a mutable value of type 'a.
<csmrfx> anyway, there it lies: http://koti.kapsi.fi/csmr/ocamlfiaq.html
<Drakken> ref is a specific datatype.
<Drakken> It's a record that contains one field, which is mutable.j
<csmrfx> yes, should have used the term "memory address pointer" or something
<Drakken> a ref is more than just a pointer.
<Drakken> It's a record.
<thelema_> csmrfx: nice. I ish we had the ocaml-tutorial wiki up still instead of just this read-only mirror of it (which may be of use, csmrfx) http://mirror.ocamlcore.org/ocaml-tutorial.org/
<csmrfx> yes, I was referring to the post-compile-time function decomposition
<csmrfx> hm, decomposition is not a good word, either
<csmrfx> but I ramble
Sablier has quit [Ping timeout: 245 seconds]
mfp has quit [Ping timeout: 245 seconds]
<Drakken> It's too bad refs aren't called "vars". Lots of people would like that better :)
<Hodapp> It's interesting how sometimes I have to look to see if I'm in #scala or #ocaml. I guess it means I'll have an easy transition back...
avsm has quit [Quit: Leaving.]
lopex has joined #ocaml
_andre has quit [Quit: leaving]
mfp has joined #ocaml
everyonemines has joined #ocaml
Nahra has quit [Quit: leaving]
BiDOrD has joined #ocaml
BiDOrD_ has quit [Ping timeout: 252 seconds]
fraggle_ has quit [Ping timeout: 260 seconds]
Kakadu has quit [Quit: Konversation terminated!]
fasta has quit [Quit: Quit]
fasta has joined #ocaml
fasta has quit [Client Quit]
fasta has joined #ocaml
manu3000 has joined #ocaml
fraggle_ has joined #ocaml
Xizor has quit [Ping timeout: 260 seconds]
bobry has joined #ocaml
eni has joined #ocaml
eni has quit [Ping timeout: 246 seconds]
Snark has quit [Quit: Quitte]
Sablier_ has quit [Quit: Quitte]
avsm has joined #ocaml
tonyg has quit [Quit: leaving]
avsm has quit [Client Quit]
SanderM has quit [Remote host closed the connection]
<manu3000> hello, any easy way to generate PDF with OCaml ?
dsheets has quit [Quit: Leaving.]
ftrvxmtrx has quit [Ping timeout: 265 seconds]
dsheets has joined #ocaml
<manu3000> Drakken: I should have mentioned that I need a non-commercial solution
<Drakken> manu3000 I don't see anything else. It would normally be here:
ftrvxmtrx has joined #ocaml
<manu3000> Drakken: thanks, I did look at Caml Hump, but could not find anything obvious. That's why I'm asking here :)
smondet has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
<Anarchos> manu3000 what is the source ?
<manu3000> Anarchos: in memory data
<Anarchos> manu3000 i mean generate PDF from what ?
<thelema_> manu3000: camlpdf is bsd licensed
<manu3000> thelema_: Ithanks, I missed that
Anarchos has quit [Quit: Vision[0.9.7-H-090423]: i've been blurred!]