<everyonemines>
mrvn: php programmers say: We only have a vulnerability found every couple weeks, php is fine. C++ programmers say: our program only crashes every couple hours, C++ is fine.
<everyonemines>
java programmers say: verbosity doesn't matter if you use eclipse, java is fine
<everyonemines>
but seriously, php makes people feel like they're getting stuff done
<everyonemines>
and ocaml frustrates people
<_habnabit>
does it? I'd say it's the opposite for me
<everyonemines>
I've seen it. it's not "worse is better" it's
<everyonemines>
if your system is designed by a noob programmer
<everyonemines>
then noob programmers will sometimes find it more intuitive
<everyonemines>
that's my explanation for php
<everyonemines>
from a business perspective, people use php because there are php developers
<everyonemines>
they don't even consider varying programmer quality across languages
<Drakken>
Frustration with OCaml is temporary; with PHP, it's built in.
<everyonemines>
or security issues
<everyonemines>
they say, there are php programmers, other companies use php
Juzor has quit [Quit: Instantbird 1.1]
<everyonemines>
Drakken: You have to admit that it's noob unfriendly. But what's weird to me is the success of haskell.
<Drakken>
Noob's shouldn't do professional software development.
<everyonemines>
maybe it's "look at how smart I am" with haskell
<everyonemines>
that causes people to write about it
<everyonemines>
that causes more people to look into it
<everyonemines>
beats me
<Drakken>
Haskell is like veganism.
<everyonemines>
and I like a good steak
<everyonemines>
but preferably grass fed
<Drakken>
OCaml is vegitarianism, and Haskell is veganism.
<Drakken>
OCaml/vegitarianism used to be cool in certain circles, but now they're not extreme enough. Only Haskell/veganism are considered hip.
<Drakken>
:)
<everyonemines>
whereas I just avoid fast food and get exercise
<everyonemines>
and cook balanced meals
<everyonemines>
this metaphor is working out pretty well
<Drakken>
Weeding out noobs is a good thing.
<Drakken>
Employers complain about all the dummies who apply for jobs, but they could weed them out easily by making them explain things like pointers, closures, and HOFs.
<Drakken>
Most of the people who shouldn't be programming wouldn't even apply if they know they'll be asked hard questions.
<Drakken>
And some of the people who have be driven away by languages like PHP would come back.
<Drakken>
BEEN driven
<Drakken>
OCaml strikes a good balance between safety and convenience.
<Drakken>
I might like to tweak it a little one way or another, but it's a great tool for large-scale development.
<everyonemines>
how would you tweak it exactly
<everyonemines>
personally i think some integrated build handling would be good
emmanuelux has quit [Remote host closed the connection]
emmanuelux has joined #ocaml
emmanuelux has quit [Read error: Connection reset by peer]
<Drakken>
It doesn't matter. I would design a whole new language if I could, but for now I just want to avoid mainstream languages.
<vext01>
on line 23, why do I have to construct a new leaf?
<vext01>
or.. why was the Leaf unpacked to int
<_habnabit>
it was never a leaf. it's of type 'a
<vext01>
i just saw it after I hit enter
<vext01>
my bad
<vext01>
i was also wondering why record exists when you can probably achieve what you need with cartesian product
<vext01>
is it just for naming of elements?
<_habnabit>
'record' ?
<vext01>
<vext01>
let p = { name = "John"; info = 23 };;
<_habnabit>
and what do you mean by 'cartesian product' ?
<vext01>
tree * int * tree
<vext01>
^ is that not what this represents?
<_habnabit>
well. that's a tuple. kind of
<_habnabit>
'a * 'b is the type of a tuple with two elements
<_habnabit>
also as soon as they get beyond two elements, they become _very_ difficult to reason about
<_habnabit>
names make that easier
<vext01>
for example?
<_habnabit>
you have to remember what position means what, since there's not a codified name for each position
<vext01>
that was my original question ;)
<vext01>
02:19 < vext01> is it just for naming of elements?
<_habnabit>
well, no
<Drakken>
but mostly
<_habnabit>
records also support 'mutable'
<Drakken>
there's also a convenient syntax where you can write { foo with bar = x }
<_habnabit>
oh, and updating a record is _much_ easier
<_habnabit>
yes
<vext01>
i see
<mrvn>
But that is all syntactic suggar. The memory representation for tuples and records is the same.
<_habnabit>
is it ?
<vext01>
how comes a record does not get a constructor?
<vext01>
like other types
<everyonemines>
has somebody already done k-means in ocaml
<_habnabit>
what would it do?
<everyonemines>
or do i need to port a c version
<mrvn>
records, tuples and variant types with only one constructor are the same in memory
<vext01>
_habnabit: suppose my tree could hold records too
<mrvn>
vext01: the lables already make the type inference happy. no need to a constructor.
<vext01>
type tree = Leaf of int | Node of tree * int * tree | ???;;
<_habnabit>
vext01, you have to define the record type separately
<vext01>
what do you put in ??? if you have a record called 'jim'
<_habnabit>
vext01, type jim = {x: int; y: int} type tree = Jim of jim
<mrvn>
vext01: type 'a tree = Leaf of 'a | Node of tree * 'a * tree, type my_tree = jim tree
<Drakken>
I would prefer explicit constructors.
<vext01>
i find this confusing
<mrvn>
Drakken: then use them instead of records
<_habnabit>
what's confusing about it?
<vext01>
there are two ways to instantiate things?
<vext01>
er
<vext01>
define types
<mrvn>
vext01: no
<Drakken>
I mean I would prefer field labels that don't conflict, and that requires specifying the type when creating a record.
<Drakken>
and in pattern matching.
<vext01>
mrvn: you must forgive me, i come from C land
<mrvn>
Drakken: there is a branch that adds lables for fields in variant types.
<vext01>
what I cam confused about is that you define a record type
<vext01>
then you cant directtly refer to it in another type?
<vext01>
or...
KDr2 has joined #ocaml
<mrvn>
vext01: sure you can
<Drakken>
vext01 what do you want to do with it?
<vext01>
hang on im just playing
<vext01>
yeh ok
<vext01>
so types are a little different to what I am used to
<vext01>
you define a class of types
<vext01>
so it seems?
<Drakken>
the main difference is variant types.
<vext01>
type xxx = A of int | B of string;;
<mrvn>
vext01: the only difference is that you can't pre-declare a type as in "struct foo;"
<vext01>
^ here i define a type and two constructors
<Drakken>
You can defined Node of 'a*'a and Leaf of 'a to have the same type.
<Drakken>
xxx is a way to fake dynamic typing.
<mrvn>
vext01: that is just a struct { enum { A, B } kind; union { int i; char *str;} }
<mrvn>
vext01: but safe
<vext01>
yeh
<Drakken>
C unions use a constant amount of space.
<Drakken>
For all variants
KDr2 has quit [Ping timeout: 246 seconds]
<mrvn>
Drakken: details, tsss
<vext01>
its different, i can live with it
<vext01>
its reminiscent of bnf
<Drakken>
right
<mrvn>
vext01: you will encounter variant types all over the place. probably the most used thing in ocaml.
<Drakken>
also right
<Drakken>
:)
<vext01>
have you guys read or skimmed the book "practical ocaml"?
<Drakken>
I learned from the Inria manual.
<everyonemines>
i learned from the module reference
<everyonemines>
and the toplevel
<vext01>
well yah, im finding this easier than the book
sizz_ has joined #ocaml
sizz has quit [Remote host closed the connection]
<everyonemines>
read some ocaml code from somebody else
<everyonemines>
maybe stuff in batteries
<vext01>
i briefly looked at batteries
KDr2 has joined #ocaml
<Drakken>
vext01 xxx is a _single_ type that comes in two flavors. Each flavor (variant) defines a class of _values_
everyonemines has quit [Quit: Leaving.]
<vext01>
understood
<vext01>
is there something for vim+ocaml?
<vext01>
lots for emacs
KDr2 has quit [Remote host closed the connection]
KDr2 has joined #ocaml
tlockney has quit [Ping timeout: 252 seconds]
iago has quit [Quit: Leaving]
tlockney has joined #ocaml
oriba has quit [Quit: oriba]
BiDOrD has joined #ocaml
BiDOrD_ has quit [Ping timeout: 265 seconds]
lihaitao has joined #ocaml
KDr2 has quit [Ping timeout: 272 seconds]
KDr2 has joined #ocaml
ulfdoz has joined #ocaml
Tobu has quit [Ping timeout: 260 seconds]
Tobu has joined #ocaml
andreypopp has joined #ocaml
<flux>
mrvn, indeed. actually what I've thought of earlier were the 3d fractals Povray can draw, but I suppose marching cubes is the standard solution for that.
ulfdoz has quit [Ping timeout: 245 seconds]
alxbl has quit [Ping timeout: 244 seconds]
alxbl has joined #ocaml
cdidd has joined #ocaml
silver has joined #ocaml
datkin has quit [Remote host closed the connection]
<eikke>
tree.ml is an implementation of a sort-of b-tree, which works on top of backing storage
<eikke>
we have several serialization systems for this storage, in flog.ml and flog0.ml
<eikke>
these are functors on top of actual storage providers, which are monadic, since we need to support both Lwt-style file IO as well as sync IO
<ousado>
nice
<eikke>
these 'Store's are in store.ml
<eikke>
so to create a database, we do something like
<eikke>
module MyLog = Flog.Flog(Store.Lwt)
<eikke>
module DB = Tree.DB(MyLog)
<avsm>
eikke: does the Baardskeerder LGPLv3 license need a linking exception for ocaml?
<eikke>
then you can use DB.get which will be (MyLog.t -> string -> string Lwt.t)
<eikke>
avsm: eeeh... maybe, dunno?
<eikke>
avsm: sorry I didnt reply oin your mail yet by the way :( havent been able to talk to legal yet, and we didnt figure out the best approach to handle our request yet (from the eng department)
<avsm>
eikke: it's that annoying "ocaml statically links stuff, so the LGPL is basically the GPL without this exception"
<avsm>
eikke: no rush :)
<eikke>
next to this, in rewrite.ml, there's an implementation which can rewrite a database from one serialization format to another
<eikke>
but because this also does IO everything should be in the same monad/store implementation, so it's a functor over 2 serialization functors and 1 store module
<eikke>
now as an external API, we'd like not to expose all these modules (and their functors)
<eikke>
but in the top-level module, have a sum type for all our serialization types and one for all store types, and 2 functions which take e.g. FLOG0 or FLOG, and return the corresponsing functor
<eikke>
might sound like a lot of trickery, but basically started with 'we need to support several ways to handle IO, without duplicating any of the logic'
<adrien>
avsm: we were discussing the LGPL exception a bit yesterday and mfp mentionned that giving an offer to provide the .o/.cm* files required for linking would be enough
<adrien>
bit unclean but would still work
<adrien>
still exception is better
<avsm>
adrien: aha, that's useful to know... so if the library installs those anyway, then all is good
<ousado>
I don't understand the point of that static vs. dynamic linking stuff
<adrien>
should but IANAL ;-)
<adrien>
ousado: ocaml does static by _default_
<ousado>
yes, I mean the license
<adrien>
ah
<ousado>
maybe there's a good reason that escapes me
<adrien>
afaiu, the idea is to not be stuck with something you can't change
<ousado>
but you can always change incase you release the code, right?
<avsm>
eikke: i'm just looking at store.ml; it looks like you basically use a file as a block device, right?
<avsm>
eikke: i'd like to benchmark it running as a microkernel (where the Xen:STORE will be a direct block device, with no filesystem on it).
<eikke>
avsm: feel free? ;)
<eikke>
you might want to use flog0 then, not flog
<eikke>
the latter requires the with_fd function to call fallocate, fadvise and other trickery
tomprince has quit [Ping timeout: 252 seconds]
<eikke>
we decided to work file-based instead of using plain block devices to keep things simple at first
Xizor has joined #ocaml
<avsm>
oh, so Flog uses multiple log files, and Flog0.make construct a single one and allocates within it?
emmanuelux has joined #ocaml
<eikke>
no, thats something different
<eikke>
working on multi-spindle support (intended to leverage throughput of multiple storage devices), but that's work-in-progress
<eikke>
for now flog0 will create 3 storage files always
<eikke>
so that should be hacked out in your case
<eikke>
we're not sure which API to use etc
<eikke>
although I think the correct approach just got into my head now :D
thomasga has joined #ocaml
<eikke>
anyway, I still have the first class functor problem :P
<eikke>
adrien: the cause I can't use the approach which passes in a module and returns a module after applying the functor to the input is
tomprince has joined #ocaml
<ousado>
eikke: nice blog you have there (incubaid)
ankit9 has quit [Ping timeout: 246 seconds]
<eikke>
sometimes I need to be able to show the compiler given L1 = F1(S) and L2 = F2(S), L1.m == L2.m and L1.bind == L2.bind (same for return)
<eikke>
ousado: thanks!
<eikke>
(out of interest: is there any reason modules are first-class but functors aren't?)
<ousado>
maybe just not done yet?
<ousado>
eikke: does baardskeerder support retrieving the previous versions of a record?
<mfp>
eikke: AFAIK there's no pb with functors packed as 1st class values
<mfp>
the only "problem" is that the syntax for the (functor) module type is a bit awkward
<flux>
hmm, I haven't been following but the original problem was returning functors, I suppose the same works there as well?
tomprince has joined #ocaml
Tobu has joined #ocaml
<mfp>
flux: well, the functor is packed as a value and passed to eval; you could as well return it
<mfp>
i.o.w., there's no problem packing functors as 1st class values
tomprince has quit [Ping timeout: 260 seconds]
tomprince has joined #ocaml
Anarchos has quit [Ping timeout: 245 seconds]
probst has quit [Quit: probst]
Tobu has quit [Ping timeout: 260 seconds]
Tobu has joined #ocaml
<eikke>
ousado: yes, you can use an old commit (top of the tree) and as such view an old version of the database, as long as you didn't compact after that commit (compaction takes a given commit as starting point)
<eikke>
mfp: will check, thanks
iago has joined #ocaml
Anarchos has joined #ocaml
oriba has joined #ocaml
<eikke>
mfp: that sort-of works but the type of store's 'a m is not propagated etc
emmanuelux has quit [Ping timeout: 264 seconds]
<eikke>
which is an issu
mika1 has joined #ocaml
mika1 has left #ocaml []
kaustuv has joined #ocaml
<kaustuv>
adrien: just reading your followup on caml-list: if the pointer gets rewritten to 0x1 (i.e., Val_int(0), iirc) then maybe what happened is that the entire module got gc'd right after the initialization?
<eikke>
but 'a L1.m = 'a S1.m = 'a Store.Sync.m = 'a
<eikke>
(which is why api1 compiles)
mika1 has joined #ocaml
<mfp>
eikke: you'd have to define a module type like functor(X : FOO) -> BAR with type baz = foobar X.foo
<eikke>
mfp: I have that, reload the gist, it's in the diff I added
<mfp>
m is the concurrency monad, right=
<mfp>
?
<eikke>
it's the monad used by Store implementations to do their work
<eikke>
in case of Store.Lwt this is Lwt.t
<eikke>
in case of Sync and Memory, it's just the identity monad (somewhat) without any wrapping
<mfp>
you've got a L1.t S1.m and it wants a L1.t, you just have to use the monad's bind to extract the L1.t, unless I'm misunderstanding something
Anarchos has quit [Ping timeout: 245 seconds]
iago has quit [Ping timeout: 248 seconds]
<eikke>
mfp: sure, but in case the sync backend is used, I dont want to enforce using 'bind'
<eikke>
since bind is simply fun v f -> f v
<mfp>
if the code is generic over a monad, you have to use the monad's bind, I don't think there's any way around it
<mfp>
unless you mean the code for a _specific_ monad
<mfp>
(the identity one, in this case)
<mrvn>
in which case you need a GADT
<mfp>
in which case you have to add a with type 'a m = 'a somewhere
<mfp>
oh, that'd be neat :)
<eikke>
hmh, indeed, I overlooked something
<eikke>
damnit
<mrvn>
is anyone using mirage?
ftrvxmtrx has quit [Remote host closed the connection]
<eikke>
mrvn: guess I need to learn some more about GADTs to figure out how they're involved here
<mrvn>
eikke: with a GADT you can use different code depending on the type. So you could use x for one monad and m.bind x for others.
<mrvn>
assuming the types work out
ftrvxmtrx has joined #ocaml
<pippijn>
I wish I could restrict functions taking non-polymorphic ADTs to a subset of that ADT
<mrvn>
pippijn: like [< `A : int -> int t ]?
<mrvn>
(not that that works)
<pippijn>
yes
<pippijn>
but not `A
<pippijn>
I want it with A
<pippijn>
oh wait, no, what you said is not what I meant
<pippijn>
type t = A | B of int | C of string
<pippijn>
val f : t [B | C] -> unit
<pippijn>
restrict at compile time the valid tags for a type
<mrvn>
# let f = function `B (x:int) -> () | `C (s:string) -> ();;
<mrvn>
val f : [< `B of int | `C of string ] -> unit = <fun>
<mrvn>
That is what ` is for
<pippijn>
not `
<pippijn>
exactly
<eikke>
pippijn: the type if 't', not 'A' or 'B' or 'C'
<mrvn>
pippijn: you can use a GADT as witness type to ensure the t is only B|C but that gets quite complex with more types.
<mrvn>
[`B|`C] does all the work for you
<pippijn>
GADT?
<pippijn>
since when does ocaml have GADTs?
<mrvn>
pippijn: since 4.0
<pippijn>
ah..
<mrvn>
(next release)
<mfp>
the way I use private type abbreviations (mostly to mark int/string values & not confuse them), I often wish it were possible to do (1 :> myabbr)
<mrvn>
mfp: That would work only if the type is public and then you could still confuse them
<mfp>
or more specifically things like (x :> myabbr X.t) for compile-time at 0 runtime cost
<mrvn>
# type t = int;;
<mrvn>
type t = int
<mrvn>
# (1 :> t);;
<mrvn>
- : t = 1
<mfp>
mrvn: what I have in mind is to allow explicit type abscription
<mrvn>
abscription?
<mfp>
E_ENGLISH_ERROR? I mean the (x : foo :> bar) thing
<mrvn>
# (1 : int :> t);;
<mrvn>
- : t = 1
<mfp>
say type t = explicit int let f (x : t) = printf "OK, you have a t: %d" (t :> int)
<mfp>
then f 1 -> ... of type int, but expected type t
<mrvn>
mfp: Yeah, that only works if t is private and then (1 :> t) is not allowed.
<mfp>
but you can tag it at no cost with f (1 : t)
<mfp>
right, I'm talking about an hypothetic extension to satisfy that use case ("type x = explicit bar")
<mfp>
"explicit type abbreviations"
<pippijn>
mfp: you mean like strong typedefs?
<pippijn>
which needs explicit coercion between abbreviation and original?
<mfp>
sounds like what I have in mind
<mrvn>
mfp: # module M : sig type t = private int val make : int -> t end = struct type t = int let make x = x end;;
<mrvn>
module M : sig type t = private int val make : int -> t end
<mrvn>
# let f (x : M.t) = Printf.printf "%d\n" (x :> int);;
<mrvn>
val f : M.t -> unit = <fun>
<mfp>
private type abbreviations give you the coercion in one way, but not in the other
<mrvn>
f 1;; f (M.make 1);;
<mrvn>
Thanks to cross module inlining M.make will be a NOP.
<mfp>
mrvn: the problem is when you have a int X.t and want to get a M.t X.t -> you have to do X.map M.make t
<mfp>
when it could all be a NOP
<mrvn>
and instead you will iterator over the full tree/hashtbl/set/... and do a NOP for every entry.
<mfp>
btw. the most important gain I've found in private type abbreviations vs. plain old abstract types is the 0-cost conversions
<mrvn>
mfp: would be nice to have such an "explicit" keyword
<mrvn>
mfp: I would also like "protected". Meaning the type is private unless the module is included.
<mfp>
hmm would that use case be satisfied with namespaces + type abbreviations?
<mfp>
any news about the namespace branch (from OCP?)? it's been a while since I last looked at it
smondet has joined #ocaml
munga has joined #ocaml
nantralien has joined #ocaml
nantralien is now known as Anarchos
Submarine has quit [Quit: Leaving]
<hcarty>
mfp: The last thing I heard was that it is on hold until other projects are completed.
<hcarty>
mrvn: Submit a feature request? There may be some willingness to add support if a large enough group expresses interest.
<hcarty>
mfp: The namespaces branch is gone too
<hcarty>
From github that is
avsm has quit [Quit: Leaving.]
<mrvn>
hcarty: I'm still waiting for my int31 patch for Bigarray to be added
<mrvn>
hcarty: or O_CLOEXEC
<hcarty>
mrvn: Both useful. Type fiddling may spark more interest.
<mrvn>
hcarty: The int31 patch just needs to be commited. I really don't get why that is so hard.
<hcarty>
mrvn: It may be a matter of catching the attention of a core team member who is interested in the feature and willing to support it.
<mrvn>
Which is what sucks with the ocaml developement model. Ocaml only gets stuff the core people want and the community is mostly ignored.
<hcarty>
A community branch with experimental patches has been proposed a few times. If people maintained it actively I imagine such a branch would get community interest and support.
<mrvn>
hcarty: read the last discussion on the ML about it. My take was that the core people are against it.
lihaitao has quit [Quit: Ex-Chat]
<hcarty>
mrvn: That was my take as well. I'm not pushing for it - OCaml's development works for me in its current form. But if there is a string enough community need/desire for such a project then I think it could be made to work.
<hcarty>
s/string/strong/
<hcarty>
My guess is that a proven implementation will go a long way toward to easing the core team's concerns. Particularly if the implementation is shown to be active in tracking the core team's development and working with the core team if/when changes transition from the experimental community branch to the core implementation.
<hcarty>
A lot of the concern seemed to revolve around the apparent emotion driving the proposed fork
<hcarty>
Rather than a cold/dry technical discussion and proposal.
<mrvn>
I don't want to fork. I just want a more repsonsive core team.
<mrvn>
If they accept a patch then good. If they reject it then that is OK too. But just letting things you aren't hyped about rot is bad.
<hcarty>
mrvn: It's been a few years since your patch was submitted. Perhaps pinging the core team would help.
<hcarty>
The core development team seems to have grown significantly over the past year or so.
<Anarchos>
IMHO, the best thing for ocaml (in a theoretically point of view) would be to use again the concurrent GC of D. Doligez
<hcarty>
They have done a lot of cleanup in the BTS but I'm sure there is a large backlog to get through.
<Anarchos>
i don't know for you, but i always found that the master class of X. Leroy on "why concurrency is bad for the gc" is biased : it gives not a busrt of performance, but it allows to write concurrent programs, which is interesting per se :)
<mrvn>
A concurrent GC that gives no preformance bust is stupid.
<mrvn>
The whole point of a concurrent GC would be to gain performance by utilizing multiple cores.
<mrvn>
One thing I always want to try is to infere the lifetime of a value during compilation and then alocate that value on a per-thread/global minor/major heap.
<mrvn>
E.g. a tail recursive function that builds a temporary list and then return "List.rev list" at the end should build that list on its own heap but then might build the reverse list on a global heap.
<mrvn>
The compiler and maybe runtime should track when a value escapes the local scope and needs to be tracked across threads. That way the per-thread GCs could handle most values locally.
<f[x]>
Anarchos, please, don't misuse term "concurrent" for "parallel"
<f[x]>
you can write concurrent programs right now
<Anarchos>
f[x]: so i really thought about the parallel GC of D. Doligez, as implemented in caml light :)
cdidd has joined #ocaml
<hcarty>
mrvn: 'want' implies that the illusion of simultaneous access may be sufficient
<mrvn>
The problem is that concurrent translates as "at the same time" and is used that way in english. Concurrent programming only relies on the illusion of actual concurrent operations / parallelism. concurrent programming != concurrent operations.
<mrvn>
But lets call it a multi-core GC so there is no risk of confusion.
<Anarchos>
a simple use case : i wanted to interface a graphical multithreaded API with ocaml : i couldn't cause it was impossible from each thread of the graphical API to make callbacks to ocaml and communicate about global shared objects (except with socket communication maybe, but too slow for me than memory shared objects)
<mrvn>
sure you can. You only need to acquire/release the ocaml runtime for each callback.
<Anarchos>
mrvn: i never found the good architecture to be able to call C++ threads to/from ocaml in both directions
<Anarchos>
mrvn: it was like porting X or Qt to ocaml :)
<mrvn>
Anarchos: The problem isn't the calling. The problem is that the first callback blocks all other callbacks until it releases the runtime again.
<mrvn>
FYI someone implemente the X library in ocaml.
<mrvn>
+d
Anarchos has quit [Ping timeout: 245 seconds]
cago has quit [Quit: Leaving.]
mika1 has quit [Quit: Leaving.]
ulfdoz_ has joined #ocaml
ulfdoz has quit [Ping timeout: 245 seconds]
ulfdoz_ is now known as ulfdoz
andreypopp has joined #ocaml
Drakken has left #ocaml []
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
sizz has joined #ocaml
sizz_ has quit [Ping timeout: 245 seconds]
ftrvxmtrx has quit [Quit: Leaving]
silver has quit [Read error: Connection reset by peer]
wtetzner has joined #ocaml
Juzor has quit [Remote host closed the connection]
oriba has quit [Ping timeout: 272 seconds]
notk0 has joined #ocaml
smondet has quit [Read error: Connection reset by peer]
<notk0>
Hello, what would be a good way of interfacing Ocaml with other languages? I found out the is Swig to make C libraries available for OCaml, and some project to make python libraries available on Ocaml, but in general is there a preferred way, or should I use pipes/ other posix process communication stuff
<mrvn>
read the chapter about interfacing with C in the manual
<notk0>
mrvn, I mean in general, not necessarily C
eikke has quit [Ping timeout: 260 seconds]
avsm has quit [Quit: Leaving.]
oriba has joined #ocaml
thomasga has quit [Quit: Leaving.]
oriba has quit [Read error: Operation timed out]
smerz has joined #ocaml
oriba has joined #ocaml
xlq has joined #ocaml
<wtetzner>
notk0: I think the way to do it is expose a c interface from the other language, and consume that from ocaml
apropos has joined #ocaml
xlq has quit [Ping timeout: 260 seconds]
apropos is now known as xlq
thomasga has joined #ocaml
<pippijn>
is it recommended to do: "let a = foo and b = bar in" or rather "let a = foo in let b = bar in"?
<notk0>
pippijn, they are different
<notk0>
and creates them at the same level
<notk0>
pippijn, depends on what you need to do
<pippijn>
right
<pippijn>
so when b does not depend on aß?
<pippijn>
should I use and?
<notk0>
you usually use and, (from my experience) when you need both definitions "at the same time"
<notk0>
when you use in, it's like a temporary variable inside your code, let a be used inside this expression inside this, and only the result is evaluated
<notk0>
I mean the last expression
<notk0>
let a = 1; let b=2;
<notk0>
let a =1 and b = 2 in is like the above, but I think when you need two definitions, in case they are recursive or something, you use and
<notk0>
why not create each function independently ?
<thomasga>
but both ways are correct
<notk0>
thomasga, there are specific cases when you need and , I can't think of an example right now, but I have a few rare instances when and was requires to have both definitions at the same level at the same time
<thomasga>
(because let … in … as a nice syntaxic scope whereas in "let … and" the end of the first expression is not very clear)
<thomasga>
yes sure, in some cases, you need it (when you overwrite an already existing variable name for instance)
<thomasga>
but for the fonction pippijn gave, it does not make any difference, it's just syntax / style
<thomasga>
let x = 3 in let x = 4 and y = x + 1 in y ;;
<thomasga>
let x = 3 in let x = 4 in let y = x + 1 in y ;;
<thomasga>
in this case, the semantic is different
<notk0>
pippijn, you know you can define each function independently ?
<pippijn>
notk0: you mean in global scope?
<notk0>
pippijn, yes
<pippijn>
I know I can
<pippijn>
but they capture the buffer in that function's scope
<pippijn>
thomasga: I thought it would be clearer that the functions are independent in that add_uni does not depend on add_chr
srcerer has quit [Quit: ChatZilla 0.9.88.1 [Firefox 11.0/20120312181643]]
ftrvxmtrx has joined #ocaml
emmanuelux has quit [Remote host closed the connection]
ankit9 has quit [Ping timeout: 260 seconds]
cyphase has joined #ocaml
emmanuelux has joined #ocaml
notk0 has quit [Remote host closed the connection]
smondet has joined #ocaml
<hcarty>
pippijn: using 'in' everywhere 'and' is not needed also makes it easier to move code around.
ankit9 has joined #ocaml
kmicinski has joined #ocaml
avsm has joined #ocaml
ftrvxmtrx has quit [Ping timeout: 244 seconds]
<_habnabit>
thelema, I'm using odb.ml, and installing one package (using --have-perms) succeeds, but another says "installed package is not available to the system". I can start up ocaml and topfind finds it, though
<thelema>
is it a library or program or both?
<_habnabit>
just a library
<_habnabit>
both are just libraries
<_habnabit>
(ounit succeeds and camlzip fails fwiw)
<thelema>
can you run this in your toplevel (assuming you've done '#use "topfind"')
<_habnabit>
I don't remember adding an 'o' to camlzip
<_habnabit>
well, I guess I'll use the ~oasis2
<hcarty>
_habnabit: Your _oasis is much better
<_habnabit>
oh, is it?
<hcarty>
The one I put together, IIRC, only wraps the existing Makefile
<_habnabit>
ah, yeah
<hcarty>
It looks like your _oasis is a proper oasis-ification of the library
<hcarty>
It's probably worth submitting upstream
<_habnabit>
okay. I think I'll take your more-comprensive metadata and make a new _oasis from it. (if you don't mind.)
<hcarty>
_habnabit: Please do, thank you
<hcarty>
It looks like upstream uses 'zip' as the findlibnap
<hcarty>
findlib name
<hcarty>
The latest Subversion revision uses zip as the ocamlfind install name
<_habnabit>
okay. changing everything to use 'zip'
<hcarty>
I think I have a compatibility package around somewhere ... it's a Makefile + META file to install a dummy zip/camlzip package that depends on the other
<hcarty>
Hopefully having a consistent upstream name will eventually remove the confusion.
andreypopp has quit [Quit: Computer has gone to sleep.]
jmpf has left #ocaml []
lorill has quit [Quit: Ex-Chat]
ankit9 has quit [Ping timeout: 260 seconds]
<_habnabit>
oh haha
Submarine has quit [Quit: Leaving]
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
ankit9 has joined #ocaml
Submarine has quit [Read error: Operation timed out]
<pippijn>
hcarty: yes, the moving aspect is my main point why I use let in
ftrvxmtrx has quit [Ping timeout: 240 seconds]
andreypopp has joined #ocaml
ankit9 has quit [Ping timeout: 246 seconds]
Tianon has quit [Ping timeout: 260 seconds]
ftrvxmtrx has joined #ocaml
ankit9 has joined #ocaml
<hcarty>
thelema: I'm rather impressed that your github site is the 4th Google search result for odb, and the matching oasis-db site is the 5th.
<adrien>
for you
<adrien>
google tailors its results
<pippijn>
I wonder if google shows my name more often for me than for others
<hcarty>
adrien: Ah... of course
<hcarty>
adrien: Given that, I'm not sure why it isn't #1 :-)
<adrien>
;-)
<adrien>
but making it get higher for everyone wouldn't be hard
Zedrikov has quit [Quit: Bye all, see you next time!]
iago has quit [Ping timeout: 264 seconds]
snearch has quit [Quit: Verlassend]
snearch has joined #ocaml
cdidd has quit [Read error: Operation timed out]
diml has quit [Read error: Operation timed out]
diml has joined #ocaml
cdidd has joined #ocaml
_andre has quit [Quit: leaving]
snearch has quit [Quit: Verlassend]
Tianon has joined #ocaml
Tianon has quit [Changing host]
Tianon has joined #ocaml
<pippijn>
are there any documents on how ocaml implements exception handling?
<xlq>
I think I was told the other day it's just longjmp.
<pippijn>
ok
<pippijn>
that's a pity, I thought it was something really clever
<mfp>
pippijn: it's definitely not longjmp
Tobu has quit [Ping timeout: 272 seconds]
<mfp>
pippijn: http://pastebin.com/XDAZzZCn <- try ... with performs a call, saves the exn handler register, sets its new value (%sp); raise ... restores sp and the exn handler pointer, then returns
ggherdov has joined #ocaml
ggherdov has left #ocaml []
<pippijn>
mfp: thanks
<pippijn>
that asm also shows how GC works in ocaml
<pippijn>
at least a small part of it
<pippijn>
mfp: so try...with doesn't save all registers
<pippijn>
unlike setjmp/longjmp
emmanuelux has quit [Read error: Connection reset by peer]
Tobu has joined #ocaml
emmanuelux has joined #ocaml
eni has joined #ocaml
srcerer has joined #ocaml
emmanuelux has quit [Quit: @+]
drewbert has joined #ocaml
Xizor has quit []
xlq has quit [Ping timeout: 260 seconds]
Tobu has quit [Ping timeout: 272 seconds]
Tobu has joined #ocaml
eni has quit [Quit: Leaving]
dark has joined #ocaml
<dark>
how can I install a package like xstr by source? (what I'm actually doing is installing proofweb - built on top of coq and ocaml - on an amazon ami instance; amazon ami doesn't seem to have an ocaml package so I had to build myself)
<dark>
this package is from godi. I could maybe install godi itself.. right? but I think ocaml 3.11 won't work (but not entirely sure)
<dark>
ops, ocaml 3.12
<dark>
there are rpms with ocaml-xstr and so on.. but I guess it would not install on /usr/local ..
<dark>
can I install a godi package on some ocaml installation from source?