rwmjones 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!)
<palomer> variant types are wicked cool!
<palomer> classes + variant types == a replacement for datatypes and records
<ikatz> does having mutually recursive modules in ml imply that you can write self-recursive modules?
<palomer> you already have self recursive modules
<palomer> module rec ...
<ikatz> hmmm... its been a while since i looked at this
Anarchos has quit ["Vision[0.8.5-0418]: i've been blurred!"]
Demitar has quit [Read error: 110 (Connection timed out)]
<palomer> ok, this is the reason I need classes and inheritance: I have a tree and I want my user to be able to move around the tree, so I have a pointer to the current node
<palomer> what type will the pointer have? superclass ref
<palomer> wait, I could also use variants
* palomer ponders this
<palomer> this sounds like a good idea!
<palomer> this completely changes the design of my app
hkBst has quit ["Konversation terminated!"]
<ikatz> palomer: you may want to look up the "zipper" data structure
<palomer> that's exactly what I need!
Demitar has joined #ocaml
|Catch22| has quit []
ita has quit [Remote closed the connection]
<ikatz> palomer: do you work much with recursive modules?
nuncanada has joined #ocaml
Morphous is now known as Amorphous
mwc has joined #ocaml
thelema has joined #ocaml
johnnowak has joined #ocaml
TimeMage has joined #ocaml
Jedai has quit [Read error: 110 (Connection timed out)]
Jedai has joined #ocaml
TimeMage has quit ["."]
szell` has joined #ocaml
szell has quit [Read error: 110 (Connection timed out)]
eelte has quit ["bye ca veut dire tchao en anglais"]
adu has joined #ocaml
<adu> what is the proper capitalization of OCaml/Ocaml?
<thelema> adu: OCaml
<adu> ok, thanks :)
thelema has quit ["My damn controlling terminal disappeared!"]
thelema has joined #ocaml
<johnnowak> perhaps the title could be more self-consistent ... this is a pressing issue, i'm sure of it!
AxleLonghorn has joined #ocaml
thelema is now known as thelema|away
mbishop 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!)
netx has joined #ocaml
AxleLonghorn has quit ["Leaving."]
brooksbp has joined #ocaml
thelema|away has quit [Read error: 110 (Connection timed out)]
brooksbp has left #ocaml []
mwc has quit ["Leaving"]
johnnowak has quit []
SniX__ has joined #ocaml
adu has quit [Remote closed the connection]
<bluestorm> palomer: if you have some seeable code someday, i'd be interested in it
<bluestorm> it seems me that you use every "most complicated feature" available, so the real application must be worth seeing :p
goalieca has quit [Remote closed the connection]
<bluestorm> (additionally, i'd be very happy to try a simple-minded version of that code if it's not big enough, but i really can't know if it can be done (you *might* be right about the need of classes and polymorphic variants after all) until i see it)
ygrek has joined #ocaml
wy has quit [Read error: 110 (Connection timed out)]
wy has joined #ocaml
Snark has joined #ocaml
Linktim has joined #ocaml
thermoplyae has quit ["daddy's in space"]
l_a_m has joined #ocaml
Linktim has quit [Read error: 110 (Connection timed out)]
wy has quit ["Leaving"]
Linktim has joined #ocaml
Linktim_ has joined #ocaml
Linktim has quit [Read error: 110 (Connection timed out)]
Linktim- has joined #ocaml
Linktim_ has quit [Read error: 110 (Connection timed out)]
kotarak has joined #ocaml
Linktim_ has joined #ocaml
Linktim- has quit [Read error: 110 (Connection timed out)]
Linktim- has joined #ocaml
Linktim_ has quit [Read error: 110 (Connection timed out)]
Linktim- has quit [Read error: 110 (Connection timed out)]
hkBst has joined #ocaml
coucou747 has joined #ocaml
<pippijn> does ocaml have implicit conversion of derived to base?
<mfp> pippijn: there's no implicit subsumption, you'll need an explicit (foo :> upperclass)
<pippijn> right
<pippijn> is there a way to make a function "uc" for "upcast" that automatically does this?
<mfp> this is typically done with let uc x = (x :> upperclass) instead of (foo :> upperclass) everywhere
<mfp> you get uc : #upperclass -> upperclass and you're using row polymorphism instead of subsumption
<pippijn> ah, good
Yoric[DT] has joined #ocaml
thelema has joined #ocaml
Linktim- has joined #ocaml
Linktim- has quit [Read error: 110 (Connection timed out)]
TimeMage has joined #ocaml
mfp has quit [Read error: 104 (Connection reset by peer)]
Mr_Awesome has quit [Read error: 110 (Connection timed out)]
jeremiah has quit [Read error: 104 (Connection reset by peer)]
mfp has joined #ocaml
jeremiah has joined #ocaml
ita has joined #ocaml
ita has left #ocaml []
smimou has quit [Read error: 110 (Connection timed out)]
Linktim- has joined #ocaml
thelema has quit [Read error: 104 (Connection reset by peer)]
Linktim- has quit [Read error: 110 (Connection timed out)]
<fremo> ...how to convert a double in binary in a string to a ocaml float ?...
<bluestorm> you may need the FFI
<fremo> of course, I didn't think about this...
<bluestorm> hm
<bluestorm> it seems the Obj module can do that as pure ocaml
<fremo> Got it ! Int64.float_of_bits
<fremo> Obj ?
<bluestorm> hm
<fremo> I dont know it...
<bluestorm> seems Int64 can do the job, and it's probably simpler
<bluestorm> it's funny, i'd never had looked for a float_of_bits there
<fremo> heh, me neither, I found that in extlib
<bluestorm> (Obj is a black-magic module that allows one to mess with OCaml internal value representation, provoking wonders and segfaults)
<fremo> :)
<flux> I think there is a library to do that
<flux> maybe ExtLib, maybe some other..
<flux> for parsing binary strings as floats, and the reverse
flithm has joined #ocaml
<flithm> hey everyone... I'm curious, are there any ocaml dialects that allow for SMP and incremental GC? (aside from F#)?
smimou has joined #ocaml
<bluestorm> flithm: and aside from forking
<bluestorm> JoCaml must provide what you're looking for
<flithm> bluestorm: cool thanks, reading about it now.
jlouis has joined #ocaml
Linktim- has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
bluestorm_ has joined #ocaml
bluestorm has quit [Read error: 104 (Connection reset by peer)]
nuncanada has quit ["Leaving"]
Linktim- has quit [Read error: 110 (Connection timed out)]
jlouis_ has joined #ocaml
thelema has joined #ocaml
kotarak has quit [":qa!"]
flithm has left #ocaml []
jlouis has quit [Read error: 110 (Connection timed out)]
AxleLonghorn has joined #ocaml
jlouis has joined #ocaml
AxleLonghorn has left #ocaml []
jlouis_ has quit [Read error: 110 (Connection timed out)]
filp has joined #ocaml
filp has quit [Read error: 104 (Connection reset by peer)]
johnnowak has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
pango has quit [Remote closed the connection]
pango has joined #ocaml
Morphous has joined #ocaml
Smerdyakov has joined #ocaml
<palomer> hmm
<palomer> how do I start the ocaml interpreter?
<thelema> # ocaml
<palomer> righto!
<flux> "ocaml". however, if you want (and I believe you do want) a line editor, "rlwrap ocaml" or "ledit ocaml"; you will need rlwrap or ledit installed, they don't come with ocaml
<palomer> what's a line editor?
<flux> move cursor left/right, command line history, etc..
<palomer> does ocaml have any support for infinite types?
<palomer> I'd like to right type nodeWrapper = <parent : <toNodeWrapper : nodeWrapper> >
<palomer> but instead I have to write
<palomer> type nodeWrapper = NodeWrapper of <parent : <toNodeWrapper : unit -> nodeWrapper> >
<Smerdyakov> And it's not a good idea to call 'ocaml' an interpreter. It interprets compiled bytecode programs, but not source programs, which is what people usually mean when they write "interpreter."
<Smerdyakov> "toplevel" is the idiomatic OCaml term.
<thelema> palomer: what do you want nodewrapper to do?
<bluestorm_> Smerdyakov: on the other hand, "interpreted languages" are now a quite wide class, including (at least according to most people) eg. Python, wich is actually bytecode-compiled
jeremiah has quit [Read error: 104 (Connection reset by peer)]
Amorphous has quit [Read error: 110 (Connection timed out)]
<bluestorm_> but i agree that "toplevel" is a much more precise term
<palomer> actually, it should be
<palomer> type nodeWrapper = NodeWrapper of <parent : <toNodeWrapper : unit -> nodeWrapper> > ref
<Smerdyakov> Objects? You dirty bastard.
<palomer> thelema, it stores the current node
<palomer> Smerdyakov, I'm using the object as a fancy record
<thelema> palomer: type nodeWrapper = node ref
<Smerdyakov> Dude, just use SML instead. ;)
<palomer> thelema, a node is something which has a parent, a child, a left sibling and a right sibling
<palomer> type nodeWrapper = NodeWrapper of <parent : <toNodeWrapper : unit -> nodeWrapper>; leftSibling : <toNodeWrapper : unit -> nodeWrapper>; rightSibling ... > ref
AxleLonghorn has joined #ocaml
<thelema> type node = { mutable parent : node; mutable child: node; mutable left_sibling : node; mutable right_sibling: node; }
<palomer> whoa, that's possible?
<palomer> that's wicked!
<palomer> wait, that's a record!
<thelema> yup.
<palomer> but I want objects
<palomer> I want to be able to do things like : getAllRightSiblings n = n#getRightSibling () : n#getRightSibling ()#getRightSibling ...
<thelema> type 'a node = <links : node_links; data : 'a> and node_links = {mutable parent: node; mutable child: node; ...}
SniX_ has joined #ocaml
<palomer> cool
<palomer> that works!
Linktim has joined #ocaml
<palomer> type node = < parent : <to_node_wrapper : node > ref ; .. > <--what about this?
<thelema> the ..?
<thelema> to_node_wrapper?
<palomer> type node = < parent : <to_node_wrapper : node ref > ; child : <to_node_wrapper : node ref> ; .. >
<thelema> you seem stuck on objects.
<thelema> might as well return a [node], not a [node ref].
<palomer> there's a reason
<palomer> getRightSibling might not return a node
<thelema> then you want node option
<palomer> but it WILL return something that can be transformed into a node
<thelema> or exceptions.
<palomer> type node = < get_right_sibling : <to_node : () -> node ref > ; .. > ...
<palomer> easter brunch!
<palomer> we must continue this later
<palomer> !
AxleLonghorn has left #ocaml []
jeremiah has joined #ocaml
johnnowak has quit []
SniX__ has quit [Read error: 110 (Connection timed out)]
schme has joined #ocaml
Linktim has quit [Read error: 110 (Connection timed out)]
Linktim has joined #ocaml
schme has quit [Read error: 104 (Connection reset by peer)]
schme has joined #ocaml
Linktim has quit [Read error: 110 (Connection timed out)]
Linktim has joined #ocaml
comglz has joined #ocaml
|Catch22| has joined #ocaml
comglz has quit ["Lost terminal"]
Linktim_ has joined #ocaml
bongy has joined #ocaml
Linktim- has joined #ocaml
mwc has joined #ocaml
Linktim has quit [Read error: 110 (Connection timed out)]
Linktim_ has quit [Read error: 110 (Connection timed out)]
Linktim- has quit [Read error: 110 (Connection timed out)]
szell has joined #ocaml
middayc has joined #ocaml
<middayc> oj
xbebe has joined #ocaml
xbebe has left #ocaml []
* palomer loves ocaml
bongy has quit [Read error: 113 (No route to host)]
szell` has quit [Read error: 110 (Connection timed out)]
goalieca has joined #ocaml
<palomer> type node_wrapper = <get_parent: <to_node_wrapper: unit -> node_wrapper option ref>; get_child: <to_node_wrapper: unit -> node_wrapper option ref>; get_sibling : <to_node_wrapper : unit -> node_wrapper option ref> > (* this type definition seems cyclical, no? *)\
<thelema> type nwor = unit -> node_wrapper option and type node_wrapper = <get_parent : nwor; get_child: nwor; get_sibling: nwor>
<thelema> I don't know why you want to return refs. And I don't know why you want to have an object with a method #to_node_wrapper
<thelema> maybe it should be [type unwo = unit -> node_wrapper option]
<thelema> both seem like useless levels of indirection
<palomer> lemme write up two classes which exemplify what I'm trying to get done
<thelema> you could do type nwor = <to_node_wrapper : node_wrapper option>, but why not use a function - this "object" will only do one thing.
<palomer> http://pastebin.com/m2a9c97f8 <--this is a rough idea of what I want to do
<palomer> so I have function definitions and expressions
<palomer> function definitions have function definitions as siblings
<palomer> and expressions have expressions as siblings
<palomer> they will, however, have a common interface (a common list of functions)
<palomer> like show_node, is_selected, remove_node, ...
<palomer> expressions can have function definitions OR expressions as parent node
<palomer> what bother sme about my type definition is that it's cyclical!
<thelema> why does functionDefinition need ref options?
<palomer> you're right
<palomer> err
<thelema> palomer: the type of a binary tree in ocaml is: type 'a tree = Empty | Node of 'a tree * 'a * 'a tree
<thelema> does this make sense?
<palomer> yeah
<palomer> the trees going to be moving around and stuff
<palomer> nodes will be deleted
<palomer> I've used functional trees (in haskell)
<palomer> but I'm staying away from them
<mwc> palomer, nice to see you again
<thelema> palomer: why don't you like functional trees?
<palomer> mwc, nice to be back
<palomer> thelema, I'm thinking it'll be hard to delete nodes and move nodes around
<palomer> mwc, this ocaml stuff is neat
<mwc> well, I think a zipper could help you with deletion and simple moves
<thelema> do you have the source for the builtin Set module?
<mwc> but there's seek overhead
<palomer> mwc, as in get_parent and get_child ?
<mwc> uhm, sort of
<palomer> and get_right_sibling
<mwc> a zipper implies a decomposition of a data structure
<palomer> I looked into the zipper a little
<thelema> Unless your tree has hundreds of thousands of nodes, I don't expect a zipper to help much in insertion/deletion
<ikatz> just a quick question on the topic of "ref None"...
<mwc> ikatz, ...?
<ikatz> i have a module with a function that depends on data read from standard in
<thelema> ikatz: just ask
<ikatz> thelema: yeah, didn't want to interrupt, you guys were discussing something more interesting :)
<ikatz> currently i'm using a "ref None" to store the input data
<ikatz> so the first time i call the module function that needs it, i check the reference and read the input data if necessary
<ikatz> is that a crappy way to do things?
<mwc> hmmmm. seems sort of C-like
<thelema> doesn't seem that bad to me. I've done the same before.
<ikatz> ok cool
<palomer> hrmph, I'll keep working on it and ill get back to you guys
<thelema> You might use a lazy instead, if you just want to delay the computation until the first call
<ikatz> i dont think that's what i want... my control flow is to read the input data, use it to create the function, then use that module in a functor
<thelema> ref None it is, then.
<mwc> How do you mean, create the function?
<ikatz> thanks... if you know of any best practices for ocaml, or style guides, i'd love to read them
<mwc> It seems to me that you might want a higher order function instead
<ikatz> mwc: i'm reading in a STRIPS-style planning domain, so i "create" the initial state and successor function depending on what objects and actions are read in
<mwc> let fooizer = configure_foo_with_data () in
<mwc> and then fooizer is your successor function
<ikatz> that's basically what i'm doing
<ikatz> it just seemed like bad practice to have a module that read from standard in instead of reading the data somewhere else and passing it in
<ikatz> thanks for your reassurance :)
<mwc> Yeah, so the closure version would be to parse the text once, create a value representing a parameterization of your successor function, and then to make your successor function take both one of those parameterizations and a state. You just return a partial application of that function to the particular parameter set from your configuration-parsing functoin
<ikatz> mwc: will that work for a function inside a module?
<mwc> sure, you can pass a closure out of a module
<mwc> or rather, a function in a module can return a closure
<ikatz> what's a closure, as opposed to a function?
<mwc> a closure is what you get by doing a partial application
<ikatz> oh ok
<thelema> ikatz: as far as ocaml is concerned, no important difference
<mwc> I'm pretty sure there's no way to distinguish the two in ocaml, except by doing some black magic in the run time system.
<thelema> ikatz: all functions in ocaml enclose any relevant data, thanks to "what I want" scoping
<ikatz> closure = currying
<thelema> ikatz: sure.
<mwc> pretty much, it's the function's "code" with any free data it needs to be able to compute
<ikatz> thats sort of what i wanted to do when i was writing this module
Mr_Awesome has joined #ocaml
<ikatz> but i couldn't figure out how to create a (struct * input_data) -> struct
<mwc> so if you had type f = a -> b -> c;; and type g = b -> c;; then if I take some ff of type f, some aa of type a, then (ff aa) is of type g.
<mwc> ikatz, you want input_data -> struct -> struct
<mwc> generic_successor : input_data -> struct -> struct
ygrek has quit [Remote closed the connection]
<mwc> particular_successor = generic_successor my_data
<ikatz> hmm.... i seemed to have trouble getting a function to return a module earlier
<mwc> modules are static, you can't return them
<thelema> mwc: only functors can return modules.
<ikatz> right... so, how would i accomplish input_data -> struct -> struct ?
<mwc> and functors are "executed" once, at compilation
<mwc> well, you can't return a struct.
<mwc> by which I think you mean module?
<thelema> ikatz: why do you need to return a whole module?
<mwc> ikatz, out of curiosity, are you coming from an SML background?
<ikatz> either or :) if i understand the terminology correctly, a module is a named struct?
<ikatz> i learned SML first, a few years ago
<mwc> yeah, I figured from the struct usage and the (a * b) -> c function typing
<mwc> generally in Caml, avoid that type, write it out fully curried a -> b -> c
<ikatz> i usually do... although i heard somewhere that ocaml is optimized for tuple-ized arguments
<ikatz> but getting back to what you said earlier,
<ikatz> is there a way to partially apply one of the functions in a struct and get a new struct?
<mwc> actually, there's no speed advantage to either form, in the former case, ocaml actually automatically *untuples* the function
<mwc> no, not at run time
<mwc> does it need to be a struct?
<mwc> can you not return a (successor,init) pair?
<mwc> the module system is static, evaluated entirely at compilation.
<ikatz> it needs to be in a struct ... i have a functor that takes a problem domain and returns a search environment
schme has quit ["bfirc sucks."]
<mwc> hmmm.
<mwc> stick with what you have now
<thelema> I think you can evaluate your functor with a pre-written module that refers to the created function.
<mwc> it sounds like you're abusing the module system a bit
<ikatz> in what way? again, i know very little about best practices in this language
<thelema> let particular_successor = ref None in
<ikatz> mwc: what makes you say that i'm abusing the module system?
<thelema> module Searching = let successor args = match !particular_successor with None -> assert false | Some f -> f args
<thelema> end
<thelema> that's a bit ugly... A bit of Obj.magic can get rid of the match, as long as you're *extra, extra sure* that the value will get filled before usage.
<flux> Obj.magic really gets too much publicity around here ;)
<mwc> ikatz, sorry, was afk. The module system is static, so it's used for compile-time structural design
<flux> you can get "rid of the match" with let unopt = function None -> failwith "argh" | Some x -> x
<palomer> http://pastebin.com/m4c84aeaa <--I claim that this should typecheck
<palomer> oh wait, forgot an option
<palomer> whoa
<palomer> type node_wrapper = <get_right_sibling: unit -> node_wrapper option> <--this looks like an infinite type!
<Smerdyakov> Please stop writing "infinite type." Its your own private terminology that doesn't mean anything to anyone else.
<palomer> sorry
<palomer> Smerdyakov, your comments are quite stinging sometimes
<palomer> no offense or anything
<Smerdyakov> palomer, your general way of communicating aggravates me. So we're even. :-)
<mwc> flux, hehe, there was a post to the effect of: "the semantics of obj.magic are as follows: Obj.magic does not exist. Don't use it."
<palomer> anyways, I meant a cyclic type
<Smerdyakov> palomer, what makes lists not qualify as a cyclic type family?
<palomer> or a type which can be expanded ad infinitum
<mwc> binary trees. lists.
<palomer> Smerdyakov, there's a constructor in lists, trees
<mwc> perfectly well defined
<Smerdyakov> palomer, so is there for records and objects. There is a special syntactic form for writing out a record or object.
<palomer> I'm treating the <> in < foo: bar ; ...> like any other type constructor
<palomer> type foo = foo list <--doesn't pass
<palomer> type foo = < bar : foo> passes
<Smerdyakov> I suggest learning about the type theory to which these apparently disparate OCaml constructs is usually compiled for formal study. In particular, look at "recursive types." There it's clear that your characterization of "infinite types" is faulty.
<Smerdyakov> List types already permit infinite unfolding.
nuncanada has joined #ocaml
<ikatz> thelema: your example worked, thanks!
<ikatz> i think i found the source of my confusion too, so let me see if i have this right
<ikatz> modules can't be defined within a "let" block
<ikatz> but they can be defined on the top level and refer to other things defined on the top level
<ikatz> ?
<Smerdyakov> ikatz, no, there is an OCaml extension that allows local module definitions.
<Smerdyakov> ikatz, modulo that weirdness, if you know SML, there should be no confusion.
<Smerdyakov> ikatz, the SML and OCaml module systems are almost identical. Just different surface syntax.
<palomer> sml allows recursive record types?
<Smerdyakov> No.
<Smerdyakov> All type recursion goes through 'datatype' in SML.
<palomer> ditto in haskell
<palomer> that's why I'm surprised
<Smerdyakov> palomer, maybe you should read the manual instead of guessing, eh? :P
<ikatz> aaah! that goes for me as well!
<ikatz> local modules were exactly what i was looking for
<palomer> :P
<ikatz> although i'm surprised that they are defined "let module ..."
<mwc> Smerdyakov, eh? How many canadians are there in this channel
* palomer raises his hand
<Smerdyakov> mwc, "eh" is a very useful little word.
<palomer> before I forget: happy easter everyone!
<mwc> Smerdyakov, sure it is. And as far as I know, it's only used by canadians.
<Smerdyakov> mwc, no, it's very common among programmers of all nationalities online.
<thelema> mwc: people from northern US states use 'eh' as well.
<ikatz> we used a bastardized version of "huh" in northern NH
<mwc> thelema, really
<mwc> I knew some americans used huh similarly
<thelema> mwc: yes, really. Minnesotans, especially
<mwc> Ah yeah, but Minnesota is pretty much the 11th province anyways
<Yoric[DT]> Canadian expansionism ?
<Yoric[DT]> ...
<ikatz> my "huh" doesn't really go well in typed conversations... you'd have to spell it "auh"
<Yoric[DT]> Smells like Canadian Bacon :)
* Yoric[DT] should watch that movie again, some day.
<ikatz> "not too bad, auh?"
<ikatz> what types of programs do you guys write with ocaml?
<mwc> I used to write all my course code in caml or haskell
<mwc> I wrote an entire FEM system in haskell last year :)
<ikatz> FEM?
<palomer> ikatz, I'm writing a structure editor
<mwc> but lately I'm afraid NUMPY has been way to useful
<Smerdyakov> ikatz, often that question implies that the asker things that OCaml is limited in scope or impractical or something. Do you have that innuendo, or should we take the question literally? :-)
<ikatz> please take it literally
<mwc> ikatz, finite element method, it's a numerical method for boundary-value problems.
<palomer> mwc, linear programming?
<mwc> nope, not quite my field
<ikatz> most of the ocaml i've seen has been for AI or for compilers
<mwc> I do feedback control, it's optimal control guys who get into the optimization stuff
<palomer> what's NUMPY?
<ikatz> i was curious if anyone uses it for graphics, networking apps, or robotics
<mwc> ikatz, functional languages of the ML family (and I include Haskell) have a sweet spot for manipulating abstract tree-like structures
<mwc> compilers, AI, and symbolics fit nicely there
<mwc> palomer, numpy.scipy.org
<mwc> most of the functionality of matlab without the pain and suffering of matlab.
<palomer> fast matrix multiplication/decomposition?
<mwc> yeah
<mwc> at the very basic level
<mwc> but that's OT
<mwc> I would have used Ocaml+GSL for the work this term, but the GSL didn't have all the functionality I needed
<palomer> GSL?
<mwc> when I was an undergrad, I would have implemented it, no time now.
<mwc> Gnu Scientific Library
<ikatz> does anyone have experience with graphics or GUI programming in ocaml?
<Smerdyakov> I have experience with GUI programming in OCaml.
<thelema> ikatz: I've a GTK project in ocaml.
<ikatz> Smerdyakov: what library did you use, and how did you find it?
<ikatz> find it = like it
<Smerdyakov> I wrote a wrapper on top of Lablgtk. I find Lablgtk unusable by itself. Unfortunately, the library I started is only available internally at Jane Street now.
<ikatz> you work at jane st?
<palomer> Smerdyakov, you worked at jane street?
<palomer> I applied for a job there, and they turned me down. I think it's because I didn't know anything about ocaml:P
<ikatz> i'm glad i'm not the only one who thought lablgtk sucked
<thelema> ikatz: lablgtk doesn't have an easy learning curve
<palomer> is it worse than any other binding?
* thelema hasn't used any other gui bindings in ocaml
<flux> too bad apparently the functional reactive gui bindings haven't quite been developed further
<ikatz> are there any tools for graphically creating a GUI?
<flux> ikatz, with gtk you can use glade
<ikatz> hmmm... i will check that out
<palomer> I mean bindings in other languages
<flux> glade is supported
<Smerdyakov> palomer, I work at Jane street.
<palomer> cool!
<palomer> Smerdyakov, how is it?
<ikatz> yes, i'm a little envious too... although that's based on the fact that they're the only ocaml-based employer i know if
<ikatz> "know of"
<palomer> http://ocaml.pastebin.com/m13df3c2d <--does this type check?
<palomer> errr
<Smerdyakov> palomer, great place for an ML hacker. It's not academic research, but if you want more standard development but with real programming languages, then I don't think any other opportunities on the planet beat Jane Street.
<palomer> shouldn't it typecheck
<palomer> Smerdyakov, and the work environment, coworkers, etc...?
<Smerdyakov> palomer, A+. (My boss is in the channel, but I mean it. ;-)
<thelema> palomer: you need some ..'s
<palomer> ahh
<thelema> and you can probably get away with not specifying the type of None
<ikatz> does jane st. have any programming puzzles as part of the application process?
<Smerdyakov> ikatz, sure.
<palomer> http://ocaml.pastebin.com/m5f374521 <---another problem! (and this one I don't even understand the error message, where is 'a ?)
<palomer> when I applied there weren't any puzzles
<ikatz> i'm always interested in those because it helps me judge my skill level
<palomer> when they interviewed me they asked me one puzzle
<palomer> find a function unit -> unit which returns something different every time
<palomer> coming from haskell, it stumped me
<thelema> palomer: good error message. Got me where 'a came from.
<ikatz> you could just return the current time ?
<palomer> or just create a reference and increment it
<thelema> palomer: unit -> unit doesn't return anything.
<Smerdyakov> palomer, are you sure you got that question right?
<palomer> err
<palomer> unit -> int
<palomer> it was a long time ago!
<ikatz> Smerdyakov: do they have puzzles online like facebook or itasoftware?
<Smerdyakov> ikatz, we have hardly anything online. The OCaml blog is new and is all there is beyond about 5 static pages.
<thelema> palomer: hmm, it seems you can't define an object type with ..
psnively has joined #ocaml
<Smerdyakov> ikatz, if you want a job as a programmer, it generally helps to complete impressive projects, rather than practice puzzles, BTW. :P
<palomer> I like the new Smerdyakov + emoticons!
<psnively> Although doing practice puzzles is a start.
<Smerdyakov> I've used emoticons extensively for 12 years. What else are you claiming has changed?
<palomer> hadn't noticed:P
<thelema> type 'a c'_class = 'a constraint 'a = < m : int; .. >;;
<Smerdyakov> OCaml type constraints are soooo dodgy.
<ikatz> i'm preparing for a career jump... but i'm not sure what the skill set is for the programmer i hope to become
<palomer> brown nosing is a safe bet
<Smerdyakov> ikatz, if you're not writing code, then you're not making any progress towards any skill set!
<palomer> thelema, that's the solution?
<thelema> Smerdyakov: agreed, but it seems that they're necessary to put .. into a class type.
<palomer> where did 'a pop into?
<ikatz> true... i'm trying to find out whether i've learned enough automata theory and graph theory to "make it"
<thelema> palomer: I think so... there's a bit of discussion about this in the ocaml manual, end of section 3.12
Snark has quit ["Ex-Chat"]
<Smerdyakov> ikatz, the specifics don't matter.
<Smerdyakov> ikatz, if you've learned enough that you can learn any theory you need quickly, then you're ready.
<ikatz> i feel fairly inadequate in those areas and always worry that the jobs i want will require a lot of them
<palomer> thelema, the name of the type is _class?
<Smerdyakov> ikatz, if not, then you're not ready to be a mathematician-programmer.... but most programmers aren't that.
<ikatz> thanks for that :)
<ikatz> actually, one pet projcet that i have is an sql-style interface to the filesystem
<thelema> palomer: no, the type is named c'_class
<palomer> thelema, is that a random name?
<ikatz> that has taken a backseat to grad school though
<Smerdyakov> ikatz, what kinda grad school?
<thelema> palomer: no, it means something in its context, but the name isn't important.
<ikatz> university of NH
<psnively> The hard part isn't acquiring the skills to blend theory and practice. The hard part is finding an employer who cares.
<Smerdyakov> ikatz, I meant subject and degree.
<ikatz> oh, MS CS
<Smerdyakov> ikatz, so you want to go into industry afterward?
<ikatz> yes, but i'm still trying to figure out what's out there for interesting jobs
<Smerdyakov> You could listen to Paul Graham and found a start-up.
<ikatz> i worked in QA during my undergrad and i'm trying to break from that
<psnively> For OCaml programmers, Jane Street or Galois, I would guess.
<Smerdyakov> psnively, Galois has only a small amount of OCaml going on, right?
<psnively> I don't have even second-hand knowledge, but that comports with my interpretation of what I've heard.
<Smerdyakov> I think Galois is mostly Haskellers.
<Smerdyakov> But, seriously, if you start your own company, you can use whatever you want.
<palomer> thelema, but now my type takes a type argument, what should that argument be?
<ikatz> that's true
<palomer> found a start-up using arc
<mwc> palomer, hahahah
<mwc> probably have the reddit experience
<mwc> I read somewhere once that "the only people to ever take paul graham seriously are now rewriting everything in python"
<Smerdyakov> Yeah, Lisp sucks. :-)
<Smerdyakov> But they should have picked Standard ML instead!
<palomer> shakespearelang!
Mr_Awesome has quit ["aunt jemima is the devil!"]
<thelema> palomer: 'a has to be whatever you've constrained it to be in the declaration.
<psnively> Python makes me appreciate Lisp. Lisp makes me appreciate ML. ML makes me appreciate Haskell.
<psnively> Haskell makes me appreciate Coq.
<mwc> I don't think there's anything missing from caml that standardml has except for its record system and the local ... in ... end construct
<palomer> thelema, this 'a variable is new, what does it represent? how do I use it? can't we just do away with it altogether?
<Smerdyakov> mwc, that's a strange statement. There are a whole lotta design decisions that the languages make differently.
<mwc> really?
<Smerdyakov> mwc, and there are huge differences in the language ecosystems. SML has a modern optimizing compiler, for instance.
<mwc> hmmm
<Smerdyakov> mwc, behold the viewing globe: http://adam.chlipala.net/mlcomp/
<psnively> Whole-program optimizing compiler...
<mwc> I thought the difference was more ecological: standardml has a mathematically-defined standard, ocaml is more of an evolving system
<psnively> Smeryakov's page on the two is quite good, IMHO.
<palomer> ocaml coders are represented by a construction worker
<thelema> palomer: why not create a class node_wrapper and inherit from it?
<psnively> Actually, there's at least one case where Smerdyakov feels (correctly, IMHO) that OCaml is more "pure" than SML.
<Smerdyakov> palomer, no. You've clearly not read the page if you said that.
<mwc> except for the object system, I was under the impression the two languages were isomorphic
<palomer> Smerdyakov, it was a joke! (albeit a lame one)
<Smerdyakov> palomer, jokes that don't even make sense do more harm than good.
<palomer> thelema, I would! but, for example, expression have expression siblings and function definitions have function definitions sibling
<psnively> palomer: I thought it was funny. :-)
<mwc> well, a lot of languages are isomorphic
<psnively> All of the Turing-complete ones, actually.
<palomer> even brainpluck
<mwc> "aside from the object system, the differences betweem SML and Caml are mostly cosmetic"
<palomer> psnively, I'm glad I have at least one fan:P
<Smerdyakov> I have to disagree. You haven't specified what you mean by "isomorphic," and your definition is useless in practice if it defines a universal relation.
<thelema> palomer: if the current code typechecked, it wouldn't give you different return types.
wy has joined #ocaml
<palomer> thelema, but it would, since both classes satisfy node_wrapper
<mwc> now, sml has equality types, ocaml has universal equality/comparison
<mwc> sml has overloaded arithmetic operators, ocaml has + and +.
<thelema> palomer: no, they'd both return a value of type node_wrapper
<Smerdyakov> mwc, are you just reading off the section headings from my comparison? :P
<psnively> Smerdyakov, but isn't that exactly the point of observing that most languages are Turing-equivalent? Not only that they can express the same things, but that they can--by definition--express anything computable?
<mwc> nope
<thelema> palomer: err, node_wrapper option
<mwc> just going off the top of my head
<Smerdyakov> psnively, I don't think that fact is usually relevant, and tends to distract more than it enlightens.
<mwc> but I did skim your article, so I think it might be influencing my thought
<palomer> but both expression and function_definition satisfy node_wrapper
<Smerdyakov> psnively, interesting for students in a theory of computation class; harmful to the community of working programmers. :)
<mwc> psnively, I'd agree with Smerdyakov. it tends to get you into the turing tarpit
<psnively> I agree with that. I was just riffing on the observation that "a lot of languages are isomorphic," and suggesting that that was the sense of "isomorphism" in this context.
<thelema> palomer: and? the return type is set at node_wrapper option, so that's what's returned. You'd have to up-cast to expression or function_definition to use their methods.
<Smerdyakov> My response is that we can't have started with a worthwhile definition of "isomorphic" in the first place.
<psnively> Oh, quite: I'm constantly telling people that the observation that assembly language and, e.g. OCaml are both Turing-complete isn't very helpful. :-)
<mwc> I probably should have said "nearly trivially isomorphic", but then of course, Smerdyakov would have picked over my definition of trivially :)
<psnively> And "isomorphic."
<psnively> It's a twofer!
<Smerdyakov> mwc, please give a definition that different people can actually be counted on to understand in the same way.
<mwc> Smerdyakov, I changed the statement to: "aside from the object system, the difference between SML and Ocaml are mostly cosmetic"
<psnively> Great. Now we all have to learn category theory. :-D
<Smerdyakov> mwc, OK. That's clearly wrong.
<Smerdyakov> mwc, or we have different definitions of "mostly."
<mwc> so what basic principles do they differ on?
<Smerdyakov> The OCaml manual section on "language extensions" alone should be enough to show you the differences.
<Smerdyakov> Do you mean to exclude those?
<mwc> Smerdyakov, to approximate what I mean by "mostly cosmetic," I'd say that Java and C# differ mostly cosmetic
<palomer> thelema, assume I have a virtual class node_wrapper_class, then calling get_right_sibling will return an element of node_wrapper_class, which will not have all the functionality of an expression. Now, assume we do it the current way, then get_right_sibling returns expression (in all its glory), which happens to also be a node_wrapper
<psnively> Sounds like "different definitions of 'mostly'" to me. :-)
<mwc> Smerdyakov, since I'm pretty sure I've never used an extension, I'll go with yes, I meant to exclude them :)
<palomer> mwc, there are some differences in the C# and java type systems
<palomer> java generics are slightly borked (at least, last time I tried they were)
<mwc> oh right, Java got generics.
<mwc> does C# have them?
<Smerdyakov> mwc, well, I just advise reading my page before making any further statements. Labeled and optional arguments and polymorphic variants are a pretty big addition in OCaml vs. SML, and by now they're not considered an extension.
<mwc> okay, I'll grant you polymorphic variants
<palomer> mwc, yeah, C# has them, but they're slightly different
<palomer> polymorphic variants rock!
<mwc> optional and labelled arguments are syntactic sugar
<Smerdyakov> mwc, I dare you to say that to Jacques Garrigue's face. I don't agree with you.
<palomer> garrigue doesn't seem like someone who gets easily offended
<palomer> he might just shrug and agree with you
<psnively> No, he isn't. But the point is that it took a fair amount of effort to get optional and labelled arguments to work.
* palomer is off!
<Smerdyakov> I don't think so. There is some fancy type system work behind this.
<mwc> pardon my ignorance, but how are optional arguments different than 'a option parameters
<mwc> I agree their non-trivially in their implementation and type semantics
<mwc> but in their actual usage
<mwc> how are they accomplishing anything that couldn't be done with plain old positional parameters?
l_a_m has quit [Remote closed the connection]
<Smerdyakov> You don't need to know all of a function's optional arguments to call it.
<mwc> hmmmm, let me think on that for a moment
<mwc> alright, I get it.
<mwc> so what about labeled arguments, what do they add beyond positional arguments. The only benefits I've noticed are self-documentation and freedom from remembering which argument goes where
<Smerdyakov> What do you mean by "positional arguments"?
<mwc> plain old arguments to a function: f a b c = ...
<Smerdyakov> Yeah, I agree with your summary of the benefits. The second one is not syntactic sugar; you can't implement it nicely with macros.
<mwc> alright
<mwc> so we have a slightly different definition of syntactic sugar then
<mwc> I assume desugaring occurs at the AST level, as opposed to the lexical.
<Ugarte> palomer: Java generics aren't true generics. It's boxing and unboxing from object.
<Smerdyakov> You can't do labeled arguments properly without types.
<mwc> yep
<mwc> so you'd need for type elaboration to take place on the AST before desugaring the labels
<mwc> or at least, to know a "canonical order" of the labelled arguments to rewrite them into positional arguments at each application site
<Smerdyakov> I don't think anyone else thinks of "syntactic sugar" as operating with the benefit of full type information.
<mwc> fair enough
<mwc> so it's a feature of the language
<palomer> Ugarte, that's a semantic difference, no?
<palomer> thelema, I got an email from martin suggesting I should cast to solve my problem
<palomer> which brings me back to the old way
<thelema> palomer: I realize now, you don't need that type. Objects are structurally typed.
<Ugarte> palomer: No treally. It matters.
<Ugarte> palomer: For example, if you use reflection, a generic list is really just a list of objects.
<Ugarte> In most cases, you won't see the difference, it's true.
<palomer> thelema, eh?
thelema is now known as thelema|away
<thelema|away> palomer: drop node_wrapper, and do (None : function_definition option)
<palomer> so I don't need the .. ?
<thelema|away> palomer: and (None: expression option)
<thelema|away> palomer: drop node_wrapper entirely
<mwc> Smerdyakov, thanks for the discussion
<thelema|away> you'd have to declare it if it were a record, but objects need no type declarations.
* thelema|away really goes away
<palomer> thelema|away, I need node_wrapper since I'm going to create val currentNode : node_wrapper ref
<palomer> which can be a function definition or expression or whatever
<palomer> (which, really, is the whole point of this exercise)
<thelema|away> try it without.
<palomer> really?
<palomer> okay
<palomer> but, erm, how could it possible work?
<palomer> I mean, the reference can contain many different things
<palomer> holy crap, it works
<palomer> actually, it doesn't
<palomer> actually, I can just cast it whenever I need to store it
Yoric[DT] has quit ["Ex-Chat"]
psnively has quit []