<Drakken>
pippijn are you sure you want to define your module type in terms of an externally defined type?
lggr has quit [Ping timeout: 255 seconds]
lggr has joined #ocaml
lggr has quit [Ping timeout: 245 seconds]
lggr has joined #ocaml
Cyanure has joined #ocaml
lggr has quit [Ping timeout: 240 seconds]
lggr has joined #ocaml
lggr has quit [Ping timeout: 256 seconds]
ftrvxmtrx has joined #ocaml
lggr has joined #ocaml
thomasga has joined #ocaml
lggr has quit [Ping timeout: 260 seconds]
Yoric has joined #ocaml
lggr has joined #ocaml
Cyanure has quit [Remote host closed the connection]
lggr has quit [Ping timeout: 260 seconds]
lggr has joined #ocaml
cago has joined #ocaml
lggr has quit [Ping timeout: 245 seconds]
lggr has joined #ocaml
mnabil has joined #ocaml
lggr has quit [Ping timeout: 244 seconds]
ontologiae has joined #ocaml
lggr has joined #ocaml
Kakadu has joined #ocaml
mcclurmc_away is now known as mcclurmc
lggr has quit [Ping timeout: 240 seconds]
lggr has joined #ocaml
lggr has quit [Ping timeout: 255 seconds]
lggr has joined #ocaml
trotro has joined #ocaml
lggr has quit [Ping timeout: 255 seconds]
lggr has joined #ocaml
lggr has quit [Ping timeout: 240 seconds]
lggr has joined #ocaml
<Kakadu>
hey
<Kakadu>
Let's have three files: A.ml B.mli B.ml where module B depends on module A
<Kakadu>
We should compile them in order [A.ml; B.mlil B.ml] and _not_ in order [*.mli; *.ml] ?
lggr has quit [Ping timeout: 246 seconds]
ocp has joined #ocaml
lggr has joined #ocaml
<trotro>
i remember that *.mli could be compiled before
<Kakadu>
I really think That B.mli can't be compiled before A.ml because of error "A.cmi" not found
<Drakken>
Kakadu apparently it doesn't matter. There's no mention of order in the manual, and even listing B.ml first seems to work.
<trotro>
Kakadu, only if B.mli is really dependent of a.cmi
<Kakadu>
trotro: Yeah, it is my case
<trotro>
you should write your dependence and make will handle it like a piece of cake :)
<adrien>
if B depends on A and you compil nothing related to A before compiling B
<Kakadu>
So the (rhetorical) question is:
<adrien>
how could ocaml manage?
<adrien>
also
<adrien>
don't bother with that
<adrien>
use a tool that already handles that properly
<adrien>
ocamlmakefile, ocamlbuild, omake, others
<Kakadu>
How can they compile this code on Mac and with this order
<Kakadu>
adrien: I know about tools, but it is not mine code
<adrien>
apparently you're able to do changes to it
<trotro>
Kakadu, are you not confusing the dependance between internal code and interafces ?
lggr has quit [Ping timeout: 260 seconds]
<Kakadu>
Why I shold be confusing?
<Kakadu>
should*
<Kakadu>
adrien: I don't want to go deep to rewriting build system beacsuse I don't want a hell with porting their linux/MacOS/iOS/Android build targets today
<trotro>
adrien, sometimes you have to write dependent architecture codes... like for the boot of linux
<trotro>
or if you want a real good compiler
<adrien>
if you add windows 32 bit, windows 64 bit, a couple linux versions, different bitnesses, x86, and arm, mac os x, haiku/beos (yes, there are people using that, on this channel), ios, android, you already have many files
<adrien>
trotro: of course, that's the 1% I left :-)
<trotro>
ha ok
<trotro>
and the ones who want a real fast program :)
beginner42 has joined #ocaml
lggr has quit [Ping timeout: 244 seconds]
Snark has joined #ocaml
<beginner42>
mcclurmc: hi could you tell me again the url for the git repo of opam to upload own packages?
<Kakadu>
beginner42: you can check logs
lggr has joined #ocaml
<beginner42>
Kakadu: i am using the webinterface how can i check out the logs?
<troydm>
according to this OCaml bytecode and native code programs can be written in a multithreaded style, with preemptive context switching. However, because the garbage collector of the INRIA OCaml system (which is the only currently available full implementation of the language) is not designed for concurrency, symmetric multiprocessing is not supported
<troydm>
does that mean that ocaml process can't use more than one processor at a time?
<flux>
correct. ocaml code of one process can run only in one core at a time.
<ocp>
but you can have other threads running computations in C
thelema_ has joined #ocaml
<flux>
or you can do concurrency with multiple processes
<troydm>
ic
<troydm>
thx for claryfying
<adrien>
what you won't see is "150%" CPU usage for a single process of pure ocaml
<flux>
there is a project attempting to remedy this, but so far I don't think no production quality releases have been made.
<ocp>
true
<ocp>
we are working on a "multi-runtime" system
<troydm>
multi-runtime?
<ocp>
i.e. one runtime per thread
<ocp>
no shared memory
<troydm>
ohh ic
<ocp>
threads will communicate by messages, a la Erlang
<troydm>
actor model
<ocp>
the good thing is that it will be the same communication abstraction between threads on a multicore, and processes in a cluster
<ocp>
yes, actors...
<ocp>
with runtime support for better efficiency
thelema has quit [Ping timeout: 265 seconds]
fusillia has quit [Ping timeout: 248 seconds]
<flux>
ocaml can already serialize (marshal) objects of various kinds, including functions (but only if the receiving process is the same executable)
lggr has quit [Ping timeout: 246 seconds]
ankit9 has joined #ocaml
lggr has joined #ocaml
ankit9 has quit [Ping timeout: 240 seconds]
flx_ has joined #ocaml
flux has quit [Read error: Connection reset by peer]
<fx_>
novices fiddling with Obj.magic - what a joy
lggr has quit [Ping timeout: 246 seconds]
<flux>
pippijn, how about putting the objects into a multiset, and then for each equal value, check if they are identical..
<flux>
or are they big objects or difficult to compare?
<pippijn>
at that point, they are not big yet
<pippijn>
and easy to compare
<flux>
there are probably few equal values?
<flux>
if there are many, it wouldn't help
<pippijn>
there are probably none
<pippijn>
this code is just an "assert"
lggr has joined #ocaml
<flux>
too bad batteries doesn't come with multiset
jamii has joined #ocaml
<flux>
(ie. set of objects that can be equal under some criteria but not another, so they should be separated)
<pippijn>
I'm pretty sure there is no sharing
<pippijn>
I just want to be really sure
<pippijn>
and I'm done
<pippijn>
there can't be any sharing
<pippijn>
by construction, really
lggr has quit [Ping timeout: 248 seconds]
lggr has joined #ocaml
cdidd has quit [Ping timeout: 246 seconds]
lggr has quit [Ping timeout: 252 seconds]
smondet has joined #ocaml
lggr has joined #ocaml
lggr has quit [Ping timeout: 248 seconds]
lggr has joined #ocaml
lggr has quit [Ping timeout: 240 seconds]
lggr has joined #ocaml
lggr has quit [Ping timeout: 240 seconds]
lggr has joined #ocaml
Kakadu has quit [Quit: Konversation terminated!]
troydm has left #ocaml []
fraggle_laptop has quit [Ping timeout: 246 seconds]
lggr has quit [Ping timeout: 240 seconds]
lggr has joined #ocaml
tufisi has joined #ocaml
tac has joined #ocaml
lggr has quit [Ping timeout: 240 seconds]
ocp has left #ocaml []
lggr has joined #ocaml
cago has quit [Quit: Leaving.]
lggr has quit [Ping timeout: 246 seconds]
lggr has joined #ocaml
lggr has quit [Ping timeout: 260 seconds]
<tizoc>
it seems to me that the version of Async in bitbucket and the version installed by opam are different, but both are version "108", I am missing something?
<tizoc>
for example, Async.Tcp in bitbucket has Tcp.serve, but the version I have installed doesn't have that (I have Tcp.Server.create instead)
lggr has joined #ocaml
lggr has quit [Ping timeout: 248 seconds]
lggr has joined #ocaml
jack has joined #ocaml
<jack>
hi
jack is now known as Guest94232
<tizoc>
does anyone know from which sources are the async and core packages in opam built? I see that the version available there is newer (108.07.00 vs 108.00.01 which I have cloned from bitbucket)
<Guest94232>
i need some help with a piece of code
ontologiae has quit [Read error: Connection reset by peer]
<thelema_>
Guest94232: just ask
<thelema_>
tizoc: I think the opam meta file for core would tell that
<Guest94232>
i declarete this function: let xor= fun x y ->if((x==true)&&(y==true)||((x==false)&&(y==false))) then false else true;;
<thelema_>
tizoc: n/p
<Guest94232>
let f7 = fun s->if (xor(xor((s.[0]=='1')(s.[1]='1'))(xor((s.[3]='1')(s.[4]='1'))))) then true else false;; ^^^^^^^^^^^^ Error: This expression is not a function; it cannot be applied
<thelema_>
let x1 = xor (s.[0] = '1') (s.[1] = '1') in
lggr has quit [Ping timeout: 255 seconds]
<thelema_>
let x2 = xor (s.[3] = '1') (s.[4] = '1') in
<thelema_>
if xor x1 x2 then true else false
<thelema_>
err, the last line is redundant; `xor x1 x2` is enough
<thelema_>
Guest94232: almost certainly there's a problem with your (), just rewrite to use intermediate expressions, and life is easier.
<Guest94232>
but i want to do all in a fuction
<thelema_>
let f7 s = let x1 = ... in let x2 = ... in xor x1 x2
<Guest94232>
ah ok
ontologiae has joined #ocaml
<thelema_>
I think your problem is that you have `xor ( (x) (y) )`
<Guest94232>
thanks for the help
<thelema_>
because of the extra () after xor, it tries to treat (x) as a function and apply (y) as the argument
Yoric has quit [Ping timeout: 240 seconds]
lggr has joined #ocaml
larhat1 has quit [Quit: Leaving.]
<Guest94232>
let f7 = let x1 =xor((s.[0]=='1')(s.[1]='1')) in let x2=xor((s.[3]=='1')(s.[4]='1')) in if xor x1 x2;;
<Guest94232>
like this?
<thelema_>
you still have the problem xor ( (...) (...) )
<Qrntz>
also, «let xor x y = not (x && y) && (x || y)»
lggr has quit [Ping timeout: 246 seconds]
<thelema_>
in ocaml, functions don't need () around their arguments
fraggle_laptop has joined #ocaml
<Guest94232>
let f7 = let x1 =xor s.[0]=='1' s.[1]='1' in let x2=xor s.[3]=='1' s.[4]='1' in if xor x1 x2;;
<thelema_>
that's too few ()
<thelema_>
you still need () around = expressions
<thelema_>
around s.[x]=='1'
<Guest94232>
ok
<thelema_>
hmm, actually...
<thelema_>
you might be able to get away with that.
* thelema_
checks
lggr has joined #ocaml
<Guest94232>
let f7 = let x1 =xor (s.[0]=='1') (s.[1]='1') in let x2=xor (s.[3]=='1') (s.[4]='1') in if (xor x1 x2);;
<thelema_>
remove the last 'if', and it looks good.
<thelema_>
you can also replace all == with =
<thelema_>
and you don't *need* the () around the last xor
<Guest94232>
let f7 s = let x1 =xor (s.[0]=='1') (s.[1]='1') in let x2=xor (s.[3]=='1') (s.[4]='1') in (xor x1 x2);;
<Guest94232>
this works
<thelema_>
good.
<Guest94232>
i'll try properly later
<Guest94232>
thanks for the hints
<thelema_>
yes, you do need the (), otherwise it's (xor s.[0]) = ('1' s.[1]) = '1'
Guest94232 has left #ocaml []
lggr has quit [Ping timeout: 252 seconds]
lggr has joined #ocaml
thomasga1 has joined #ocaml
thomasga has quit [Read error: Connection reset by peer]
lggr has quit [Ping timeout: 240 seconds]
lggr has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
lggr has quit [Ping timeout: 244 seconds]
fusillia has joined #ocaml
lggr has joined #ocaml
mnabil has quit [Ping timeout: 248 seconds]
err404 has quit [Remote host closed the connection]
lggr has quit [Ping timeout: 245 seconds]
lggr has joined #ocaml
avsm has joined #ocaml
lggr has quit [Ping timeout: 256 seconds]
ontologiae has quit [Read error: Operation timed out]
lggr has joined #ocaml
avsm has quit [Quit: Leaving.]
avsm has joined #ocaml
lggr has quit [Ping timeout: 252 seconds]
trotro has quit [Quit: Leaving]
lggr has joined #ocaml
sepp2k has joined #ocaml
lggr has quit [Ping timeout: 240 seconds]
lggr has joined #ocaml
fraggle_ has quit [Remote host closed the connection]
<thelema_>
you know that there's 'incr' in the stdlib to increment an integer reference.
lggr has joined #ocaml
<wieczyk>
It is my typechecker, my language is currently simply typed [I am using standard type inference without let-generlization, small hack for simply-typed]
<wieczyk>
Sorry I had guest, owner of flat wanted moneys
<wieczyk>
Nice, I did not know.
<wieczyk>
I am thinking about rewrite this code into one objects, only for passing ,,context'' in implicit way
<wieczyk>
maybe also encapsulate other modules as subobjects, or something like that.
<thelema_>
sure, you can do that pretty easily.
<wieczyk>
Is this code clean? I dont know the ml-culture of code-style
<thelema_>
at least locally, it's clean; I've not grokked its overall structure enough to comment on thta.
<thelema_>
| [] ->
<thelema_>
[]
<thelema_>
Most OCamlers are fine with this being on one line, and not needing a newline between match clauses
lggr has quit [Ping timeout: 264 seconds]
<thelema_>
s/newline/empty line/
<wieczyk>
But other clauses are new-lined, I am trying to have some consequence.
<thelema_>
consistency is fine too.
<thelema_>
let solve_constraints solver =
<thelema_>
let constraints = get_constraints solver in
<thelema_>
let mgu = compute_mgu constraints in
<thelema_>
mgu
<thelema_>
for code like this, I use a function `let (|>) x f = f x`
<thelema_>
and then this can be written `let solve_constraints solver = get_constraints solver |> compute_mgu`
<wieczyk>
Hm
<thelema_>
I notice you have |- already; it could also be used, although point-free is discouraged by some OCamlers
lggr has joined #ocaml
<thelema_>
let infertype_program = function | PROGRAM declarations ->
<wieczyk>
I do not understand the thinks related to eta-conversion in Ocaml
<thelema_>
it's unusual style to use variants with a single case... allowed, of course, but a bit unusual
<thelema_>
wieczyk: '_a?
<wieczyk>
let # let f = List.map (fun x -> x);;
<wieczyk>
val f : '_a list -> '_a list = <fun>
<wieczyk>
It is not generalized.
<wieczyk>
I understand what is '_a
<thelema_>
'_a is weakly polymorphic
<wieczyk>
I was inspired by this doing my type-inference
<wieczyk>
but why it is not fully generalized?
<wieczyk>
I remember
<thelema_>
since 'f' is not a syntactic function, there might be some mutable state hiding somewhere that would prevent full polymorphism
<wieczyk>
on studies
<wieczyk>
that without '_a
<wieczyk>
it was possible to break type system
<wieczyk>
by imperative constructs like ref and :=
<thelema_>
want an example?
<wieczyk>
No
<wieczyk>
I will try to do it again
<wieczyk>
It was exercise and I did it five years ago
<wieczyk>
I hope that I still can :
<wieczyk>
:D
<wieczyk>
ref (fun x -> x)
<wieczyk>
was the trick
lggr has quit [Ping timeout: 248 seconds]
fusillia has quit [Ping timeout: 246 seconds]
<thelema_>
not my preferred example; I like the one where values of different types are placed in a list.
<wieczyk>
With list, mhmhm
<wieczyk>
tell me ;]
fusillia has joined #ocaml
<thelema_>
let f = let l = ref [] in (fun x -> l := x :: !l)
<thelema_>
f 3; f "sandwich"
<wieczyk>
nice
<wieczyk>
But Ok
<wieczyk>
I understand needs of weak polymorphism with imperative constructs
<wieczyk>
but why the standard expansion cannot be done automaticly
<wieczyk>
# let f = List.map (fun x -> x);;
<wieczyk>
# let f xs = List.map (fun x -> x) xs;;
<wieczyk>
val f : 'a list -> 'a list = <fun>
lggr has joined #ocaml
<wieczyk>
eta-equivalent but different type.
<thelema_>
wieczyk: it could be, but it's easy enough to work around that it's not worth adding complexity in the compiler
<wieczyk>
Ok.
<thelema_>
At least that's Xavier's position on things like this - compiler complexity comes at a high cost.
<wieczyk>
Mhhm
<thelema_>
adding tricks like this to make people's lives a little easier 1) doesn't really solve the real problem, and 2) makes his life harder
<wieczyk>
Ok, pragmatic argumentation.
<thelema_>
yes, xavier is very pragmatic, which is why we don't have multi-core GC
<wieczyk>
Well, I do not understand why not having multicore GC is pragmatic.
fusillia has quit [Ping timeout: 240 seconds]
<thelema_>
it's a huge amount of complexity to add to the runtime, and it will cost performance in single core. Also, in long run, SMP is doomed; message passing is required.
<wieczyk>
It is not true in my opinion.
<wieczyk>
It is an mathematican opinion who see a multicore as a model of computation.
<wieczyk>
But not all people use SMP to compute something in a graph etc.
<wieczyk>
People want to write servers, event-driven applications, systems etc.
<tac>
SMP?
<wieczyk>
multicore
<wieczyk>
multicore/multiprocessors
<tac>
ah
<tac>
Symmetric MultiProcessing
fusillia has joined #ocaml
<thelema_>
my perspective is that even when we have 100 cores in a CPU, they will be organized in SMP groups that are as big as feasible.
<thelema_>
that said, GPUs aren't doing this, so...
lggr has quit [Ping timeout: 256 seconds]
<wieczyk>
For example in my work we produce a software for telecommunications, it is a really big system, big components etc
<wieczyk>
multicore is something natural here.
<thelema_>
wieczyk: Xavier has no problems with multicore, just the SMP version with a single GC spread across multiple cores.
<thelema_>
the existing threads are great for event-driven applications.
<wieczyk>
No, because they cannot utilize more than one processor.
<wieczyk>
Also I dont know what exacly happens when some ocaml thread will execute some external library with will call a blocking system call like select etc.
<thelema_>
wieczyk: blocking system calls are already all worked out for what's in the stdlib (Unix)
<wieczyk>
in Ocaml stdlib or system stdlib?
<thelema_>
ocalm stdlib
<thelema_>
*OCaml
<wieczyk>
Because in Ocaml stdlib we can have wrappers for blocking routines
<thelema_>
we do
lggr has joined #ocaml
<wieczyk>
We have problem when we for example link our program with some
<wieczyk>
for example FreeBSD specific library
<wieczyk>
which would like to sleep on some system call, like kqueue
<wieczyk>
or link with GUI which would like to sleep on its main-loop
<wieczyk>
It is hard to handle those situations which own user-space emulation of threads.
<wieczyk>
with*
<thelema_>
see otherlibs/threads/unixthreads.ml in the ocaml source tree
<wieczyk>
Yes, concurrent programming is possible without SMP.
<wieczyk>
But it is not issue, issue is to utilize others CPU and dont worry when we use some C library which can block [our threads are blocked then too]
<wieczyk>
our emulated ocaml threads*
<wieczyk>
There is also one another ML-related think which I cannot understand.
<thelema_>
to use other CPUs, use multiple processes. there's some good libraries to help with message passing between processes
<wieczyk>
Why it is not popular? ;]
<thelema_>
jocaml?
<wieczyk>
Multiprocessing uses processes, this communication is very costly
<wieczyk>
it is not practical to use for writing servers
<wieczyk>
I think that you agree with me that it is complicated. You cannot freely push (MyConstructor (a,b,c)) to another process, you need to allocate shared-memory-buffers, serialize data to this buffer, do some synchronizations, lockings etc with other processes with uses this same buffer, on other site deserialize this data etc.
<thelema_>
actually, netshm avoids the serialization step
<thelema_>
and deserialization
lggr has joined #ocaml
<wieczyk>
Wow, how?
<thelema_>
by using ocaml's type safety to copy the in-memory representation of the values
<wieczyk>
Ok, still need of copying whole data.
<thelema_>
yes, have to copy into shared memory
<thelema_>
but no real transformation
<wieczyk>
Good, compare it to threaded servers where you can pass just pointer.
<thelema_>
yes, there's some interesting work in integrating this kind of information into type systems so that you can do pointer passing safely
<thelema_>
but ocaml will likely not have this any time soon.
<wieczyk>
I am ,,crying'' because the functional languages have nice type system, I dont know why high performance applications cannot be written in ML-like language. Why Ocaml need to be only for some small programms.
<wieczyk>
(you cannot omit copying here because processes share only a shm buffer)
Yoric1 has joined #ocaml
<thelema_>
wieczyk: my belief is that the problem is that OCaml's tooling is such that it's easier to write from scratch than to use others' code, and this restrains the community from "standing on the shoulders of giants" as much as we should
<thelema_>
There's some good work on this front.
Yoric has quit [Ping timeout: 240 seconds]
lggr has quit [Ping timeout: 245 seconds]
<tac>
What advantages does Ocaml give you over other languages used in industry?
<thelema_>
tac: over scripting languages: execution speed & safety, over compiled languages: expressivity
<thelema_>
warning: the above is a gross over-simplification
lggr has joined #ocaml
<wieczyk>
tac: I can write applications fast in ocaml.
<wieczyk>
And I have also polymorphism which is nice feautre. Compare it to polymorphism and type-system in C++
<tac>
Why is Ocaml faster than, say, Java?
<thelema_>
tac: it compiles to native code, and has a much simpler runtime
ocp has joined #ocaml
ocp has left #ocaml []
<wieczyk>
where parametric polymorphic does not have any constraints and type system allow you to encode a lot of thinks (see the boost library).
<wieczyk>
I see ML as an elemegant language for programmer.
<wieczyk>
Maybe Haskell is more elegant in syntax, but it is non-strict language what I see as non pragmatic.
<thelema_>
ML is in that sweet spot between expressivity and performance
<tac>
thelema_: Ocaml doesn't have reflection does it?
<wieczyk>
dont
<thelema_>
tac: not particularly sophisticated reflection
<thelema_>
ocaml types don't exist at runtime
<tac>
Type safety doesn't afford you anything when working with most APIs, either
<tac>
If I have to deal with XML, or SQL, or anything on the web
<tac>
I like effect systems, but they always end up more expressive than I care about. You have to deal with things like effect subtyping or positioning effects in a type expression.
<wieczyk>
I dont know, dont have experience.
<wieczyk>
What did you try to use?
<tac>
DDC is a really interesting attempt at a real-world effect system. I've studied it a bit.
<wieczyk>
Tell us about this ;]
<fasta>
tac: I think ATS also looks really pragmatic.
<orbitz>
has anyone seen code that compieles fine in ocamlc fail with pa_extended?
lggr has quit [Ping timeout: 264 seconds]
avsm has quit [Quit: Leaving.]
lggr has joined #ocaml
* orbitz
rage fists
<tac>
wieczyk: DDC also has a very fragile type inference system, from what I understood. It probably isn't well-suited for adding many type extensions.
lggr has quit [Ping timeout: 256 seconds]
<tac>
How do Ocaml users feel about type classes?
<thelema_>
tac: many wish we had them, or something similar so that printing & comparison would be easier
<wieczyk>
I am a new Ocaml user so maybe I am not a good probe. But I see type classes as a constraints, nice for small things like Show, Eq, Ord etc
<thelema_>
wieczyk: "constraints"?
<wieczyk>
Yes, f :: TC a => a -> a -> a, "The f is polymorphic on types which satisfy the TC constraint"
<thelema_>
okay...
<wieczyk>
It is how I understand typeclasses.
<tac>
I always just think of them as implicit parameters :)
<wieczyk>
For example with subtyping you can have constrainted polymorphic
<thelema_>
in ocaml, we have modules+functors, which can do this, but not nearly as conveniently
lggr has joined #ocaml
<wieczyk>
f : forall a < b, a -> a -> a
<wieczyk>
I see typeclasses as something similar, constraints.
<tac>
I only have a fuzzy understanding of modules and functors (and functor is used differently than haskell, from what I understand)
<thelema_>
yes, ocaml functors are functions from modules to modules, which haskell doesn't have.
<tac>
And modules are something related to existential types, right?
<thelema_>
tac: not to me; they're just collections of types and values
<thelema_>
with some namespacing properties
<orbitz>
wow! That erro was not on the line camlp4o told me it was! Tricky dick
<tac>
are modules first-class objects?
<thelema_>
tac: as of 3.13, they are.
<tac>
hm neat
<thelema_>
quite.
<tac>
What is the typical unit of compilation in Ocaml?
<tac>
In Haskell, everything is compiled as a Haskell-module.
lggr has quit [Ping timeout: 256 seconds]
<thelema_>
.ml files are implicitly wrapped in an ocaml module with the same name as the file
lggr has joined #ocaml
<tac>
hm
<wieczyk>
Yeah, Ocaml and Haskell are ,,similar'' here.
<wieczyk>
Haskell also maps filesystem path into module name, Ocamls not.
<wieczyk>
So A/A.ml is the A module, as is B/A.ml
<thelema_>
wieczyk: yes, OCaml may get a fix for that shortly.
<wieczyk>
Yeah
<wieczyk>
probably in Ocaml 4.01... someone here told me about it.
<thelema_>
probably me
<wieczyk>
hihi ;]
<thelema_>
:)
thelema_ is now known as thelema
<wieczyk>
Oh
<wieczyk>
now I can recognize you.
<wieczyk>
(absurdally joke)
<wieczyk>
From where are you?
<thelema>
USA
lggr has quit [Ping timeout: 246 seconds]
<tac>
Chicago here
<thelema>
MI
<tac>
How long have you been doing ocaml, wieczyk?
lggr has joined #ocaml
<wieczyk>
SOrry I forgot about IRC
<wieczyk>
I know it is weird when you ask queastion and forgot about chat.
<tac>
It happens :P
<wieczyk>
I am from Poland.
<wieczyk>
tac: No.
<wieczyk>
tac: Well, I was studying on university so I have a lot of contact with lambda calculus, type systems, Coq etc
<wieczyk>
but I have never programm something not-small in Ocaml
<tac>
I never learned any of this stuff in college. I should have asked for my money back :P
<wieczyk>
hehe
<thelema>
yes, many US universities lack these good bits.
<tac>
We're too pragmatic.
<wieczyk>
In Poland also.
<wieczyk>
Only universities where are logicans.
<tac>
We learn Java and then we get lofty jobs writing shitty code the rest of our lives.
<thelema>
tac: :)
lggr has quit [Ping timeout: 260 seconds]
<tac>
The Curry-Howard Correspondence is what I really love most about this stuff.
<tac>
I just wish the real world was as interested in rigorous proof as I am.
<wieczyk>
;]
larhat has joined #ocaml
<wieczyk>
I am highly inspired by this correspondence.
<wieczyk>
Currently I work at place where we writing in C++ big code
<wieczyk>
but I show one of my coworkers ocaml
<wieczyk>
and give some ,,introduction to type theory''
<wieczyk>
and he is interrested.
<wieczyk>
I treat it as my success of changing world to better.
<wieczyk>
Where do you use Ocaml?
lggr has joined #ocaml
<wieczyk>
Do you have any code in public, I would like to read it and ,,stole'' some experience ;]
<tac>
Mostly because I think lazy evaluation and category theory is overrated.
<adrien>
I've grown very defiant of lazy evaluation
<wieczyk>
Well
<wieczyk>
hard to say about category theory
<orbitz>
I quickly discovered I only wanted lazy eval in a few places
<wieczyk>
it is very advanced stuff. Sometime it looks good for describing semantics etc.
<wieczyk>
I have similar opinion about lazy evaluation.
<wieczyk>
It is overrated, it is unpractical.
<wieczyk>
It is even hard to put debug messages in programmer
<wieczyk>
It is even hard to put debug messages in programm*
<wieczyk>
You need to put unSafePerformIO in places where something will be computed to WHNF
<tac>
I would prefer a language where you can mark functions as total, and lazy evaluation becomes a JIT optimization.
<wieczyk>
in other cases.. your ,,print-debug-message'' expression will be not evaluated :D
<wieczyk>
Hm
<wieczyk>
I would not like it ;]
<wieczyk>
Because see that lazy evaluation changes the maning of programm. You program can fail in eager-evaluation and work in lazy-evaluation. It would be dangerous optimalization
<wieczyk>
becuase you could not see error in your program.
<wieczyk>
Haskell for example is not a lazy languge
<wieczyk>
HAskell is non-strict, it means that
<wieczyk>
programm will work if it would work under lazy evaluation
<wieczyk>
but compiler can change some parts to eager
<thelema>
tac: you mean mark them as pure?
<wieczyk>
(you really dont know how you program work after compilation :D)
<tac>
brb
lggr has quit [Ping timeout: 255 seconds]
lggr has joined #ocaml
avsm has joined #ocaml
<tac>
back
<tac>
thelema: in Ocaml, both pure and total, I guess
lggr has quit [Ping timeout: 248 seconds]
<wieczyk>
It is hard for telling that function is total.
<tac>
I think for many useful functions, it's not so bad.
<wieczyk>
He cannot check if function is total so you need to ensure it by syntax by using only structura recursion. It is very hard.
<tac>
map, for instance
<wieczyk>
But map is small, now compiler and human can easily check that function is total.
<tac>
If you're doing your own recursion, then proving totality is sometimes hard
<tac>
But many programs can be written by composing functions you already know are total
<wieczyk>
It is hard, trust me.
<wieczyk>
Look that not always you are calling recursivery on subpart of your argument
lggr has joined #ocaml
<wieczyk>
sometime you are calling on something smaller but this is not a part of your argument
<wieczyk>
for example quicksort
<tac>
right
<wieczyk>
It is hard to ensure by syntax and type system, hard to tell compiler that your function is total.
<wieczyk>
let drcs : (module Language_driver) = [ ... ];
<thelema>
one must pack modules as first-class values, and then unpack them to use.
<thelema>
probably not, because of the packing step
bobry has quit [Quit: Connection closed for inactivity]
<thelema>
although in 4.00, you should be able to say `let drcs = [ (module WHILE_driver); (module MiniML_driver)]
<thelema>
`
<wieczyk>
It is very nice.
<wieczyk>
I hope that ML will be more popular and people will create some idioms how to programm in it.
<wieczyk>
How it is i possible that Haskell is more popular?!
<thelema>
2 things: package support and polymorphic printing
<adrien>
3rd: more aggressive marketing
<thelema>
it is a pain to have to say "print_int 5" as opposed to "print 5", and all the generalizations of this
lggr has quit [Ping timeout: 245 seconds]
<adrien>
but when you print an hashtable, it doesn't matter anymore because chances are you want it sorted, or maybe no
<adrien>
t
<thelema>
while in OCaml, one doesn't directly have to specify types for values at the callee, but you have to specify the types (in the form of List.length/String.length/Array.length) at the caller
tac-tics has quit [Ping timeout: 240 seconds]
<wmeyer>
4d: Purity and laziness
<wmeyer>
4th actually
<wmeyer>
people like purity and laziness is even bigger advantage
<wmeyer>
polymorpic printing: use deriving
<thelema>
wmeyer: camlp4 is not as good as cpp. cpp just works. camlp4 is a pain
lggr has joined #ocaml
<adrien>
ok, tomorrow, new release of yypkg I think
<wmeyer>
thelema: I disagree.
<wmeyer>
thelema: Joking :-)
<thelema>
:)
<adrien>
reminds me: as soon as rtti appears, I make interfaces to set command-line options and configuration options, including with lablgtk stuff
<adrien>
good night
<thelema>
adrien: good night
<wmeyer>
adrien: good night
lggr has quit [Ping timeout: 245 seconds]
Sablier has quit []
<wieczyk>
22:58 < thelema> 2 things: package support and polymorphic printing
tac has joined #ocaml
<wieczyk>
I thought about it, in each language you are telling how to print your own Data-type. The Show typeclass is a adventage of Haskell, not disadventage of ML
<wieczyk>
I cannot believe that it is a crucial thing in the ML vs Haskell war for souls.
<wmeyer>
wieczyk: but you have deriving
<wmeyer>
wieczyk: there is never one thing
<wmeyer>
that is responsible for this situation
tac-tics has joined #ocaml
lggr has joined #ocaml
<wieczyk>
Maybe Ocaml should add some generic printer from the interpreter
<wmeyer>
I think we had some chat about this before :-) many camlers know about these issues, and the usual consensus is that we need to feel being responsible for that
Znudzon has joined #ocaml
<wmeyer>
maybe
<wieczyk>
We currently have a Weird polymorphic compare etc
<wieczyk>
so we also can add a 'to_string_or_better_name : 'a -> string'
<wmeyer>
wieczyk: remember that polymorpic compare works on runtime rep
<wmeyer>
wieczyk: not at all, we could generate this functions only at compile time
<wmeyer>
I advise to look at deriving-ocsigen package
<wieczyk>
Maybe, I dont know how the runtime representation looks like.
<wmeyer>
it adds the missing part
mcclurmc_away is now known as mcclurmc
<wmeyer>
it's just enough to traverse the data structure by gc + it adds some tags for the efficient pickling
<wieczyk>
23:00 < wmeyer> people like purity and laziness is even bigger advantage
<tac-tics>
The one thing I don't care for about type classes is how badly Haskellers abuse them.
tac has quit [Ping timeout: 240 seconds]
<wmeyer>
wieczyk: that's sort of a joke :-)
<wieczyk>
I think that laziness and purity are disadventages for programmer.
<wieczyk>
OK :D
<wmeyer>
most of Haskell programmers are Mathematicians though
<wmeyer>
so they can't stand ML
<tac-tics>
it feels that way :)
<wieczyk>
but they have good marketing power, Haskell has big communitiy
<wieczyk>
Maybe not as big as python, but is much much bigger than ml.
<tac-tics>
I think Haskell is good for making people excited about programming again.
<wieczyk>
Maybe we should do soemthing with this? ;]
<wieczyk>
Hm
<wieczyk>
nice point.
<wmeyer>
wieczyk: I do it all the time
<tac-tics>
Haskell makes you think "I never even thought something like that was possible!" over and over.
<wmeyer>
to be honest, I apperaed to be alien, but never stop to do so
<wmeyer>
stopped
<wmeyer>
do it at day time job - gauranteed resistance across the company. Some people however are interested, some of the people that are interested actually start asking questions, some of these will install OCaml, and some of them will learn
<wmeyer>
doest that make sense?
lggr has quit [Ping timeout: 256 seconds]
<tac-tics>
I think it would be good to go after startups
<wmeyer>
I've never met anybody learned OCaml because I washed her brain.
<tac-tics>
Make a really good, functional web language out of Ocaml
lggr has joined #ocaml
<wieczyk>
wmeyer: I am also popularizing ML at my work
<wieczyk>
wmeyer: in the C++ fanatics world
<wmeyer>
wieczyk: Powoddzenia z całego serca :-)
<wieczyk>
I think that people working with programmign languages and type theory
<wieczyk>
know a lot of thinks about compilers etc
<wieczyk>
type systems
<wieczyk>
And i am many times can explained how we can do something weird by c++ templates, or what is something not working
<wieczyk>
or how compiler will do something
<wieczyk>
and one guy is currently inspired to learn ML
<wieczyk>
;]
<tac-tics>
I don't think I would ever be impressed by what someone does with C++ templates.
<tac-tics>
Afraid, yes. Impressed, no.
<wieczyk>
So we have some seed of new-ML-programmer ;]
<wmeyer>
wieczyk: Inspiration is not enough, but yes keep trying
<wieczyk>
Yes, it is first step.
<wmeyer>
as I said, I try my best
<wieczyk>
;]
<tac-tics>
oh, and if you want to make a language big
<tac-tics>
blog a lot, and post it on reddit
<wmeyer>
C++ conversion is NP complete.
<wmeyer>
(but somewhat I've done that)
<wieczyk>
C++ is CRAZY-complete
<wieczyk>
and C++ programmers are EXPCRAZY-comlete :D
<wieczyk>
Yes
<wmeyer>
I'm implying here that just few years ago I was one of them
<wieczyk>
current world likes Facebook, REddit etc
<wieczyk>
I hate those things.
<wmeyer>
wieczyk: Y? that's our weapon
<wmeyer>
you don't need to like it
<tac-tics>
I've never been a big fan of Y. I prefer strong normalization.
ontologiae has quit [Ping timeout: 248 seconds]
<wieczyk>
"Y?"?
<wieczyk>
"Y?" is "WHY?"
<tac-tics>
(It was a joke). Y combinator.
<wieczyk>
We know ;], but wmeyer did not speak about Y-combinator.
<wieczyk>
OR did it?
lggr has quit [Ping timeout: 244 seconds]
<tac-tics>
I think languages should also spend a little more on marketing than they do.
<wmeyer>
no, he hasn't
<tac-tics>
That's the only reason Ruby was popular.
<wmeyer>
tac-tics: people
<wmeyer>
not the language
<wmeyer>
that's what I do
Yoric1 has quit [Ping timeout: 246 seconds]
<wmeyer>
but I pay a lot for that
<tac-tics>
Because the Rails community made everyone feel like if they knew Ruby and they knew Rails, they were cool and hip.
<wmeyer>
tac-tics: there is more than RoR
<wmeyer>
it's a paradigm switch
<wmeyer>
and type system also
<wmeyer>
it's brining people to knees
<wieczyk>
Yeah
<wieczyk>
I remember first step in ocaml
<wieczyk>
it was very hard.
<wieczyk>
even when I know C,C++ etc
lggr has joined #ocaml
<wieczyk>
but Haskell should have here same problem
<wieczyk>
first steps are hard.
<tac-tics>
haskell is even harder because you can't cheat
<wieczyk>
yeah
svenl has quit [Ping timeout: 260 seconds]
<tac-tics>
The people in #haskell won't help you if you're using unsafePerformIO even after they tell you not to.
svenl has joined #ocaml
tufisi has quit [Ping timeout: 248 seconds]
lggr has quit [Ping timeout: 255 seconds]
lggr has joined #ocaml
emmanuelux has joined #ocaml
lggr has quit [Ping timeout: 246 seconds]
<ousado>
tac-tics: that's a bit too much of a generalization, don't you think?
<ousado>
it's close to 1000 people there
<tac-tics>
Poorly worded, but basically, you can't fall back on your old habits in haskell
<tac-tics>
because they simply don't work at all.
<wmeyer>
tac-tics: but some of them do that's the point :-)
<ousado>
depends :) if all you have been using before is list comprehensions in python, you feel like you just arrived in heaven
lggr has joined #ocaml
<wmeyer>
ousado: Camlp4 has it, batteries toplevel loads it by default
<tac-tics>
I actually learned Haskell coming from a Python background.
<wmeyer>
I agree Haskell has it out of the box
<tac-tics>
That was rough....
GnomeStoleMyBike has joined #ocaml
<GnomeStoleMyBike>
Hi All
<wieczyk>
Which editor do you use?
<wieczyk>
I am using vim for everything.
<GnomeStoleMyBike>
emacs dude
<wieczyk>
Is it possible to generate TAGS for ocaml (I was not googling)
<GnomeStoleMyBike>
vim is marked by chaos gods ;<
<tac-tics>
I enjoy Notepad++ or gEdit on Linux. Very simple tools.
Anarchos has joined #ocaml
<thizanne>
I enjoy emacs on Linux. Very simple tool. Oh and also, useful.
<tac-tics>
which is why I hate Hindley Milner
<GnomeStoleMyBike>
emacs is simple and it works just great with everything :D why even try to use gEdit ?
<tac-tics>
I never know what type something is looking at my editor
<tac-tics>
emacs is almost a good tool
<wmeyer>
GnomeStoleMyBike: pls, no editor wars
<Drakken>
tac-tics you can add as many type signatures as you want.
<tac-tics>
Emacs lisp and the default configurations basically ruin it though, IMO
<thizanne>
let's talk about the default configuration of notepad++ ;)
<tac-tics>
Drakken: It's a duality. You aren't required to write your own type sigs. But if you're looking at someone else's code, you *are* required to figure it out.
<thizanne>
and about its scripting possib... wait
<tac-tics>
Without loading your code in a REPL, you can't tell what the type of things are.
<Drakken>
It would be nice to get more info out of the type checker.
<GnomeStoleMyBike>
Drakken: for example ?
<wieczyk>
Well
<wieczyk>
I need to say that writing type signatures in Haskell is a nice think
<Drakken>
GnomeStoleMyBike no specific examples
<wieczyk>
MLish let (a:t) (b:s) : u = ...
<wieczyk>
is not readable and noone uses it
<tac-tics>
wieczyk: what does that even do?
lggr has quit [Ping timeout: 256 seconds]
<wieczyk>
sorry
<thizanne>
wieczyk: usually, the types of the functions you use are written on the interface of the module
<wieczyk>
let f (a:t) (b:s) : u = ...
<ousado>
wieczyk: sorry for correcting you, but I think I read "think" instead of "thing" a few times today :)
<wieczyk>
Yes, I am interchanging those words ;]
<wmeyer>
there is ocamlc -i if you want types
<wmeyer>
this # is hyperactive today, yay!
<wieczyk>
thizanne: Yes, but usually you are not writing .mli to each file
<thizanne>
then you can simply ocamlc -i file.ml
<ousado>
wieczyk: it's somewhat funny that it always made sense in both versions, though
<wieczyk>
;]
<wieczyk>
thizanne: See that ocamlc -i is good for small programs.
<wmeyer>
wieczyk: you could also do ocamlbuild file.inferred.mli
<GnomeStoleMyBike>
wieczyk: this may be because of community, in haskell community there is strong stress on type annotations because it is pure functional.
<wieczyk>
thizanne: tac-tics finds problem in reading other code
<wieczyk>
what is this code is big? You need to unhask compiler options
<wieczyk>
to run ocamlc -i
<wmeyer>
GnomeStoleMyBike: not because of that; because haskell requires them
<wieczyk>
it is unpractical, only for one or two filed projects.
<wmeyer>
wieczyk: please find the answer above
<wieczyk>
ehm english my
<GnomeStoleMyBike>
wmeyer: it requires them because haskell is pure you can't "cheat" some things
<wieczyk>
wmeyer: I did not find.
<wmeyer>
GnomeStoleMyBike: you mean value restriction, or? In general in community is well received to give toplevel signatures
lggr has joined #ocaml
<wmeyer>
<wmeyer> wieczyk: you could also do ocamlbuild file.inferred.mli
<wmeyer>
<wieczyk>
Yes, I did not saw it.
<wmeyer>
and then find your file in the _build directory
<wieczyk>
But I am not using ocamlbuild, still using my dirty Makefile
<GnomeStoleMyBike>
wmeyer: i mean in general in community. Well the whole Ocaml community i know is You actually :D so yeah i might be wrong.
<wieczyk>
Nice feature.
GnomeStoleMyBike is now known as MyBikeWasNotType
<wieczyk>
23:56 < wmeyer> this # is hyperactive today, yay!
<thizanne>
wieczyk: if this code is big, there will be .mli files
<wieczyk>
This is first step to conquer the functional world.
MyBikeWasNotType is now known as TypeSafeGnome
<wieczyk>
We are like tribe which was suppresed by other culture.. it is time to uprise!
<wmeyer>
wieczyk, thizanne: the best part is that when actually there is a single function in a module
<wieczyk>
(yes I am crazy)
<wmeyer>
(pure function)
<TypeSafeGnome>
i checked Ocsigen 2.2.2 and 2.2.1 and 2.2 with OCaml 4.0 on OsX and Linux don't want to work. =(
Kakadu has quit [Quit: Konversation terminated!]
TypeSafeGnome is now known as GnomeStoleMyBike
<wieczyk>
wmeyer: Yeah, this .infered.mli is nice
<wieczyk>
wmeyer: But still I think that nice way to write type for toplevel definition is nice competition.
lggr has quit [Ping timeout: 244 seconds]
<ousado>
I very often write out signatures - coming from far less concise languages, it's not a big difference, and I think it's easier for the compiler to give preice errors
<wmeyer>
wieczyk: I agree but that's ML
<ousado>
*precise
<wieczyk>
wmeyer: Maybe some changes are required in ML to gain popularity.
<wmeyer>
wieczyk: I don't have problems like ousado with signatures, and mli files are beautiful enough + they provide enough information for the ocamldoc
<wieczyk>
Ok
<wieczyk>
I am going to ocaml build
<wieczyk>
[Still thinkg that it is weird that i dont know control of binary name in ocamlbuild]
<wmeyer>
wieczyk: But i agree - saying somewhere on the side like: val helper_function : 'a -> ('a -> 'b) -> 'b
<tac-tics>
wmeyer: I was the one bitching about type sigs :)
<thizanne>
I don't think you just can, wieczyk
<wmeyer>
wieczyk: is pretty much explanatory? :-)
<thizanne>
simply use mv
<thizanne>
(yeah, that's weird)
<wieczyk>
dont have*
<wieczyk>
Is it possible to colorize compile errors
<wmeyer>
wieczyk: you can, with _tags and myocamlbuild.ml
lggr has joined #ocaml
<wmeyer>
wieczyk: at some point the pluggable modules will be provided
<wieczyk>
On C++ i have script which sed-dize output with ANSI sequence
<wmeyer>
wieczyk: Emacs does it
<ousado>
man.. C++ errors
<wieczyk>
It could be nice feature in ocamlbuild (colors), I will check if it is possible.
<tac-tics>
C++ is the worst.
<wmeyer>
wieczyk: I already thought about it.
<wieczyk>
C++ is the best, when you see STL/BOOST error you need to take break to get the power ;]
<wmeyer>
but it's not important i think as other "features"
<ousado>
yes, implement ML-style functors in C++ and make a mistake :)
<wieczyk>
I am not ocamlbuild user, i dont see any other ,,required features''
<wmeyer>
ousado: with a template and class with a single constructor - quite possible - however I agree mistake
<wmeyer>
wieczyk: just look at the mantis
<ousado>
wmeyer: yes, it's possible
<wmeyer>
ousado: that's what most notable projects doo with classes ...
<wmeyer>
(LLVM)
<wieczyk>
What is the mantis?
<wmeyer>
and also that's what .net does with interfaces ...
<wmeyer>
bugtracker
<wmeyer>
the biggest chalenge is for me, 6G of ram and 5m linking time of Clang
<wieczyk>
;]
<wmeyer>
because of the blessed templates and the way how C++ "includes" modules
<wieczyk>
One time
<wieczyk>
I copied a VHDL grammar from standard
<wieczyk>
to Haskell's YACC (Happy)
<ousado>
wmeyer: just before I stopped using c++ that was how I did everything ..
<wieczyk>
and... this grammar was so bad
<wieczyk>
more than 500 conflicts...
<wieczyk>
and Happy generated code which GHC was unabel to compile
<wieczyk>
:
<wieczyk>
:D
lggr has quit [Ping timeout: 256 seconds]
<wieczyk>
compiling compiling... and out of RAM
<tac-tics>
Out of memory errors wouldn't happen in a total language :)
<wmeyer>
ousado: :-)
lggr has joined #ocaml
Yoric has joined #ocaml
<wieczyk>
Untrue
<wieczyk>
It is easy to to do out of memory in Coq ;]
<wieczyk>
Just try to do computations on big numbers :-)
<wieczyk>
He is translating numbers to inductive type (n ::= 0 | Succ n)
<wieczyk>
what means that numbers are represented in unary form.. so big numbers are big lists of Succ succ succc...
<wieczyk>
it is easy to consume memory ;]
<dsheets>
typerex/tuareg + emacs + -annot -> type queries with C-c C-t
<wmeyer>
dsheets: \o/ hi
<wieczyk>
It is possible to use .annot in vim?
<thizanne>
no
<thizanne>
there is a law about it
<wieczyk>
?
<thizanne>
which basically says that you must use emacs if you want to code properly in OCaml
<thizanne>
too bad, isn't it ?
<wmeyer>
yeah, I forgot about .annot and cmt and rest
<thizanne>
on this troll, good night all
<wieczyk>
I am using only Emacs for ProofGeneral
<wieczyk>
and it is enough for me.
<dsheets>
wieczyk: yes and i know of people who do this in vim but I do not know what magic is needed
<dsheets>
wmeyer: hi. might come to cambridge, soon
<wmeyer>
dsheets: yay
<wmeyer>
dsheets: please do
<wmeyer>
dsheets: is it ocamllab?
<dsheets>
wmeyer: nah, other things. perhaps in january-march 2013 and perhaps next autumn — we shall see
<wmeyer>
thizanne: it made me sad, but i do use Emacs
<dsheets>
but right now: tacos
<ousado>
dsheets: cambridge in the UK?
lggr has quit [Ping timeout: 248 seconds]
<wmeyer>
ousado: the only that matters :-)
<wmeyer>
dsheets: we shall have a beer then.
<ousado>
wmeyer: hm.. I still don't know which :)
<wmeyer>
ousado: yes, the one in UK :-)
<ousado>
.. since the MIT and Harvard are in another cambridge
<ousado>
I see
lggr has joined #ocaml
<wmeyer>
ousado: yes, but Newton and Turing was from Cambridge UK (and btw that's two of many), but you are right perhaps MIT is not worse
<ousado>
heh
<wmeyer>
and not being here a Troll
<ousado>
wmeyer: so you're from /at cambridge I take it?
<wmeyer>
ousado: not really "from" rather "at", I've been living here for quite while
emmanuelux has quit [Quit: emmanuelux]
jave has joined #ocaml
<wmeyer>
ousado: I didn't mean hurt the other Cambridge, but it's somewhat special for me. I wish to see the other Cambridge two, btw there is another cambridge in uk and another in Canada I think
jave_ has quit [Read error: Connection reset by peer]
jamii has quit [Ping timeout: 246 seconds]
lggr has quit [Ping timeout: 255 seconds]
<ousado>
wmeyer: btw, this is an example I wrote up once, to demonstrate the technique, and someone then told me it was basically ml-style functors: https://gist.github.com/82eb673e0cf4a271fe08
fusillia has quit [Ping timeout: 260 seconds]
lggr has joined #ocaml
lggr has quit [Ping timeout: 240 seconds]
lggr has joined #ocaml
sepp2k has quit [Remote host closed the connection]
fusillia has joined #ocaml
lggr has quit [Ping timeout: 256 seconds]
lggr has joined #ocaml
lggr has quit [Ping timeout: 256 seconds]
<wmeyer>
ousado: very nice! This is essentially what I also meant. However, the problem is disrepancy between "C++ runtime functors" - objects with virtual methods that you pass another object, i.e. BIND Bind(factory, http_protocol, tcp_transport) and the way you've done with templates. In particular the first way does support parametrisation of types, but is static
<wmeyer>
ousado: Also, there is no way to open the module, or include the module
<wmeyer>
ousado: so they are annoyances
lggr has joined #ocaml
<wmeyer>
they=there
<ousado>
wmeyer: yes, it's far from perfect
<wmeyer>
ousado: I meant: only templates support parametrisation by anything (including types), and the classes won't
<ousado>
wmeyer: what I really like about c++ is the support for structural typing
milosn has quit [Ping timeout: 248 seconds]
<ousado>
.. via templates, which makes this possible
<ousado>
but the errors are presented is almost prohibitive
<ousado>
*the way the errors
lggr has quit [Ping timeout: 255 seconds]
milosn has joined #ocaml
lggr has joined #ocaml
<wmeyer>
ousado: yes, and it does type inference and meta programming too, generic programming too :-)
<wmeyer>
ousado: function templates - type inference, meta programming - recursive unrolling, generic programming - overloading
<ousado>
wmeyer: heh, I see you are a fan
<ousado>
wmeyer: it's rare to meet a non-C++-hater these days :)
<wmeyer>
ousado: but I agree, the problems they create are un-bearable. Error messages you mention but also lot of symbols
lggr has quit [Ping timeout: 255 seconds]
<wmeyer>
ousado: to be clear: I hate C++ :-) I really hate ....
<ousado>
well, I think the linkers are pretty smart these days
<ousado>
and WPO
<ousado>
wmeyer: hm.. OK, but well-informed C++ haters are also rare :P
jave has quit [Read error: Connection reset by peer]
<wmeyer>
maybe, but still, tell the C++ programmers to not abuse :-)
<wmeyer>
ousado: full heartly compliment received :-)
lggr has joined #ocaml
<ousado>
I can't really say I hate it - it certainly gave me the hardest times, but I also learned a lot from C++
<wmeyer>
certainly it has a lot of features, some of the are nice
<wmeyer>
but combination of these is deadly for the compilers
Yoric has quit [Ping timeout: 256 seconds]
<ousado>
I just can't understand how any language/programmer can live without ADTs
<wmeyer>
think of local volatile template variables in a static template inside the header file that is also inline
<ousado>
heh
jave has joined #ocaml
<wmeyer>
and now, expect that the compiler will compile it correctly and the linker will not see miessing symbols etc. more over, what would you expect from the standard would be desired behavior?
<wmeyer>
in contrast OCaml has some very well defined semantics, it has some complicated features and mix of them might be deadly, but that's a fraction what C++ allows
<ousado>
yes ..
<ousado>
also it's just beautiful
<wmeyer>
I'm not trying to kill your enthusiasm of C++ :-) I appreciate I can talk about it
<wmeyer>
(and this is what I do at work too...)
<ousado>
well, I'm not really enthusiastic about it anymore
<ousado>
I was beck then, when I made these things work
<ousado>
*back
lggr has quit [Ping timeout: 248 seconds]
<wmeyer>
ousado: slowly you will be less and less, mine stopped about TR1
<ousado>
now that I've discovered FP, I think there's no way back
<wmeyer>
ousado: hacking things in C++ is fun once you know these things :-)
<dsheets>
i hope cambridge, uk is warmer than cambridge, us in wintertimes
<wmeyer>
(just fun, and source of light to the fellow programmers in the company)
<ousado>
I've never written C++ at a job
<wmeyer>
(some of the comments: "your fix looks like it's another way of programming", "my eyes bleed when i look at your fix")
lggr has joined #ocaml
<ousado>
dsheets: are you still in europe?
<wmeyer>
(all I've done was using pre-processor to factor the common patterns...)
<wmeyer>
ousado: what do you write at work?
<ousado>
currently, mostly haxe
<wmeyer>
oh cool
<ousado>
a bit of ocaml
<ousado>
and C
<wmeyer>
even cooler
<wmeyer>
lucky you are
<ousado>
it's my own company :)
<ousado>
so I do what i want
<wmeyer>
even luckier :-)
<ousado>
much to the horror of my (only) partner
<ousado>
I switched languages on the current project 3 times
<wmeyer>
i suppose yes
<dsheets>
ousado: no, back in sf right now
<wmeyer>
ousado: switching is not a bad thing
<wmeyer>
as long as it's a move in the right direction
<ousado>
wmeyer: totally
<ousado>
I was looking for things that compile to JS
<wmeyer>
js_of_ocaml?
<ousado>
I discovered that only after haxe
<ousado>
unfortunately
<wmeyer>
haxe is already nice
<ousado>
yes
<wmeyer>
and you can compile to different languages
<ousado>
I even used the unspeakable for some time
<wmeyer>
and people will not be scared
<wmeyer>
because of braces
<ousado>
yes, I have lots of client/server-side code shared now
<wmeyer>
and maybe there will be an ocaml -> haxxe compiler
<ousado>
and everything is type-safe
BiDOrD_ has joined #ocaml
<wmeyer>
sounds great
<ousado>
so much that it's almost the ML-experience (comiles->works)
<wmeyer>
how is that working? haxxe?
<wmeyer>
I suppose it's not like the lean OCaml syntax
<wmeyer>
but that's just syntax
<wmeyer>
i mean the feeling
lggr has quit [Ping timeout: 245 seconds]
<ousado>
the syntax is not really nice
<ousado>
but macros to the rescue
BiDOrD has quit [Ping timeout: 240 seconds]
<ousado>
it's very productive, really
<wmeyer>
thanks for recomendation!
<wmeyer>
i appreciate, it sounds what i also felt when looked at the language briefly
<ousado>
if you haven't lately, take a look at the type-system, it supports structural typing among other things
<ousado>
and it evolves quickly
<ousado>
I wrote a compiler extension, so I can write macros in ocaml, too
lggr has joined #ocaml
<ousado>
for when speed matters
<wmeyer>
that's good excuse to departure from Haxxe :-)
<ousado>
indeed
thomasga1 has quit [Quit: Leaving.]
<ousado>
I'm a little surprised that haxe seems to be quite attractive for many here in #ocaml
<ousado>
where many is like 4 :)
lggr has quit [Ping timeout: 248 seconds]
<ousado>
but maybe that's because it's easier to recognize a good language when you're already using one
<wmeyer>
i looked at this langugae smiled and said to myself: "That was the Right thing to do"
<ousado>
yeah
<ousado>
it's sooo clever
lggr has joined #ocaml
<ousado>
the user-base is mostly AS3-refugees who make games
<wmeyer>
that's the only way to change how people think
<wmeyer>
the type system is already a major thing here
<ousado>
yes.. and it really works
<ousado>
it makes people go functional
<wmeyer>
haxe can be another OCaml you know
<wmeyer>
easily
<wmeyer>
just different syntax
<wmeyer>
but without type system it would be very hard
<wmeyer>
and once you give them a candy in form of braces
<ousado>
but who would want that
<wmeyer>
they will happily swallow the rest
<ousado>
hehe
<ousado>
yes
<ousado>
that's a very smart obsevation, especially for someone not watching the community
<wmeyer>
unfortunately there are two ways of converting people
<wmeyer>
one are devilish tricks like this
<wmeyer>
the other way is direct evangelisation
<ousado>
yes
<wmeyer>
pitches
<ousado>
e.g. what happens in #scala
<wmeyer>
it needs to be combined to get the effect
<wmeyer>
scala is evil looking at this from side
<wmeyer>
that's exactly what they want to achieve
<ousado>
yes, but many take the direct evangelisation approach