joewilliams has quit [Remote closed the connection]
<peper>
Error: This expression has type Vector.point2 * float -> unit -> unit but an expression was expected of type Vector.point2 * float -> unit
<peper>
any obvious mistakes?
<mrvn>
a -> unit to many
<peper>
yeah, i saw that. gtk api sometimes wants () at the end of function calls and sometimes not
Alpounet has quit [Read error: 113 (No route to host)]
<mrvn>
peper: I think those will be functions where all other args are optional.
yakischloba has quit ["Leaving."]
ikaros has joined #ocaml
_zack has joined #ocaml
fx___ has joined #ocaml
ygrek has joined #ocaml
kaustuv has joined #ocaml
ttamttam has joined #ocaml
dark has quit [Read error: 110 (Connection timed out)]
_unK has joined #ocaml
avsm has joined #ocaml
demitar has joined #ocaml
ygrek has quit [Remote closed the connection]
avsm has quit ["Leaving."]
thrasibule has joined #ocaml
WuJiang_ has quit [Read error: 60 (Operation timed out)]
Alpounet has joined #ocaml
WuJiang has joined #ocaml
mjsor has joined #ocaml
patronus has quit [Remote closed the connection]
Yoric has joined #ocaml
mjsor has quit []
Alpounet has quit [Read error: 113 (No route to host)]
munga has joined #ocaml
patronus has joined #ocaml
det__ has quit [Connection reset by peer]
itewsh has joined #ocaml
rwmjones_ has joined #ocaml
rwmjones_ has quit [Client Quit]
Alp has joined #ocaml
ygrek has joined #ocaml
Associat0r has quit []
avsm has joined #ocaml
_zack has quit ["Leaving."]
_zack has joined #ocaml
_unK has quit [Read error: 104 (Connection reset by peer)]
itewsh has quit ["There are only 10 kinds of people: those who understand binary and those who don't"]
_andre has joined #ocaml
maskd has joined #ocaml
tmaeda is now known as tmaedaZ
munga has quit [Read error: 113 (No route to host)]
valross has quit ["Ex-Chat"]
ikaros has quit [Remote closed the connection]
thrasibule has quit [Read error: 113 (No route to host)]
thrasibule has joined #ocaml
munga has joined #ocaml
struktured has quit [Read error: 110 (Connection timed out)]
spicey has joined #ocaml
thrasibule has quit [Read error: 113 (No route to host)]
thrasibule has joined #ocaml
<spicey>
I'm thinking about writing an ocaml interface for SDL_Mixer. Any ideas what should I consider so that it would be nicely usable for people other than me? - i'ts extremely close to glcaml / sdlcaml project, but as it's somewhat separate part of sdl, i wouldn't want to pollute sdlcaml - or should i?
<Camarade_Tux>
well, *I* would prefer to see it directly in Sdl, merging it will make much easier for everybody (build system is already there and it'll for sure integrate better)
<spicey>
hmm, i see that there is a OCamlSDL project, and it interfaces with sdl_ttf, sdl_image _and_ sdl_mixer - which is the problem i wouldn't like to have, as i have no need for either sdl_ttf or sdl_image and even don't have them installed
jimmyb2187 has left #ocaml []
jimmyb2187 has joined #ocaml
<Camarade_Tux>
I see, maybe you can simply mod the current ocamlsdl and don't always include these modules
<flux>
I think indeed you can
<flux>
you need to have them installed, though
<flux>
unless you manually trim after installation, or patch the installation..
<flux>
not sure why you'd do that, unless you're extremely tight on space
rbancroft has quit [farmer.freenode.net irc.freenode.net]
Ori_B has quit [farmer.freenode.net irc.freenode.net]
ozzloy has quit [farmer.freenode.net irc.freenode.net]
prigaux has quit [farmer.freenode.net irc.freenode.net]
nimred has quit [farmer.freenode.net irc.freenode.net]
fremo_ has quit [farmer.freenode.net irc.freenode.net]
orbitz has quit [farmer.freenode.net irc.freenode.net]
prigaux_ has joined #ocaml
orbitz has joined #ocaml
Ori_B has joined #ocaml
rbancroft has joined #ocaml
nimred has joined #ocaml
fremo_ has joined #ocaml
ozzloy has joined #ocaml
dark has joined #ocaml
thrasibule has quit [Read error: 113 (No route to host)]
dark has quit [Read error: 101 (Network is unreachable)]
<spicey>
at least here on arch linux sdl separated in independent sdl-* packages, and e.g. sdl_image won't get installed until something _actually_ would need that - even though sdl itself would be available
<flux>
in theory someone could package ocamlsdl bindings as multiple packages as well, I think..
NexT||eVo has joined #ocaml
NexT||eVo has left #ocaml []
tmaedaZ is now known as tmaeda
dark has joined #ocaml
<spicey>
in its current look, though, ocamlsdl packaging seems somewhat frightening, with the ./configure (!) and lablgl bindings. i'm currently going with a small optional-ish sdl_mixer drop-in in the spirit of sdlcaml and glcaml, will put a glcaml fork with it included on github when it's done
Pimm has joined #ocaml
hsuh has joined #ocaml
<peper>
mrvn: mm true
yakischloba has joined #ocaml
ikaros has joined #ocaml
jonafan_ is now known as jonafan
struktured has joined #ocaml
<dark>
spicey, what's the problem with ./configure?
ikaros has quit ["Leave the magic to Houdini"]
<spicey>
dark, nothing much, it just feels somewhat un-ocaml-ish to me
<dark>
well, ocaml only runs on certain platforms, no need to be ultra-portable
<dark>
but at least you know that the configure will work in your system without any additional dependencies =P
dmentre has joined #ocaml
joewilliams has joined #ocaml
kaustuv has left #ocaml []
palomer_ has joined #ocaml
<palomer_>
hrmph
palomer_ has quit ["Leaving"]
<palomer>
now I need to figure out how to compare two infinite trees for equality
yakischloba has quit ["Leaving."]
lutter has joined #ocaml
_unK has joined #ocaml
dmentre has quit ["Leaving."]
<thelema>
palomer: impossible
<thelema>
at least impossible to tell that they're equakl, if they really are infinite
_andre has quit ["leaving"]
yakischloba has joined #ocaml
dark has quit [Read error: 60 (Operation timed out)]
<thelema>
use some structure (hashtbl is most common) to keep track of the nodes you've already visited, and if you revisit, you don't need to recompute - just return equal
<thelema>
lambda expressions are general functions. You just have a data structure.
<palomer>
it is true that every recursion must pass by either a record, a variant and a polymorphic variant
<palomer>
the polymorphic variant case is the only interesting one
<thelema>
your data structure encodes the syntax of functions, checking equality there isn't so bad.
<palomer>
but wait, you can get full recursion by use of polymorphic datatypes
<thelema>
give an example of an infinite [term]
<palomer>
polymorphic variants
<palomer>
type t = [`Foo of t * [`Bar of t] ]
<thelema>
How is that encoded in your [term] type?
<palomer>
that would be type t = [`Foo of t * [`Bar of t] ]
<palomer>
wait, I'm missing the foo and the bar
<thelema>
x :: [] = [x]
<palomer>
one sec
<palomer>
(im generating these with seditable)
<thelema>
palomer: are you sure it's not (fun i -> u (fun v -> v))?
<thelema>
palomer: are you sure it's not (fun u -> u (fun v -> v))?
<palomer>
I'm thinking about type t = \u -> (u * (\v -> u))
<palomer>
type t = [`Foo of t * [`Bar of t] ]
<palomer>
I'm taking the polymorphic variant constructor [] to be abstraction
<thelema>
type t = [`Foo of 'a * [`Bar of 'b] ] ?
<palomer>
type t = [`Foo of 'a * ['Bar of 'a]] as 'a
<thelema>
why [as 'a]?
<thelema>
is that just implied in your model?
<palomer>
type t = [`Foo of t * [`Bar of t] ] === type t = [`Foo of 'a * ['Bar of 'a]] as 'a <-- this is ocaml stuff
<thelema>
yes, I'm fine that those are equivalent, I just don't see where the [as 'a] is in your datatype
<palomer>
right
<palomer>
so (t as a) is the same as (\a -> t)
<thelema>
but you introduce u and v
<palomer>
I think polymorphic variants are the only place you can introduce type abstractions
<palomer>
so im associating every polymorphic variant with an abstraction
<palomer>
(I may be wrong)
<thelema>
hmmm... What can you do with these types?
<palomer>
the types described by "term" ?
<palomer>
they're a subset of the ocaml types
<thelema>
yes - you don't seem to have any ground types
<palomer>
well, admittedly they're not very useful
<palomer>
my actual datatype is much more complicated
<palomer>
"term" is just to figure out how to deal with type recursion
<thelema>
If you can, canonize your types and use normal (=)
<palomer>
which in the most general case, it seems, is equivalent to lambda term equivalence
<palomer>
I don't think my terms have a canonical form
<thelema>
Then restrict yourself to a subset which do or give up on decidability
<palomer>
right, remove recursion
<palomer>
but I'm wondering how ocaml deals with type recursion
<palomer>
since deciding type equivalence between possibly recursive types is undecidable, how does ocaml work?
<thelema>
I think it's able to canonize every type it allows
<thelema>
there's strict rules on recursive types
<palomer>
you can always write ([`Foo of t] as 'a), which corresponds to \a -> t
<palomer>
I agree that without polymorphic variants, everything is nice and easy
<thelema>
yes, but you may not be able to use all such types in real code.
<palomer>
for example?
<thelema>
you can't directly compare two types in ocaml, you can compare a type with the necessary type for a given bit of code.
<thelema>
The types constructible through valid ocaml code aren't necessarily all possible recursive types
<palomer>
let _ = foo : t -> unit = .... in let bar : u = ... in foo bar
<palomer>
ocaml will need to compare t with u
<thelema>
hmmm... ok, fair enough.
<thelema>
well, maybe not...
* thelema
thinks
<thelema>
(t->unit) and (u) are just restrictions on the types that are eventually inferred
<palomer>
yeah
<palomer>
let _ = foo : t -> unit = raise (Failure "foo") in let bar : u = raise (Failure "bar") in foo bar
<palomer>
you can write anything you want for t and u
Pimm has quit [Read error: 110 (Connection timed out)]
<thelema>
ok, then it will try to unify t and u. If it can do that, done. If it can't, no done. It doesn't exactly test if they're equal, though.
<palomer>
if t and u don't contain any unquantified variables, then unification is the same as equality
<thelema>
I'd say it's weaker than equality, as failure to unify doesn't guarantee unequality
<palomer>
yes it does!
<palomer>
unify (t,u) returns a map theta such that theta(t) = theta(u)
<palomer>
if t does not contain free variables then theta(t) = t
Yoric has joined #ocaml
<thelema>
ok, let's put ocaml to the test. Let's produce pairs of types that are represented differently but equal.
<palomer>
hey Yoric
<thelema>
hi Yoric. happy new year
<Yoric>
Hi everyboy, happy new year.
<Yoric>
(can't stay, though)
<palomer>
hmm...
Submarine has joined #ocaml
<palomer>
oh my
<palomer>
woops
<palomer>
no beta reduction, I knew it was a simpler problem
<palomer>
right, so type equality is comparing cyclic trees for equality
<palomer>
which might be a decidable problem
<palomer>
(probably is)
<thelema>
ok, there you go.
<palomer>
but, what's the algorithm??!?
<palomer>
the old "put stuff in a hashtable" trick doesn't work
<thelema>
why not?
<thelema>
memoization deals with cycles quite well.
<palomer>
how would your algorithm work?
<palomer>
ack, im late for an appointment
<palomer>
we'll continue this some other time
<thelema>
let equal t1 t2 = let ht = Hashtbl.create 10 in let loop x y = try Hashtbl.find ht (x,y) with Not_found -> Hashtbl.add ht (x,y) true; if compare x y then equal (decompose x) (decompose y) ...
<palomer>
oh, I see
<palomer>
assume they're equal
<palomer>
when you decompose
<palomer>
that should work
<palomer>
I don't know if it will always terminate though
Amorphous has quit [Read error: 110 (Connection timed out)]
hsuh has left #ocaml []
<palomer>
hrmph
<palomer>
we'll talk later
<palomer>
cya!
Amorphous has joined #ocaml
yakischloba has quit ["Leaving."]
<Gertm>
I did #use "topfind" and #require "curl" in the toplevel, now how do I compile a file that needs those things with ocamlc?
<Gertm>
hmm #require "netclient" gives me: Error: Reference to undefined global `Netsys'
<thelema>
how did you install netclient?
<Gertm>
apt-get
<Gertm>
err I installed libocamlnet or whatsitcalled with apt
<thelema>
hmm, that should have taken care of installing deps... But that error inicates a missing library
<Gertm>
brb
<spicey>
What's with the CAMLreturn? caml/memory.h specifically mentions not to return a [value] with simple return; yet various interfaces i look frequently omit that. The macro itself does some magic with caml__frame and caml_local_roots, but the meaning and importance of that is unclear to me
<thelema>
has to do with the GC - if you don't allocate (or some other things), you can omit CAMLreturn, I think.
<mrvn>
everyCAMLparam needs to be matched by a CAMLreturn.
<mrvn>
If you don't allocate you should also note that in the extern declaration.
pad has joined #ocaml
<spicey>
so, generally, if nothing gets allocated in my external function, then I could skip using CAMLparam / CAMLreturn, right?
<mrvn>
spicey: it means you can. makes it faster. But if you have a value then you can also not call any other function that might allocate without CAMLparam / CAMLreturn
Submarine has quit ["Leaving"]
<spicey>
looking at OCamlSDL interface (and learning much from it), i see that to use a weird-ish C structure it defines simple "type chunk_type" and just stuffs it as a void* into the v = alloc_small(1, Abstract_tag); Field(v, 0) = Val_bp(p);. What is this Val_bp? mlvalues.h doesn't really explain it, and I see no meaningful references
<spicey>
...it could be byte pointer, though there are various *_op and *_hp defines as well, and i can't guess them either
<mrvn>
spicey: it casts a pointer to value.
<mrvn>
it is also undocumented.
<spicey>
then, is it a good way to pass around a pointer to this struct? it sure makes everyhing much easier
det has joined #ocaml
<mrvn>
then you have a value and might to CAMLlocal it
<mrvn>
or do you mean p?
Modius has quit [Read error: 54 (Connection reset by peer)]
<mrvn>
spicey: Personally I prefer the Custom_tag because then you can define a finalizer that frees the C struct.
<spicey>
i mean more like, is it a good practice to take a "struct complicated*" and stuff it into a simple abstract/custom value via Val_bp as a simple pointer?
<thelema>
yes, that's the appropriate way to do it.
<mrvn>
sure. If you pass the pointer back as plain value and free it before ocaml removes all references to it then the pointer might end up in a new ocaml heap and become valid for the GC. Then you have big trouble.
<thelema>
be careful with freeing that pointer,
<mrvn>
In the function that frees the pointer you should probably also set it to NULL in the abstract type. But that only works if you get the abstract type as argument to the close function or have it registered as root somewhere.
<spicey>
in OCamlSDL, when the underlying data is freed, it calls void nullify_abstract(value v) { void **p = (void**)v; *p = null; } - this is good and sufficient, right?
<thelema>
spicey: maybe a bit better to use Val_op() instead of val_bp
<spicey>
yes, as I was previously not understanding, what is _bp, and what is _op?
<mrvn>
I would have thought Field(v, 0) = Val_bp(NULL)
<thelema>
#define Val_op(op) ((value) (op))
<mrvn>
Why use the ocaml macros in one function and then do it the hardway in another?
<thelema>
#define Val_bp(p) ((value) (p))
<thelema>
but semantically they differ: #define Bp_val(v) ((char *) (v))
johnnowak has joined #ocaml
jeddhaberstro has joined #ocaml
<thelema>
#define Op_val(x) ((value *) (x))
<mrvn>
char* is frequently used instead of void* because early C didn't have that
<Gertm>
thelema: apparently I needed the libnethttpd-ocaml-dev package :)
<palomer>
seems revised syntax doesn't have elseless ifs
<palomer>
spicey, are you the new maintainer of ocamlsdl?
<mrvn>
palomer: Great for the parser but having to always add "else ()" sucks
<spicey>
palomer, no, not at all. i'm playing around with glcaml / sdlcaml and currently learning the interfacing by adding SDL_mixer support to this nice package. as I'm new to this, i'm reading bits of ocamlsdl as a textbook
<palomer>
on the other hand, it makes type errors a little clearer
<palomer>
I was never able to mix ocamlsdl and opengl
<palomer>
if foo then bar; .... <--ocaml would tell me that bar does not have type unit
<palomer>
a more meaningful error would be to tell me that I forgot the else clause
<thelema>
palomer: ocaml can benefit from a proper close to if statements.
<spicey>
ocamlsdl uses lablgl for the gl, and it's a pity, as you don't get opengl 2 goodies. well, the main pity is that lablgl doesn't support gl2, I guess, as otherwise it is a very neat interface
<thelema>
I find myself having to catch errors of the form: if foo then bar; baz
<thelema>
when I want baz inside the [if]
<thelema>
I don't think this can be changed without breaking all existing code
<palomer>
ah, right, also ambiguity
<palomer>
I don't run into that problem very often
* thelema
adds debugging code inside his [if]s all the time
<palomer>
the let a = foo and b = bar problem happens more often
<palomer>
there's a missing rec
<palomer>
so it's parsed as let a = (foo and b = bar)
<palomer>
rather annoying
<thelema>
huh? it's not for me.
* thelema
uses let ... and all the time.
<thelema>
too often for some
<palomer>
you mean you forget the rec?
<thelema>
I don't put in the rec intentionally because I'm doing simultaneous variable bindings.
<thelema>
# let a = true and b = false;;
<thelema>
value a : bool = True
<thelema>
value b : bool = False
<thelema>
maybe it's only a problem in the revised syntax. I use original
<palomer>
oh, you can have and without rec?
<flux>
yes :)
<palomer>
because you're too lazy to write let in ?
<palomer>
well, in let in
<flux>
well, you can do this: let a = 1 and b = 2 in let a = b and b = a in (a, b)
<flux>
:)
<flux>
I rarely use it, though
<thelema>
I just use it to indicate to the reader (who probably won't notice anyway) that the following bindings *aren't* sequential, and are independent
<palomer>
oh, and is not sequential?
<flux>
palomer keeps surprising me. he has this awesome programming language project there and then this ;-).
<thelema>
within the let...and..in, the new variables aren't bound, only after the 'in'
<palomer>
I learned ocaml completely by myself!
<thelema>
It's like having a diamond in the dependency graph
<thelema>
palomer: few here took a class in ocaml
<palomer>
not even a mentor?
<flux>
butbut they don't teach ocaml here in finland either :/
<thelema>
I can't say I had any mentor in ocaml.
<thelema>
noone else I know in person knows ocaml that I've not taught them.
<Gertm>
Error: Unbound module Http_client.Convenience I'm running out of libs to install, got almost all of them
<palomer>
thelema, I can't parse that last sentence
<palomer>
bah, I'm originally a haskell programmer, that's my excuse:O)
<palomer>
everyone who knows thelema and who uses ocaml was taught by thelema?
<palomer>
flux, were you taught by thelema?
<flux>
no, but he doesn't know me in person
<flux>
ie. face to face
<palomer>
ah
<palomer>
I've pretty much given up on my programming language
<palomer>
working on oset instead
<palomer>
anyone wanna give it a spin?
<flux>
I think I tried it quite some time ago. I don't think I've figured out a use I would have for it, though :/
<thelema>
actually, that's not quite correct - I've interviewed at two companies that use ocaml, so I've met ocamlers that way.
<flux>
and now I'll be off to sleep
<thelema>
flux: cheers
<thelema>
I made the switch from perl to ocaml. What a change.
<palomer>
night flux
ikaros has joined #ocaml
ttamttam has quit [Read error: 104 (Connection reset by peer)]
<mrvn>
palomer: # let a = 1 and b = 2;;
<mrvn>
val a : int = 1
<mrvn>
val b : int = 2
<mrvn>
palomer: works fine in normal syntax
<mrvn>
palomer: "and" not being sequential is the only reason for it
ikaros_ has quit [Read error: 110 (Connection timed out)]
itewsh has quit ["There are only 10 kinds of people: those who understand binary and those who don't"]
<palomer>
you learn something new everyday:O)
ulfdoz has joined #ocaml
<mrvn>
Beware the day that you don't.
<palomer>
why would anyone want computation not to be sequential?
<mrvn>
usualy so the compiler can reorder them to utilize all functional units of a chip in parallel.
<palomer>
oh, so it's a performance thing
yakischloba has joined #ocaml
<mrvn>
not in ocaml.
<mrvn>
ocaml{c,opt} is rather dumb
<maskd>
can't the compiler infer the lack of dependencies (with let..in)?
<mrvn>
maskd: let a = b and b = a in (a,b)
<thelema>
mrvn: the compiler is literal - it does what you tell it to.
<thelema>
I'm thinking that parallel maps aren't too far off in the future
<mrvn>
parallel maps?
<thelema>
yes. like List.map where the evaluation order becomes non-sequential
<mrvn>
give me a parallel threads first
<thelema>
I'm thinking this isn't as far off as it used to be.
<mrvn>
one can hope
<mrvn>
thelema: I wouldn't expect a parallel List.map to be any faster than a serial one though. Usualy my List.map functions are rather trivial and all the time is spend waiting for the ram to deliver the data.
<thelema>
True - almost all the time, List.map isn't any sort of bottleneck.
<thelema>
There are cases where a parallel one would be faster, and given a parallel map, one could organize programs to take advantage of it.
<mrvn>
lets hope they make a Parallel.List.map
<thelema>
[open Parallel] :)
Pimm has joined #ocaml
ygrek has quit [Remote closed the connection]
demitar has quit ["Ex-Chat"]
avsm has joined #ocaml
<spicey>
About sdl_mixer and error handling. most library functions originally return int (more like bool), e.g Mix_FadeInMusic. OCamlSDL usually just ignores the return value and returns unit, but for my interface, I'm wondering if it is reasonable and shouldn't better bool be returned instead?
<spicey>
Or even an exception dropped, though it's only a sound mixer and that could be an overkill, when some unsuccessful attempt at fading out some boring music could crash everything
<mrvn>
spicey: depends.
Pimm has quit [Read error: 110 (Connection timed out)]
<mrvn>
If it almost always returns true and only false on errors then I would use an exception
<mrvn>
Or have the C stub return a bool and provide two ocaml functions, one that returns bool and one an exception
<mrvn>
If it sets errno on error you might throw an Unix.Unix_error exception
<spicey>
yes, i like the idea of returning bool and then in ocaml deciding whether it should be ignored or not. on failure, it sets SDL_Error to text representation of failure as well, so I have an easy way to failwith() as well
<mrvn>
As beginer that is certainly simpler than throwing the exception from C
gandsnut has joined #ocaml
Yoric has quit []
<gandsnut>
I'd appreciate opinions regarding ocaml as a change of direction for a 'C' programmer, job outlook, comparison to other 'newer' langs. Anybody been involved with ocaml for > a few years?
<johnnowak>
gandsnut: suspect you'd have a hard time finding an ocaml-related job if that's what you're asking
<gandsnut>
Thanks johnnowak, would you elaborate on that? After all, there are 90 people on this channel, where do you think most are applying their ocaml expertise?
<palomer>
grad school
<palomer>
yoric has an ocaml job... that's the only person I know here who has a job
<johnnowak>
Not sure the number of people in the channel has much to do with it. There are hundreds in the Haskell channel and I'm aware of maybe two places that hire Haskell programmers.
<palomer>
smerdyakov used to have an ocaml job
<gandsnut>
(!) grad school, hmmm. Is it just too new or too 'exotic'?
<palomer>
credit suisse and standard chartered are hiring haskell programmers
<gandsnut>
Thanks palomer...
<palomer>
jane street and citrix are hiring ocaml programmers
<johnnowak>
Aye. There aren't zero opportunities, but I couldn't recommend it as a career move.
<gandsnut>
Ok, good to know.
<palomer>
but it's fun!
Yoric has joined #ocaml
<johnnowak>
As for why it's not more popular in industry, there are a number of reasons. Don't think it being too exotic is one of them though.
Yoric has quit [Client Quit]
<gandsnut>
I'm just trying to leverage early 90's 'C' experience towards something up and coming. I never got into C++, VC, Java, Python, yadda yadda.
<johnnowak>
It's likely that F# will be a rather employable skill soon enough. Almost everything you learn about ocaml will transfer to F#.
<gandsnut>
I'd really love to work in something Linux-related... F#? Something beyond C#? Is that .NET-related?
<johnnowak>
F# is more or less ocaml for .NET
avsm has quit ["Leaving."]
<gandsnut>
Can ocaml / F# run on a modest Linux box? Do they compile down to binary executables?
<johnnowak>
ocaml can. f# can be run on linux via mono, but i'm not sure how mature it is
<johnnowak>
i'd recommend ocaml over f# for linux development
<johnnowak>
provided either meets your requirements
<gandsnut>
Right, I saw mono as an installable on my Mandriva 2010 package list.
<gandsnut>
Presently, my requirement is paying rent, food, utilities, bills. And I don't need > USD$ 65K, I'd be happy with half that.
<gandsnut>
As for Haskell, what's the opinion on it regarding future & employability?
<johnnowak>
I think it has a good future as a research vehicle, but I don't see it making many inroads into industry. Other people will give you different opinions though.
<gandsnut>
Understood. Any other languages/environments you see as up 'n coming for telecommute workers?
<johnnowak>
likely something used at smaller companies where there's a lack of talent. maybe objective-c programmers.
<johnnowak>
presumably web programming work is easy to do remotely as well
<gandsnut>
Yeah, I've done my own domain, MySQL, CMS, HTML and CSS stuff, but not for pay. Last, might I ask your interest/involvement in ocaml?
flx_ has joined #ocaml
<johnnowak>
pl research and compiler implementation mainly... academic curiosities
<mrvn>
gandsnut: ocaml is a good way to broaden your experience with functional programming.
<gandsnut>
Cool, sounds like heady stuff. I'll have to chew over your comments, which I thank you for, :)
<mrvn>
gandsnut: Even if you don't end up using it it is good to know.
<johnnowak>
aye, ocaml is good entry point. clojure and scheme are likely easier points of entry, especially considering the abundance of good texts that user the latter
<johnnowak>
*use
<gandsnut>
Thx mrvn - looks like I'll load it up on my Linux box. Scheme - I've heard of that. Isn't that Pascal-related?
<mrvn>
but scheme really has 0 practical use. Ocaml you can actualy use here and there in a real job
<johnnowak>
no, not pascal related
<gandsnut>
Oh.
<mrvn>
gandsnut: scheme is lisp based
<mrvn>
related
<gandsnut>
Ahhhh, right, I knew it was something else. What's 'clojure' ?
<johnnowak>
mrvn: lisps are used here and there for scripting languages and such... i've seen a few common lisp jobs float by here in nyc
<mrvn>
johnnowak: yeah, but not scheme
<johnnowak>
gandsnut: a new lisp dialect that emphases immutable data and parallelism
<johnnowak>
gandsnut: runs on the JVM
<johnnowak>
mrvn: sure, but scheme is a good stepping stone in my opinion given the texts available
<mrvn>
one of those "must have seen, will never use again" languages
<gandsnut>
johnnowak: lisp has been around for quite a while, right?
<johnnowak>
i use plt scheme quite often for prototyping purposes
<johnnowak>
gandsnut: longer than most
<mrvn>
The really nice thing about scheme is that the full language specs cover only 6 pages. Verry simple language to define.
<johnnowak>
i wouldn't be surprised if clojure was employable a few years from now... too soon to say
<johnnowak>
there are already a few clojure jobs floating around
<mrvn>
if you know scheme and ocaml you can probably learn clojure in an hour.
<gandsnut>
mrvn: does scheme compile to executable like ocaml & such?
<johnnowak>
gandsnut: depends on the implementation, of which there are dozens
<mrvn>
gandsnut: don't think there is a compiler for scheme. It is usualy just interpreted.
<johnnowak>
gambit, chicken, ikarus, bigloo, and several others compile to native code
<mrvn>
johnnowak: sure they don't make bytecode + runtime linked into a binary?
<johnnowak>
yes
<johnnowak>
most compile through C, although ikarus compiles directly to machine code
<gandsnut>
Good lord, seems like there are hundreds of environments and languages now. "Boo", "Erlang", ...what did I see somewhere, "D"?
<johnnowak>
there's more than hundreds
<mrvn>
gandsnut: there are thoudsands.
<johnnowak>
erlang is employable
<mrvn>
gandsnut: But if youknow a few you can learn the rest in an hour whenever you need too.
<gandsnut>
Also seems like when a company posts for a hire, the hire has to have some 49-criteria laundry list WITH experience.
<mrvn>
.oO(if you are any good)
<mrvn>
gandsnut: the "experience" part is probably the difficult part
<johnnowak>
you can learn languages and critical core libraries that use the same paradigm within a few weeks..
<mrvn>
you need a job using ocaml first to have experience with ocaml for the next job :(
<johnnowak>
not true. just work on your own ocaml projects.
<mrvn>
johnnowak: luckily that more and more is true.
<gandsnut>
How does needing to know X11 and/or the development environments for X figure in to these 'newer' languages?
flux has quit [Read error: 110 (Connection timed out)]
<johnnowak>
it doesn't unless you want to do X programming
<mrvn>
gandsnut: totaly and not at all
<gandsnut>
So they intrinsically do X I/O?
munga has joined #ocaml
<mrvn>
And likely you will be using sdl or gtk or something instead of plain X.
<johnnowak>
if you want to create a gui that runs on top of X, you generally use another library that sits between your program and X
<gandsnut>
Right, sorry, I couldn't think of the alphabet soup names.
<johnnowak>
eg. qt, gtk, fltk, wxwidgets, etc
<johnnowak>
gandsnut: how much programming experience do you have?
<mrvn>
gandsnut: It is like driving a car. You don't need to know where to put the fuel but it helps when you need a refill.
ikaros has quit ["Leave the magic to Houdini"]
<gandsnut>
johnnowak: 6 years full-time 'C' under MS-DOS (!) and many *nix, self-taught HTML, CSS, some PHP, BASIC, micro-assembler, classes on COBOL, Pascal, SQL (Ingres, Informix, Progress, Conetics). I call what I have "trailing-edge technology".