<palomer>
but gtk_menu_popup takes a function (which gives it the position at which to popup)
<palomer>
(this is the part I'm interested in)
bongy has quit ["Leaving"]
<Anarchos>
are there some specific options to compile ocaml with dynamic linking ? Cause i always get undefined references in the unix subdir, related to caml_XXX functions
<palomer>
a user supplied function used to position the menu, or NULL
<thelema>
palomer: I see a binding that links in at gtkMenuProps, but again I don't know how to use it.
<palomer>
for the popup positioning function?
<palomer>
hrmphrmph
<palomer>
brb
Anarchos has quit ["anyway.... time to go to bed in france !!!!"]
naufraghi has quit [Read error: 113 (No route to host)]
naufraghi has joined #ocaml
coucou747 has quit ["bye ca veut dire tchao en anglais"]
naufraghi_ has joined #ocaml
naufraghi has quit [Read error: 104 (Connection reset by peer)]
catch22 has quit []
hkBst has quit ["Konversation terminated!"]
* palomer
hopes that there's a way to remove decorations, can't live without it
<palomer>
well, off to dance
Demitar has joined #ocaml
<palomer>
whoa, I got a reply in 2 hours
middayc has joined #ocaml
evn_ has joined #ocaml
pango has quit [Remote closed the connection]
pango has joined #ocaml
evn_ has quit []
rogo has quit ["Leaving."]
mwc has joined #ocaml
johnnowak has joined #ocaml
jlouis_ has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
johnnowak has quit []
jlouis has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
__suri has joined #ocaml
Demitar has quit [Read error: 110 (Connection timed out)]
naufraghi_ has quit [Read error: 113 (No route to host)]
pango has quit [Remote closed the connection]
|Catch22| has joined #ocaml
pango has joined #ocaml
seafood_ has quit []
pango has quit [Remote closed the connection]
pango has joined #ocaml
jlouis_ has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
jlouis has joined #ocaml
AxleLonghorn has joined #ocaml
AxleLonghorn has left #ocaml []
jlouis_ has quit [Read error: 110 (Connection timed out)]
johnnowak has joined #ocaml
middayc has quit []
seafood_ has joined #ocaml
mwc has quit ["Leaving"]
seafood_ has quit []
seafood_ has joined #ocaml
|Catch22| has quit []
johnnowak has quit []
<tsuyoshi>
rwmjones: yes I see that you can mark incrementally, but if you mark into a shared mapping, it requires a key
<tsuyoshi>
for example if I wanted to make the example program mark one word at a time, it would create a pretty large key table which wouldn't actually be needed
<tsuyoshi>
but anyway, I had an idea... what if ocaml was changed to have the value of every field in a block be relative to the address of the block
<tsuyoshi>
then you could have relocatable shared mappings
<tsuyoshi>
I was looking into this and I think you can do it by changing less than 10 lines in the compiler.. and then change the Field() macro
<tsuyoshi>
unfortunately any c code that writes to fields directly has to be changed, but it should all bomb out when it's compiled so it shouldn't be hard to to find code that does this
<tsuyoshi>
could also be used with sysv shared memory
schme has joined #ocaml
<flux>
tsuyoshi, what about performance hit?
ziph has joined #ocaml
<flux>
hm, doesn't the linker actually patch the offsets in the memory at load time, or is that just theoretical mumbo-jumbo?-)
<ziph>
Depends. :)
<flux>
hmph, I suppose it cannot do that for plain memory mapped pages
<tsuyoshi>
well the thing is.. if you patch all the offsets
<tsuyoshi>
it's not going tyo be shared, since ocaml data is so pointer-dense
<tsuyoshi>
in that case you might as well just marshal the data
<tsuyoshi>
I don't know what the performance hit would be like.. it's one add instruction for each memory load, one subtract instruction for each store
<tsuyoshi>
you could probably use type information to eliminate it on non-pointer loads/stores
<tsuyoshi>
like how they unbox float records/arrays
<tsuyoshi>
but then that makes c code accessing ocaml data a bit more painful
<ziph>
Is this for accessing in memory structures between processes?
<ziph>
If so you could try and find some free virtual address space in common between the processes. ;)
ziph has quit []
<tsuyoshi>
that kind of limits you though
Demitar has joined #ocaml
ygrek has joined #ocaml
ttamttam has joined #ocaml
seafood_ has quit []
ttamttam has left #ocaml []
seafood_ has joined #ocaml
seafood_ has quit []
Anarchos has joined #ocaml
middayc has joined #ocaml
<Anarchos>
is "command for building...... gcc -shared -o lib.so -Wl,-rpath,/a/path objs " correct ?
ygrek has quit [Remote closed the connection]
ygrek has joined #ocaml
Linktim has joined #ocaml
naufraghi has joined #ocaml
Anarchos has quit ["Vision[0.8.5-0418]: i've been blurred!"]
jlouis_ has joined #ocaml
naufraghi_ has joined #ocaml
naufraghi has quit [Read error: 104 (Connection reset by peer)]
Linktim has quit [Remote closed the connection]
Linktim has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
seafood_ has joined #ocaml
<Linktim>
Sdlwm.toggle_fullscreen(); -> Warning S: this expression should have type unit.
<Linktim>
if someone can help me
ttamttam has joined #ocaml
ziph has joined #ocaml
Anarchos has joined #ocaml
<Anarchos>
re
ttamttam has left #ocaml []
<Anarchos>
nobody can help me with ocamlmklib ?
<Anarchos>
i don't know if the options used to build it are the correct ones
coucou747 has joined #ocaml
munga_ has joined #ocaml
Linktim has quit [Remote closed the connection]
Linktim has joined #ocaml
Yoric[DT] has joined #ocaml
<Yoric[DT]>
hi
<Anarchos>
Yoric[DT] hello
<Anarchos>
i still have my problem with ocamlmklib
* Yoric[DT]
has never toyed with ocamlmklib.
<Anarchos>
neither with dynlink ?
<Anarchos>
i found an hidden presentation of CoreML on the documentation section of the caml.inria.site :)
<Yoric[DT]>
:)
<Yoric[DT]>
I vaguely remember using dynlink once, years ago.
ziph has quit []
<Anarchos>
Yoric i dream of an applicative server in ocaml instead this crappy J2EE ...
<ygrek>
Linktim, ignore (...);
Yoric[DT] has quit ["Ex-Chat"]
<Anarchos>
i am implementing a java virtual machine in ocaml :) pretty interesting exercise :)
<Linktim>
ygrek: ?
<ygrek>
ignore (Sdlwm.toggle_fullscreen ());
bluestorm has joined #ocaml
<Linktim>
ygrek: it works
<Linktim>
but the game crashs
<Linktim>
:/
<ygrek>
no clue :-)
<Anarchos>
Linktim which game ?
<Linktim>
a personnal project
<Linktim>
let screen = Sdlvideo.set_video_mode 1024 768 [`DOUBLEBUF] in
<Linktim>
ignore(Sdlwm.toggle_fullscreen ());
<Linktim>
maybe the problem come from screen no ?
<Anarchos>
i can't help you : i never used Sdl
<Anarchos>
i just want to be able to type #load "unix.cmo" in my toplevel :)
Linktim has quit [Remote closed the connection]
naufraghi_ has left #ocaml []
Anarchos has quit ["Vision[0.8.5-0418]: i've been blurred!"]
schme has quit ["bfirc sucks."]
ita has joined #ocaml
LordMetroid has joined #ocaml
middayc has quit []
seafood_ has quit []
<rwmjones>
tsuyoshi, it's an intriguing idea, but I think this is better discussed on caml-list!
ulfdoz has quit [Remote closed the connection]
ulfdoz has joined #ocaml
seafood_ has joined #ocaml
Linktim has joined #ocaml
LordMetroid has quit [Read error: 104 (Connection reset by peer)]
Demitar has quit [Connection timed out]
Demitar has joined #ocaml
Linktim_ has joined #ocaml
ita has quit ["Hasta luego!"]
Linktim has quit [Read error: 110 (Connection timed out)]
robyonrails has joined #ocaml
jlouis has joined #ocaml
Linktim_ has quit [Remote closed the connection]
seafood_ has quit []
jlouis_ has quit [Read error: 110 (Connection timed out)]
Illocution has quit ["Lost terminal"]
robyonrails has quit ["Leaving"]
Demitar has quit [Read error: 110 (Connection timed out)]
middayc has joined #ocaml
Illocution has joined #ocaml
munga_ has quit ["Ex-Chat"]
middayc_ has joined #ocaml
Anarchos has joined #ocaml
jlouis_ has joined #ocaml
munga_ has joined #ocaml
Demitar has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
coucou747 has quit [Read error: 104 (Connection reset by peer)]
eelte has joined #ocaml
AxleLonghorn has joined #ocaml
Demitar has quit [Read error: 110 (Connection timed out)]
jlouis has joined #ocaml
l_a_m has joined #ocaml
jlouis_ has quit [Read error: 110 (Connection timed out)]
<Anarchos>
Is this configure suspect or not for building ocamlmklib and support shared lib ? http://pastebin.com/m48f7baba
<rwmjones>
Anarchos, seems ok from here ... does ocamlmklib not work?
<Anarchos>
rwmjones lots of undefined symbols in otherlibs/unix
thermoplyae has joined #ocaml
Demitar has joined #ocaml
Snark has joined #ocaml
pango has quit [Remote closed the connection]
pango has joined #ocaml
<Anarchos>
rwmjones any idea ?
<rwmjones>
nope
* Anarchos
is idle: thanks for your support. Anyway, got to out with kids
Morphous has joined #ocaml
jlouis_ has joined #ocaml
Amorphous has quit [Connection timed out]
|Catch22| has joined #ocaml
jlouis has quit [Read error: 110 (Connection timed out)]
<bluestorm>
ah, thelema
<bluestorm>
i just thought some other day that i could implement the others obvious Numeric modules
<bluestorm>
the code i showed you was more a proof of concept, there is Int, Float, NativeInt and Int64, i guess i shall do Int32 and Bigint too, would you be interested ?
<bluestorm>
(the original idea was "see it's quite easy to add new things", but if it's meant to be included in a library, it's probably better to provide the standard stuff directly)
Linktim has joined #ocaml
Linktim has quit [Remote closed the connection]
munga_ has quit ["Ex-Chat"]
ita has joined #ocaml
<thelema>
bluestorm: sure, if you'll contribute that, I'll add it.
<bluestorm>
ok
<bluestorm>
thelema: have you considered building a test suite for your lib ?
<thelema>
bluestorm: yes - I just got stuck at what test library to use.
<bluestorm>
:p
<bluestorm>
i went to the same point and then thought "maybe i could just use thelema's library"
<thelema>
:) heh.
<thelema>
I have a local branch with ounit - I'll get started with that and see what I get.
<thelema>
ocaml has a test directory, but it's all hand-written, with a wierd test harness, iirc
<thelema>
there's a bunch of programs, and then there's a directory containing text files of what their output should be.
<thelema>
and a simple makefile-based routine to diff them.
johnnowak has joined #ocaml
Linktim has joined #ocaml
evn_ has joined #ocaml
Anarchos has quit [Read error: 113 (No route to host)]
ygrek has quit [Remote closed the connection]
ygrek has joined #ocaml
jeremiah has quit [Read error: 104 (Connection reset by peer)]
Snark has quit ["Ex-Chat"]
AxleLonghorn has quit ["Leaving."]
jeremiah has joined #ocaml
Yoric[DT] has joined #ocaml
johnnowak has quit []
<palomer>
is there any way to get put mutually recursive modules in different files?
<palomer>
the module rec ... and ... syntax doesn't seem to lend itself to seperating the modules
pippijn has joined #ocaml
<pippijn>
hi all
<palomer>
yo
<pippijn>
does anyone here know C++?
<ita>
pippijn: try #c++ ? :-)
<pippijn>
I was not going to ask a question about c++
evn_ has quit []
Groovy has joined #ocaml
Groovy has left #ocaml []
<pippijn>
I would like to know whether people here think ocaml is better than C++
<ygrek>
with my limited ocaml experience I like it much more than c++ -- less typing, inline anonymous functions, usable FP, fast compilation..
<pippijn>
bluestorm: I've seen that
<bluestorm>
what do you use C++ for ?
<pippijn>
thelema: better types?
<bluestorm>
he probably means that the type system of OCaml is more powerful, making it easier to represent structured datatypes
<pippijn>
I use C++ for many things.. irc service providers, game servers, scientific libraries
Linktim is now known as Linktimaw
<pippijn>
just programs :-) for anything I need at some point
<thelema>
pippijn: yes, ocaml's type system allows the compiler to catch more of my mistakes, while still not being burdensome in having to specify overly-complex types at every function boundary
<pippijn>
in C++ both the syntax and semantics are sometimes.. not very nice
<palomer>
apart from option, what are the other standard ocaml datatypes?
<pippijn>
const char (&data () const)[N];
<pippijn>
what about const? is there such a thing in ocaml?
<thelema>
pippijn: in ocaml, you have to specifically ask for something to be mutable, so everything is const.
<pippijn>
ah excellent
<thelema>
arrays are bounds-checked, so no buffer overflows (by default)
<pippijn>
arrays are bound checked in safe mode
<pippijn>
(which is default)
<pippijn>
yes
<pippijn>
pure functions?
* thelema
has to go, sorry.
<pippijn>
in gcc, I can say __attribute__ ((pure)), which allows for heavy optimisations
thelema has quit ["back later tonight"]
<pippijn>
does ocaml have such annotations?
<palomer>
is there an equivalent to haskell's Maybe datatype?
<bluestorm>
pippijn: wich is not standard C or C++
<bluestorm>
palomer: option ?
<pippijn>
bluestorm: no..
<palomer>
err, I meant Either
<pippijn>
but it would be nice
<bluestorm>
palomer: do it yourself
<palomer>
gotcha
<palomer>
is there a doc pointing to naming conventions?
<bluestorm>
pippijn: i've heard of a purity analysis phase in compilation
<pippijn>
ah
<bluestorm>
but there is not such annotation in pure ocaml
<pippijn>
what about conditional compilation?
<bluestorm>
hm, probably not
<bluestorm>
what is it ? :p
<pippijn>
are types always equally sized on all platforms?
<bluestorm>
hm
<bluestorm>
not the default int/float types, but there are fixed-size types too
<pippijn>
ah
<pippijn>
what about compilation on different operating systems
<bluestorm>
byte code is quite portable
<pippijn>
yes
<bluestorm>
(i guess the byte code interepreter is written in gcc-compatible C)
<pippijn>
but paths are not
<bluestorm>
native compilation support a few architectures
<palomer>
how do I make a class and a type mutually recursive?
<palomer>
err, a class and a datatype
<bluestorm>
i guess you can't unless you embed them into modules
<bluestorm>
but hm
<bluestorm>
do you really need that ?
<pippijn>
how does one write an ocaml program that works on windows and linux?
<bluestorm>
pippijn: using one's fingers :-)
<palomer>
bluestorm: would be really nice
<bluestorm>
pippijn: if your program doesn't depends on system-specific libraries, they'll work out of the box on both OSes
<bluestorm>
palomer: do you have a real example of use ?
<pippijn>
what about paths?
<palomer>
sure
<palomer>
I have an expression class
<bluestorm>
pippijn: you mean, filesystem paths ?
<pippijn>
yes
<bluestorm>
Filename.concat
<palomer>
now expressions can be many things, so I encode this in a datatype
<palomer>
which is a member of the class
<bluestorm>
do you really need the class at the first time ?
<pippijn>
right.. but Filename.concat doesn't know that on unix, user-specific configuration is in $HOME/.somedir and on windows it's in %APPDATA%/somedir
<bluestorm>
(i still don't understand why you so much want to encode a tree as an object hierarchy)
<palomer>
bluestorm, the class is going to inherit from a superclass
<palomer>
bluestorm, because I'll need a pointer to the current node
<palomer>
so I need all my nodes to inherit from the same virtual class
<palomer>
I have too many node types to encode everything in a huge datatype
<bluestorm>
pippijn: i've seen no such function in the standard ocaml libs
<palomer>
anyways, gotta run
<palomer>
be back later to discuss!
<bluestorm>
but it should not be to difficult to provide that kind of things as a separate library
<bluestorm>
*too
<pippijn>
bluestorm: written in ocaml?
<bluestorm>
why not, but i guess you'd need two version, one for each OS
<pippijn>
hm
<bluestorm>
(compatibility being easy to enforce using a module interface)
<bluestorm>
you could also pass around a simple configuration file, specifying the OS-specific data, and provide both versions to your users
<pippijn>
the reason C++ has a preprocessor is so you can reduce code duplication
<pippijn>
two different versions of a library..
<bluestorm>
how would two different versions of a library lead to more code duplication ?
<pippijn>
there are parts that are the same for both versions
<bluestorm>
you can factor them out
<bluestorm>
ocaml has got a quite powerful module system
<pippijn>
well..
<bluestorm>
you can have functors (modules taking modules as parameters)
<pippijn>
in C for example, if the only difference is the return type of a function
<pippijn>
#ifdef _WIN32
<pippijn>
DWORD
<pippijn>
#else
<pippijn>
int
<pippijn>
#endif
<flux>
in any case, ocaml has a preprocessor too
<pippijn>
funcname () { blab blah...
<pippijn>
flux: which knows things like _WIN32?
<flux>
well, it has an ifdef-module, but I don't think it has any pre-defined values
<flux>
I haven't actually used it; really, very little need
<bluestorm>
pippijn: there usually is a nicer way to do that in ocaml
<ita>
pippijn: at the end all these things from c/c++ are more noise than useful stuff :-)
<flux>
bluestorm, well, you can still need conditional compiling
<bluestorm>
hm
<bluestorm>
i'm not sure really
<flux>
bluestorm, for instance in goba you can either have metaserver support or not, and if not, I don't require linking in xmlight
<flux>
so you don't even need it to compile it, if you don't want metaserver support
<pippijn>
flux: how do you do it then?
<pippijn>
with the ifdef module?
<pippijn>
I recently started using my own preprocessor written in perl for most of my code
<bluestorm>
could you not provide the main code logic in a functorial form, and propose two different main-modules, one using it with xml-light, and the other one without ?
<flux>
no, I have a module that provides the interface, and the real module is picked from the makefile
<pippijn>
ah
<flux>
bluestorm, it basically provided a couple different metaserver-modules
<pippijn>
stub modules
<flux>
bluestorm, one with dummy behavior, one that used xmlight
<flux>
exactly
<flux>
but it needed Makefile magic
<pippijn>
I could use my perl magic for that
<pippijn>
I use perl magic all over the place anyway
<bluestorm>
pippijn: you don't think you would need to
<bluestorm>
hm
<bluestorm>
*i don't
<flux>
:-)
<pippijn>
I'm curious
Anarchos has joined #ocaml
<pippijn>
I don't know what I could do to start learning ocaml
<flux>
I think the best way always is to start doing stuff with it (it being language X to learn)
<bluestorm>
i'd say that generally "oh i don't know how to do it properly in that new language but i can quick-hack a perl preprocessor for this and that" is not a really wonderful approach
<flux>
personally, I don't see it being that wrong
<pippijn>
bluestorm: of course it would be a last resort
<Anarchos>
pippijn read the introductory section of the manual !!
<flux>
if you don't know how to do it "properly" in the first hand, that's ok
<flux>
you would learn that later, and fix it
<pippijn>
I prefer learning it right away and not fix it later
<flux>
but it can be mighty annoying if you find yourself in a situation where you cannot proceed
<pippijn>
currently, I use perl only for code generation
<flux>
"well, I could do it with perl, but I won't, because it's ugly. hence the toy project is now stopped."
<bluestorm>
:p
<pippijn>
I like perl :-)
<ita>
"when you don't know just make a compiler" <- that's the thing!
<pippijn>
I have made a compiler.. written in C++
<flux>
(obviously it's counter productive to do lots of things in Y where Y <> X ;))
det has joined #ocaml
<flux>
pippijn, as a course project or for some other purpose?
<pippijn>
flux: because I wanted to improve C++
<pippijn>
it's not really a compiler
<pippijn>
more like a translator
<flux>
pippijn, hm, so the language you parsed was C++-like?
<pippijn>
yes
<pippijn>
it was C++ with extensions
<flux>
pippijn, in that case maybe you can appreciate the context-sensitivity of ocaml.. ;-)
<pippijn>
why?
<flux>
I understand parsing C++ is far from trivial
<flux>
especially when you bring templates in to the mix
<pippijn>
yes
<pippijn>
my parser has a bug
<pippijn>
template<typename T = int> works
<pippijn>
template<typename T = int *> does not
<pippijn>
hmm
<pippijn>
speaking of templates.. what kind of templates does ocaml have?
<flux>
templates are mostly replaced by polymorphic types and the module system
<flux>
however, the module system isn't turing complete as the template system in C++ is
<flux>
I have not missed it, though
<Anarchos>
flux what is a template system 'turing complete' ??
<pippijn>
Anarchos: you can write meta-functions
<flux>
anarchos, C++ template system is turing complete (module maximum evaluation depth)
<pippijn>
which are evaluated at compile-time
<flux>
I think ghc's extended haskell98 typing is also tc, but its tcness is not quite as apparent as it is in C++, where you can have ifs and loops etc (it might be, though, I haven't really looked into those ghc extensions)
<pippijn>
loops?
<flux>
with recursion
<pippijn>
you can have recursion, yes
<pippijn>
templates are not just types, though
<pippijn>
it's also template<void (*func) ()> or template<int N>
<flux>
pippijn, the compile time evaluation aspects are not captured by the polymorphic types or modules
<flux>
pippijn, there is a fork of ocaml that provides that: metaocaml
<pippijn>
oh
<ita>
Anarchos: you can compute the mandelbrot set or factorials using c++ templates
<pippijn>
what does metaocaml offer?
<flux>
staged compiling
<flux>
so you have code that is evaluated at compile time, that may produce new code that is evaluated at runtime
<pippijn>
interesting
<flux>
I've only read about it, not actually used
<flux>
from what I've gathered, metaocaml's goal is to enhance performance with compile time evaluation
<pippijn>
hmm
l_a_m has quit [Remote closed the connection]
<bluestorm>
flux: turing completeness can be seen as a disavantage too
<flux>
bluestorm, sure
<bluestorm>
because (if i understand correctly) that means you can have non-terminating compilation of programs
<flux>
C++ has evaluation depth limits (for that reason, I suppose)
<bluestorm>
(i suppose that for example the typing phase of ocaml compilation has been proved terminating)
<flux>
which means certain algorithms won't compile without increasing those limits, in a compiler-specific way
<pippijn>
c++ has no limit
<pippijn>
compilers do
<flux>
c++ has minimums that need to be supported
<pippijn>
yes
<flux>
saying you have a maximum won't make your compiler non-conformant
<pippijn>
indeed
<pippijn>
but c++ has no limit
<flux>
I think boost (a library for C++, which covers lots of stuff, including parser generators that make heavy use of templates) is one practical (?) project that has hit those implementation-specific limits
<flux>
pippijn, maybe that even makes things worse, because a program that compiles on one conforming compiler might not compile on another ;)
<pippijn>
is ocaml standardised?
<bluestorm>
isn't
<flux>
not really. it's standardised by its single implementation.
<flux>
(well, single main fork)
<bluestorm>
although the user manual somewhat specifies a "standard"
<flux>
there are some related projects (for example that metaocaml I mentioned), that may extend or change the language
<pippijn>
how much is the ocaml language itself changing?
<flux>
very little
<pippijn>
the D programming language is very much changing
<pippijn>
so is C#
<pippijn>
both of which I don't particularly like
<flux>
the programmable preprocessor however allows controlled extension of the language
<pippijn>
hmm
<flux>
for example you can have a preprocessor module that gives you the "try..catch..finally"-construct, even though ocaml doesn't natively have it
<bluestorm>
syntaxic extensions
<flux>
ocaml and c++ preprocessors are really two very distinct things
<pippijn>
yes
<pippijn>
I like the ability to write syntax extensions
<pippijn>
does it operate on the ast?
<flux>
yes
<bluestorm>
yes it does
<pippijn>
interesting
<flux>
it provides quotations so you don't (..all the time..) need to see/write the tree form
<bluestorm>
i think it's quite similar to the lisp/scheme macro things actually, except that the caml AST, being much more structured, is heavier to use/modify
<flux>
although at times you may find yourself modifying the actual tree. I don't know a lot of this, though, bluestorm's done a lot of camlp4-stuff..
hkBst has joined #ocaml
<ita>
pippijn: there is no ternary operator, you will probably miss it
<pippijn>
hm..
<pippijn>
can syntax extensions provide it?
<bluestorm>
can't you use if/then/else instead ?
<ita>
bluestorm: shhh, let him figure out :-)
<bluestorm>
:D
<pippijn>
hm
<pippijn>
is if/then/else an expression?
<mattam>
Yes.
<pippijn>
ah
<pippijn>
in that case, it *is* a ternary operator
<pippijn>
correct?
<flux>
well, it's not an operator
<flux>
otherwise, yes :)
<pippijn>
nice
<ita>
pippijn: there is no switch-case you will probably miss it (switch in for loops ..)
<pippijn>
match with?
<pippijn>
I don't think I'll miss it
<flux>
ahha, pippijn was prepared for that piece of trolling ;)
<ita>
flux: teasing
<pippijn>
match with is actually what I added to C++ in my extension
<bluestorm>
:D
<pippijn>
amongst others
<pippijn>
match was the largest extension
<bluestorm>
do you have a decent pattern language ?
<pippijn>
pattern matching on data structures and strings
<flux>
reminds me that I wrote a c++ library at work to deconstruct s-expressions in a pattern matching -like fashion
<bluestorm>
iirc there was an INRIA cross-languages extension providing pattern matching
<ita>
pippijn: you are asking the wrong question, here are more interesting ones for you : dynamic shared objects and binary interfaces, gui toolkits, difference between + and +.
<pippijn>
is it possible to dynamically load and execute code?
<flux>
quite recently too. it was sooo much nicer to deal with them with expressions like match(sexpr_to_deconstruct, l(constant("foo"), str(str_variable1), str(str_variable2), rest(sexp_var))) etc
<bluestorm>
pippijn: bytecode can do that easily
<bluestorm>
native code dynamic loading is still a hot question
<bluestorm>
there is an experimental branch including that
<bluestorm>
and it's intended to be included in ocaml 3.11 iir
<bluestorm>
c
<ita>
on the other hand, the switch case construct with gotos makes it possible to write nice and efficient parsers easily, in javascript the switch construct even accepts strings
<ita>
the fallthrough in the case section is really nice for reducing the amount of code necessary
ygrek has quit [Remote closed the connection]
<pippijn>
in c#, switch also accepts strings
<jlouis_>
I remember there is some trick in Java to get it to accept strings there too in a switch
<jlouis_>
maybe it is about making them final or something such