tobiasBora_ has quit [Quit: Konversation terminated!]
badon has quit [Quit: Leaving]
thomasga has quit [Quit: Leaving.]
q66 has quit [Quit: Leaving]
Algebr has joined #ocaml
<Algebr>
silly question, why is the Pervasises named such?
<companion_cube>
because it's used pervasively ;)
<Algebr>
touche.
<Drup>
(and it's so much fancier than "core" or "std" :p)
racycle has quit [Quit: ZZZzzz…]
<Algebr>
trying to print out the type signature of |>, doing (|>), but that still gives error in utop.
<Algebr>
(yes, I know what the signature is, but want to print it out)
<Drup>
what kind of error ?
<Algebr>
utop[139]> (|>);;
<Algebr>
Error: Failure: "|> must be applied to two arguments"
<Drup>
it works for me
<Algebr>
strange, fwiw this is utop running in emacs buffer.
<Drup>
does it works in a normal terminal ?
<Algebr>
nope
<Drup>
this is surprising, to say the least
<Algebr>
using: The universal toplevel for OCaml, version 1.14, compiled for OCaml version 4.01.0
<Algebr>
/ bummer.
<Algebr>
Also, does doing open Foo.Bar set off all the code in Bar? (Like python?)
<Drup>
all the code in Bar ?
<Algebr>
all the let bindings
<Drup>
does "(|>);;" works in the normal top level ? not utop ?
<Drup>
"open Foo.Bar" doesn't affect the let bindings, it just brings everything in the module Foo.Bat in the scope, not sure what you mean
<companion_cube>
the let bindings are executed iff the module is linked
<Algebr>
# (|>);;
<Algebr>
Error: Failure: "|> must be applied to two arguments"
<Drup>
this is impressive, I have no idea what the issue is.
<companion_cube>
Algebr: # 1 |> succ;;
<Algebr>
Drup: I guess my question stems from let () = blah blah. the let () is kind of acting like a main then, right? so is there just one let () in the entireity of a ocaml program? or does it not have to be that way?, you could have many let () (but presumably that would be back practice? )
<Algebr>
bad*
<Drup>
you can have as many "let ()" as you want
<Algebr>
Drup: So the point of let () is what, sequencing/side-effects?
<Drup>
yes
<Drup>
it can be useful some times, but as you pointed out, having lot's of entry points can be a bit of a mess
<Algebr>
but then when does that code execute? Say I do open Foo.Bar, and Bar has a top level let (), does that code execute?
<Algebr>
is there no easy ocamlc --make like everyone else?
* Drup
didn't know that there was a gcc --make, or a ghc --make
<Drup>
;)
WraithM has quit [Ping timeout: 250 seconds]
* Algebr
talked about ocaml at interview, got quizzed on jquery afterward.
<Drup>
whitequark: Why the whole dynlink stuff in ppx_deriving ?
<Drup>
hum, I suppose the goal is to avoid multiple pass on the AST in the presence of multiple independent deriving library, but I'm not sure it's worth dynlinking stuff
<Drup>
(are there still some arch where deriving is not supported ?)
sheijk has quit [Quit: .]
<companion_cube>
Drup: there is ghc --make afaik
<Drup>
oh ?
NoNNaN has quit [Remote host closed the connection]
<companion_cube>
and as for gcc, compiling C is much easier than compiling ocaml
tidren has joined #ocaml
englishm has joined #ocaml
PM has quit [Ping timeout: 240 seconds]
tidren has quit [Remote host closed the connection]
tidren has joined #ocaml
tidren has quit [Read error: Connection reset by peer]
tidren has joined #ocaml
<Algebr>
okay, another strange one.....doing (*) ;; doesn't yield a function signature.
<Drup>
ah, yeah, that's normal
<Drup>
(*) is the empty comment
<Drup>
(yes, I know ...)
<Drup>
you should do : ( * )
<Algebr>
I guess everyone has warts.
pjdelport has quit [Quit: Connection closed for inactivity]
ygrek has quit [Ping timeout: 250 seconds]
martintrojer has quit [Ping timeout: 240 seconds]
<Algebr>
so in_channel/out_channell seem to be opaque types, them presumably they are implemented where? in the actual pervasises.ml?
penglingbo has joined #ocaml
tidren has quit [Remote host closed the connection]
<Drup>
(it's implemented on the C side, and is completly opaque on the ocaml one)
<Algebr>
Drup: ah, so does ocaml also have something like a C coded runtime ala haskell?
<Drup>
the short answer is yes
<Drup>
but in this case, it's simply a "binding" to the appropriate C syscalls
<Drup>
(using the normal ffi)
jprakash has quit [Ping timeout: 256 seconds]
manizzle has quit [Ping timeout: 256 seconds]
ygrek has joined #ocaml
englishm1 has joined #ocaml
englishm has quit [Ping timeout: 240 seconds]
<Algebr>
So every module is basically always available for you to use, no need for imports.
<Algebr>
correct?
<Drup>
given than you link against the library, yes
jprakash has joined #ocaml
tidren has joined #ocaml
englishm1 has quit [Ping timeout: 240 seconds]
<Algebr>
say you have type foo = Bar, does this mean there exists something like: type module = List | Core| ...
<Drup>
huh ? what does one has to do with the other ?
Hannibal_Smith has quit [Quit: Sto andando via]
tidren has quit [Remote host closed the connection]
<Drup>
oh, I get your point, you are playing silly with the syntax :p
<Algebr>
its not confusing that modules are capitalized and constructors are capitalized?
<Drup>
I've never seen any ambiguous statement
<Drup>
either a module is in module position, which is not really common and quite obvious, or it's followed by a dot
<Drup>
I find Haskell's "data Bar = Bar Bar Bar" significantly more confusing
<Drup>
(and about your example, I'm sorry to disappoint, but "module" is a reserved keyword :p)
<pippijn>
Drup: less annoying than "register" being a C/C++ keyword
tidren has joined #ocaml
<Algebr>
I don't think that example would work, but this seems annoying to me, type foo = Bar of string * int, and having to do Bar ("first", 1). instead of just Bar "first" 1
<Drup>
ah, currified constructors
<Drup>
yes, I agree.
<Algebr>
there is no other way?
<Drup>
no
jprakash has quit [Ping timeout: 256 seconds]
<Algebr>
So struct has nothing to do with C's struct?
<Drup>
no
<bernardofpc>
Drup> (*) is the empty comment -> for me this is just the start of a comment with '('
<bernardofpc>
and it gives a different color to (* comment *) and (**)
<bernardofpc>
oh, right, because (** Is an ocamldoc *) comment
<bernardofpc>
btw, will utop work (completion/colors/...) with ppx_* ?
<Drup>
utop doesn't do colors
<Drup>
if you use it inside emacs, I suppose tuareg is doing the coloration stuff
<Drup>
oh, my bad, there is a thingy for utop and colors, Didn't knew about it
Derander_ is now known as Derander
Algebr has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
englishm has joined #ocaml
englishm1 has joined #ocaml
englishm has quit [Ping timeout: 240 seconds]
racycle has joined #ocaml
tidren has quit [Remote host closed the connection]
tidren has joined #ocaml
englishm1 has quit [Ping timeout: 240 seconds]
englishm has joined #ocaml
jao has quit [Ping timeout: 250 seconds]
racycle has quit [Quit: ZZZzzz…]
englishm has quit [Ping timeout: 240 seconds]
englishm has joined #ocaml
siddharthv_away is now known as siddharthv
axiles has joined #ocaml
englishm has quit [Ping timeout: 256 seconds]
r0ok has joined #ocaml
englishm has joined #ocaml
englishm1 has joined #ocaml
englishm has quit [Ping timeout: 240 seconds]
englishm1 has left #ocaml [#ocaml]
ygrek has quit [Ping timeout: 250 seconds]
yacks has joined #ocaml
eikke__ has joined #ocaml
Arsenik has joined #ocaml
cdidd has joined #ocaml
WraithM has joined #ocaml
ggole has joined #ocaml
_0xAX has joined #ocaml
tidren has quit [Remote host closed the connection]
tidren has joined #ocaml
hhugo has joined #ocaml
tidren has quit [Ping timeout: 250 seconds]
FreeArtMan has joined #ocaml
tidren has joined #ocaml
ygrek has joined #ocaml
Kakadu has joined #ocaml
PM has joined #ocaml
PM has quit [Client Quit]
PM has joined #ocaml
FreeArtMan has quit [Remote host closed the connection]
Simn has joined #ocaml
divyanshu has joined #ocaml
AltGr has joined #ocaml
cago has joined #ocaml
Arsenik has quit [Remote host closed the connection]
<whitequark>
Drup: not really multiple passes over AST, no, that's a side effect
<whitequark>
what I really wanted was to have an unified [@@deriving] annotation syntax and to avoid a situation where you have silently ignored annotations
cago has quit [Ping timeout: 260 seconds]
yacks has quit [Ping timeout: 240 seconds]
ia0 has quit [Quit: leaving]
cago has joined #ocaml
ia0 has joined #ocaml
* ygrek
fails to find the description of record field disambiguation in the manual, is it missing?
<tobiasBora>
I'm looking for a simple GUI for my program, which should be then exported for Linux, MacOs, and Windows, which one is nice to use with Ocaml ?
<pippijn>
Unhammer: #require "re2";;
<ggole>
Unhammer: #require it first
jsvgoncalves has joined #ocaml
<tobiasBora>
(I just need to write some text, have some button/text input/check boxes)
<Kakadu>
tobiasBora: (Maybe you don't need OCaml for it :D )
maattdd has quit [Ping timeout: 245 seconds]
<axiles>
in the git repo I introduced a new way of dealing with events (in particular with the event_info parameter)
<tobiasBora>
Kakadu: For the moment labQt will be really fine, but I would like to know (because learning a GUI takes time and I would like to optimise it for further projects) if I can do maths/physics simulations, maybe still later 3D games/simulations etc...
siddharthv is now known as siddharthv_away
<tobiasBora>
Kakadu: For the moment I would like to port a (quite dirty) bash code to download a pdf from scribd, and I would like to port it to Windows... And give it a GUI.
<Kakadu>
tobiasBora: Qt3D was not merged into upstream, so easy 3D is not evailable
<CcxCZ>
hmm reminds me I still have to post patches to two efl bugs (one in ecore, one in it's python bindings)
<axiles>
CcxCZ: for the windows version, adrien is using it to develop the gui version of win-builds
<Kakadu>
tobiasBora: Canonical is creating some 2D library for games. Also I have seen some guys which use some 2D physics engine in QML
<Kakadu>
I can google for strict projects' names
<Kakadu>
We can try to use OCaml bindings to OpenGL with QtQuick GUI but it will need some investigations
<tobiasBora>
And in openGl it's not possible to use 3D ?
maattdd has joined #ocaml
<Kakadu>
whitequark wanted easy GUI + OpenGL recently but I do not have enought time this week and hee seems too
<whitequark>
yeh
<Kakadu>
>
<Kakadu>
> And in openGl it's not possible to use 3D ?
<tobiasBora>
whitequark: so what are you going to do ?
<Kakadu>
tobiasBora: it's possible . I want to say that it is not available out of box
<whitequark>
tobiasBora: I'll just use OpenGL
mcclurmc has quit [Remote host closed the connection]
<Kakadu>
tobiasBora: If you are good at OpenGL you will probably be able to say what is wrong in our demo
<tobiasBora>
Ohhh ok, I though it was because you sayed that "QtQuick 2 QPainter was replaced by OpenGL renderer" and labqt can deal with QtQuick.
<tobiasBora>
Oh I'm not good at all with OpenGL, my most important project using it was to draw a 3D rubik's cube ^^ But maybe in a few years ;)
divyanshu has quit [Quit: Computer has gone to sleep.]
maattdd has quit [Ping timeout: 250 seconds]
dsheets has joined #ocaml
tidren has joined #ocaml
q66_ has joined #ocaml
q66 has quit [Ping timeout: 240 seconds]
tidren has quit [Ping timeout: 240 seconds]
thomasga has joined #ocaml
q66_ has quit [Ping timeout: 240 seconds]
q66_ has joined #ocaml
q66_ is now known as q66
Gonzih has joined #ocaml
Simn has quit [Quit: Leaving]
oriba has quit [Quit: Verlassend]
sad0ur_ is now known as sad0ur
BitPuffin has joined #ocaml
racycle has joined #ocaml
darkf has quit [Quit: Leaving]
Haudegen has quit [Remote host closed the connection]
OnkV has joined #ocaml
typedlambda has quit [Ping timeout: 250 seconds]
tidren has joined #ocaml
tidren has quit [Ping timeout: 264 seconds]
tobiasBora has quit [Read error: No route to host]
tobiasBora has joined #ocaml
englishm1 has joined #ocaml
englishm1 has quit [Read error: Connection reset by peer]
englishm1 has joined #ocaml
englishm has joined #ocaml
englishm has quit [Remote host closed the connection]
englishm1 is now known as englishm
englishm has quit [Changing host]
englishm has joined #ocaml
huza has joined #ocaml
hhugo has quit [Quit: Leaving.]
hhugo has joined #ocaml
racycle has quit [Quit: ZZZzzz…]
fortitUs has joined #ocaml
<fortitUs>
Hi, does anyone know where I can find a full definition of how (<) and other ordering operators from Pervasives work?
<fortitUs>
I'm looking for the weird cases... like:
<Drup>
that might be difficult :/
<fortitUs>
type foo = B of int | A;; A < B 1;; (true)
<Drup>
it's written in the C runtime, by inspecting magically the internal representation ...
<fortitUs>
i see
hhugo has quit [Ping timeout: 240 seconds]
Algebr has joined #ocaml
typedlambda has joined #ocaml
hhugo has joined #ocaml
<Algebr>
There isn't anything stopping me from putting type declarations in a regular .ml right? Is just convention to put them in a .mli?
rishabhjain has joined #ocaml
tane has joined #ocaml
<ggole>
Algebr: you can annotate whatever you like, but the syntax is not the same.
<Algebr>
how can I get this? val uniq : int list -> int list to work in a .ml?
<Drup>
let uniq : ... = fun ...
<ggole>
A pair of .ml/.mli are pretty much treated as struct Foo : sig <contents of .mli> end = struct <contents of .ml> end
<ggole>
...which is parsimonious, but also kind of annoying.
hhugo1 has joined #ocaml
hhugo has quit [Read error: Connection reset by peer]
<tobiasBora>
I woul like to know, what is the proper way to send commands to a shell ? I say the Sys.command : string -> unit; function, but the problem is that the argument could contain special char, such as spaces, and I don't want that it to change the command line.
tani has joined #ocaml
tane has quit [Ping timeout: 250 seconds]
<tobiasBora>
/s/that//
Hannibal_Smith has quit [Quit: Sto andando via]
<tobiasBora>
In the ideal I fould like a function which takes it's parameters in a string like this : command : string list -> unit
<tobiasBora>
Does it exists ?
<ggole>
Unix.create_process, maybe
eikke__ has quit [Ping timeout: 250 seconds]
avsm has joined #ocaml
shinnya has joined #ocaml
BitPuffin has quit [Ping timeout: 245 seconds]
ta`e has joined #ocaml
tani has quit [Ping timeout: 264 seconds]
slash^ has joined #ocaml
eikke__ has joined #ocaml
<tobiasBora>
ggole: Good idea... Does it work under Windows too ?
<Algebr>
How can I parameterize types? type foo a = ..
<ggole>
Unix should work under windows, yeah
<ggole>
type 'a foo = ...
<Algebr>
ah
<tobiasBora>
Ok thank you !
<Algebr>
"Unix should work under windows" sounds funny.
jprakash has joined #ocaml
ta`e has quit [Ping timeout: 250 seconds]
_0xAX has quit [Remote host closed the connection]
mort___ has joined #ocaml
<Algebr>
is code in a .mll a subset of ocaml? or is it its own language?
<Algebr>
or rather, does that even count as code?
omqal has joined #ocaml
<Drup>
it's a weird lex-like language inside which you can put pieces of ocaml code
pjdelport has quit [Quit: Connection closed for inactivity]
tidren has joined #ocaml
<ggole>
See the manual under ocamllex
tobiasBora_ has joined #ocaml
tobiasBora has quit [Ping timeout: 250 seconds]
sgnb has joined #ocaml
tidren has quit [Ping timeout: 240 seconds]
tristero has quit [Quit: tristero]
tristero has joined #ocaml
BitPuffin has joined #ocaml
<Algebr>
silly question, aren't the followig two the same thing? (ie the extra pipe), type foo = | First | Second, or type foo = First | Second
<flux>
yes
<flux>
| before the first constructor is used for nicely aligning the code :)
<flux>
note that if you're using ocamlyacc it uses empty '|' for indicating the empty case
<ggole>
I like the "extra" |, it's more consistent
<ggole>
Makes for easier editing too
englishm1 has joined #ocaml
<ggole>
(When things are on different lines, anyway.)
huza has quit [Quit: WeeChat 0.3.8]
Gonzih has quit [Ping timeout: 250 seconds]
englishm has quit [Ping timeout: 255 seconds]
elfring has joined #ocaml
englishm has joined #ocaml
thomasga has quit [Quit: Leaving.]
englishm1 has quit [Ping timeout: 250 seconds]
tobiasBora__ has joined #ocaml
tobiasBora_ has quit [Ping timeout: 240 seconds]
<Algebr>
So regarding that extra |, is that then the same thing with match foo with | Bar, or match foo with Bar. Is the first bar not actually needed?
<Drup>
yes
cago has quit [Quit: cago]
OnkV is now known as Haudegen
<flux>
"that is correct", 'yes' is a bit ambigious :)
<flux>
(ok, not, it was the answer right)
fortitUs has quit [Ping timeout: 246 seconds]
<Drup>
flux: starting now, I will always answer "indeed", for maximum guessing possibilities :D
<Algebr>
So the code that ocamllex spits out, the .ml, you could in principle write that out by hand, but it would be incredibly tedious?
<Drup>
Indeed. :D
<Algebr>
ha.
<Drup>
Algebr: you never used a parser generator before ?
<Algebr>
no
rand000 has quit [Quit: leaving]
<ggole>
It's a big table-driven affair
<ggole>
Getting all the details right would be very error-prone (if you did it the same way).
<Algebr>
ggole: so when you say tables, you mean in the abstract right? Not necessarily symbol tables/hashtables/sql tables
englishm has quit [Read error: Connection reset by peer]
englishm has joined #ocaml
<ggole>
I mean tables as in arrays that map characters to actions to take
<Algebr>
aren't those usually called like associative arrays?
<ggole>
Well, not when they keys are integral :)
<Drup>
(and characters are pretty much integers)
<ggole>
The char type in OCaml is essentially a byte.
sagotch has quit [Remote host closed the connection]
ygrek has joined #ocaml
tane has joined #ocaml
<mrvn>
except it is a value and takes 4/8 byte.
<flux>
unless you put them in an array
mort___ has left #ocaml [#ocaml]
gal_bolle has quit [Ping timeout: 240 seconds]
<ggole>
In a string: arrays of char are unspecialised
Algebr has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
<Algebr>
What does this mean in the context of a pattern match, Foo(bar) -> //some code
<Algebr>
the Foo(bar) part
<Drup>
same as "Foo bar"
<Algebr>
ah
<mrvn>
extra () can be added around every expression at will
Eyyub has quit [Ping timeout: 256 seconds]
<Algebr>
So if Foo was defined as Foo of string * int, then it would be matched as Foo(bar, har)?
<mrvn>
Algebr: then it must be.
<flux>
yes
<flux>
though it's customary to write it with a space after Foo
angerman has quit [Quit: Bye]
<flux>
there's a succinct difference mrvn was hinting at. Foo of string * int is different from Foo of (string * int)
<flux>
the latter can be matched with (string * int) being a single value, the former must always be deconstructed to two different values as you have done
<mrvn>
That wasn't what I was hinting at.
<flux>
oh :-)
<mrvn>
Foo of string * int must always be written as Foo ("x", 1). The () aren't optional.
<mrvn>
Since constructors only take one argument.
<flux>
in other words Foo of (string * int) can be matches with Foo (a, b) or Foo (a_and_b), but Foo of string * int can only be matched with Foo (a, b), Foo (a_and_b) is an error
<flux>
I think the explanation is the memory layout, personally I consider it a small wart though
<mrvn>
Foo "x", 1 would be (Foo "x"), 1
<Drup>
flux: what annoys me is that, in almost any part of the language, paranthesis are no-op ... except here
<flux>
yep
<Drup>
this is *very* unsatisfactory
<mrvn>
except foer match x with Foo _ ->
<mrvn>
Drup: paranthesis alter precedence. That's what happens here
<Drup>
no, that's not what really happen
<flux>
mrvn, he's refererring to the fact that Foo of string * int and Foo of (string * int) mean a different thing
<mrvn>
Drup: Foo "x", 1 is (Foo "x"), 1. The tupeling , has a lower precedence so you need the ()
<flux>
and there's no precedency there
<Drup>
mrvn: what flux said
<mrvn>
Well, Foo of string * int and Foo of (string * int) simply are different types.
<Drup>
yes, my point precisely.
<flux>
exactly, but the only difference is parenthesis, that don't affect precedency at all
<mrvn>
like string * int list and (string * int) list
philtor_ has quit [Ping timeout: 250 seconds]
<flux>
it's not
<mrvn>
sort of
<flux>
because string * int list is string * (int list)
<flux>
but Foo of string * int is not (Foo of string) * int
<flux>
it's like 5 and (5) meaning different things.
<mrvn>
true
<flux>
it's using the otherwise missing 'tuple operator'
<Drup>
and also, the consequence is completly un-intuitive
<flux>
that magical 'tuple constructor operator' :-)
<mrvn>
like string * int * float vs (string * int) * float
<Drup>
mrvn: except that in this case 1) it's still a precedence thingy 2) it's quite intuitive what's going on.
<ggole>
The syntax is pretty unfortunate
<Algebr>
what's ocaml's documentation mechanism? (preferably something offline), like in ipython I could do, Map.Make?, and that would print out a docstring,
<flux>
it's nice how folks asking for innocent things in #ocaml always cause folks pointing out the dirty corners of ocaml ;-)
<mrvn>
Drup: how is that different from Foo of string * int vs Foo of (string * int)
<Drup>
Algebr: "man Map" in your terminal ;)
tidren has joined #ocaml
<flux>
drup, but sadly mange packages don't install manual pages :(
<Drup>
flux: yep :(
<mrvn>
Drup: Both extra () put the string * int into a seperate box
<flux>
algebr, most often I just look up the .mli file
<flux>
if there's no manual page installed
<Drup>
mrvn: and how is that intuitive for the average ocaml programmer ?
<flux>
failing that I typically find the docs online ;)
<mrvn>
Drup: (a * b) is always a tuple. :)
<Drup>
and "a * b" is the same tuple ... except here
<mrvn>
The toplevel pretty printer is anoying too:
<mrvn>
- : t = Foo ("x", 1)
<mrvn>
Now is that a Foo of (string * int) or Foo of string * int?
<def`>
>_<
Algebr` has joined #ocaml
<Drup>
well, it's easy to know
<Drup>
"let Foo x = Foo ("x", 1);;"
<mrvn>
Same for constructing values. Both types look exactly the same when you use them.
<Drup>
if the compiler yells, it's a Foo fo string * int
<Drup>
(easy, I told you)
<mrvn>
Drup: the compiler doesn't yell.
<mrvn>
# type t = [ `Foo of string * int | `Foo of (string * int) ];;
<mrvn>
type t = [ `Foo of string * int ]
<mrvn>
WTF?
<ggole>
Algebr: there's a tool to generate html pages from formatted comments
<Drup>
sure it does : "Error: The constructor Foo expects 2 argument(s), but is applied here to 1 argument(s)" ;)
philtor_ has joined #ocaml
<ggole>
I don't think the emacs mode comes with something to browse them though
tidren has quit [Ping timeout: 255 seconds]
<mrvn>
Drup: Foo ("x", 1) works for both types. Without () works for neither
<Drup>
mrvn: read my statement more carefully please :p
<Drup>
it's not the right part this issue, it's the left.
<Drup>
the*
Algebr has quit [Ping timeout: 250 seconds]
<Algebr`>
So the , isn't a tuple constructor?
<Drup>
no
<Drup>
you can't do "zip (,)" like in haskell
<ggole>
It's just syntax
<Algebr`>
bah
<ggole>
No sections either
<mrvn>
Can it be that polymorphic variant constructors can't take tuples? type t = [ `Foo of (string * int) ];;
<mrvn>
type t = [ `Foo of string * int ]
<ggole>
Polymorphic variants take one or zero args
<ggole>
Of course the arg can be a tuple
<ggole>
But it's a "real" tuple
<mrvn>
Unlinke real constructors where you have both cases
<ggole>
Yes.
<ggole>
No performance hack.
jsvgoncalves has quit [Remote host closed the connection]
<mrvn>
why?
<ggole>
Dunno.
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
<Algebr`>
Not sure if anyone saw my last question, I lost connection. Any kind of ocaml documentation off line? Like I want to know about Map.Make, (besides reading online)
<Drup>
Algebr`: "man Map"
<Algebr`>
wow, literally haha
<Drup>
that's only for stdlib, though
<Algebr`>
didn't realize it injected libraries into man too
<Drup>
unfortunatly
<Algebr`>
ah
<Drup>
Algebr`: also, you can read mlis installed on your system
<Drup>
(they are usually installed with libraries)
<Algebr`>
mlis are like reading .h s, right?
<ggole>
There should really be a thing in merlin to jump to the ocamldoc-generated html for an identifier
<Drup>
(to see where, you can do "ocamlfind query <library>"
<ggole>
*html doc
<Drup>
and you can read the ocamldoc generated html, indeed, which is the nicer imho
<Algebr`>
where's that at?
<Algebr`>
in some /share?
<ggole>
It's not installed by default (unless that's changed)
<Drup>
it's usually not generated by the library in opam, so you can 1) generate it yourself, usually "make doc" 2) see it online
<ggole>
Does opam support generating the docs for a library/ocaml installation?
<Drup>
yes, there is a build-doc field
<Drup>
and "opam install -d" to build doc
<def`>
ggole: if there is a more "integrated" way to manage doc, then we'll work on this
<ggole>
Ah, hmm
<Drup>
cmt ! cmt ! \o/
<ggole>
Ideally you would mash C-c d and if the docs weren't there, it would say "Documentation for package P missing, ask opam to generate it? y/n"
<Algebr`>
getting confused about seeing the module Map being called a functor?
<ggole>
Might be a bit much to ask
<Algebr`>
Not like haskell functor?
<ggole>
Functors are functions from structures to structures
<Drup>
Algebr`: not like haskell functor, indeed
<mrvn>
like ocaml functor
<Algebr`>
mrvn: lol
<Algebr`>
ggole: and structures means modules?
<Algebr`>
or something more general
<Drup>
yeah
<ggole>
The Map functor takes an argument describing a comparison op and produces an implementation
<ggole>
Like type classes, but explicit
<mrvn>
Now that modules are first class do we even need functors?
<Drup>
mrvn: yes, because functor application is compile time
<ggole>
First class modules can't escape
<ggole>
Well, that's not quite right. But there are some restrictions.
<Algebr`>
functor is such an overloaded word.
<mrvn>
Drup: optimization
<ggole>
Algebr`: Prolog and C++ also use it for different things
<Drup>
mrvn: you're very welcome to write it
elfring has quit [Quit: Konversation terminated!]
<mrvn>
Drup: that's basically just inlining the module parameter
tobiasBora__ has quit [Ping timeout: 240 seconds]
<Drup>
as I said, you're very welcome to write it.
<Algebr`>
so when add something to a Map, is it mutating the map or giving me a new map with the additional item?
<Drup>
Algebr`: new one
<mrvn>
Drup: I ment I don't need to write it. I just have to increase the inlining limit :)
<ggole>
Hashtbl is the mutable one
<Drup>
mrvn: no, it's not enough
<Algebr`>
Drup: and then presumably immediately garbage collecting the last one
<Drup>
Algebr`: hell no, it's shared
<mrvn>
Algebr`: in the standard lib the functors give you functional data structures
<Algebr`>
wat
<Algebr`>
why shared
<ggole>
Because it's faster to not create new structure
<Drup>
Algebr`: if you do "let l = [ 1 ; 2 ; 3 ] ;; let l' = 0 :: l ;;"
<mrvn>
Algebr`: a Map.add only changes a few elements in the map. Everything unchanged is shared.
<Drup>
is l garbage collected ?
<Drup>
no, it's shared
<Drup>
with l'
<Drup>
map is exactly the same
<mrvn>
The old map probably gets collected soon but most of it will remain alive through the new map.
Gonzih has joined #ocaml
thomasga has quit [Quit: Leaving.]
racycle has joined #ocaml
teiresias has quit [Quit: BBL]
thomasga has joined #ocaml
omqal has quit [Ping timeout: 240 seconds]
emias has quit [Quit: Reboot.]
anna_ has joined #ocaml
thomasga has quit [Ping timeout: 250 seconds]
anna_ has quit [Quit: Leaving]
omqal has joined #ocaml
sgnb has quit [Read error: Connection reset by peer]
englishm1 has joined #ocaml
englishm has quit [Read error: Connection reset by peer]
ollehar has joined #ocaml
Algebr` has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
philtor_ has quit [Ping timeout: 264 seconds]
omqal has quit [Ping timeout: 250 seconds]
tidren has joined #ocaml
jwatzman|work has joined #ocaml
jwatzman|work has quit [Client Quit]
jwatzman|work has joined #ocaml
jprakash has quit [Ping timeout: 240 seconds]
BitPuffin has quit [Quit: See you on the dark side of the moon!]
BitPuffin has joined #ocaml
tidren has quit [Ping timeout: 240 seconds]
thomasga has joined #ocaml
enquora has joined #ocaml
teiresias has joined #ocaml
teiresias has quit [Changing host]
teiresias has joined #ocaml
thomasga has quit [Client Quit]
englishm1 has quit [Quit: Leaving.]
<enquora>
considering switching to ocaml for several cross-platform libraries and need feedback, if possible, on likely issues. Libraries need to be used in browser, on 'nix servers and iOS. Is it possible to comment in general on difficulty of targetting javascript + native binary formats? How mature is javascript targetting for ocaml?
<whitequark>
quite mature
<whitequark>
I would anticipate most problems with iOS, as currently it needs a custom buildscript and I think a mildly patched compiler
<enquora>
it may be sufficient to use javascript library on ios
<whitequark>
then you're good
<enquora>
I'm more worried about library packaging, and calling conventions from the different host environments - browser, python, lua, erlang
thomasga has joined #ocaml
<whitequark>
you'll have to package it yourself, of course
<enquora>
yes. no experience with ocaml toolchain, so I don't know what I would need to work with
<whitequark>
you'd basically invoke ocamlopt -output-obj and get a single .o file
<enquora>
I've run across an llvm backend while googling, but this appears to have been a proof-of-concept or abandoned project. is that correct?
<whitequark>
llvm backend would not have helped you.
tidren has quit [Ping timeout: 264 seconds]
<enquora>
most difficult part I'm anticipating. Library is for custom PDF generation - layout needs constraint solving, like http://en.wikipedia.org/wiki/Cassowary_(software). Anything robust like this in the ocaml world?
AltGr has left #ocaml [#ocaml]
_0xAX has joined #ocaml
<Drup>
for pdf, you have various libraries, camlpdf in particular. Never used them, but they exists since quite some time and should be stable.
Kakadu has quit [Quit: Page closed]
<Drup>
for constraint solving .. do you need that in the javascript side ?
mort___ has joined #ocaml
<Drup>
if not, I would just use a binding for one of the lp engine
<Drup>
ocaml-glpk uses an outdated interface, so it's usable with some previous version of glpk, but not the last one. It should be possible to update it, but it needs some effort
<enquora>
Drup: we need to control table and table column widths in the pdf based on allowable maximum and minumum font sizes, word spacing and a few other typographic parameters
<enquora>
we produce very information-dense engineering reports that need tight typographic control to maintain readability
thomasga has quit [Quit: Leaving.]
<enquora>
and the content is highly variable
<Drup>
Never used the pdf libraries, so can't help you with that
<enquora>
No PDF library exists which is itself suitable for this purpose
jprakash has joined #ocaml
<enquora>
we may use an existing library for PDF primitives, but it isn't all that difficult to work at the raw PDF level
q66 has quit [Quit: Leaving]
<Drup>
Not sure what your question is, then :p
q66 has joined #ocaml
<enquora>
don't want to write constraint solver myself ;-)
<enquora>
if it can be avoided
<enquora>
have considered clojurescript to be the leading candidate language until recently, and the constraint solving is no problem there
<enquora>
but have been engaged by several recent posts on ocaml, and there are advantages to it
<Drup>
as I said, do you want the constraint solving to be compilable to javascript or not ?
<whitequark>
I found a page which refers to some mantis setup
thomasga has joined #ocaml
englishm has joined #ocaml
<Drup>
ah, yeah, it's outdated
<Drup>
I think.
thomasga has quit [Client Quit]
<tane>
patoline looks cool :)
<enquora>
is the 'objection' to camlimages based on packaging issues, or do they seem like a canary in coal mine for deeper code structure and quality?
<Drup>
enquora: it's also outdated wrt to underlying C libs
<Drup>
gif_lib, to be precise
<Drup>
and the maintaner is .. not very reactive about it, even if a patch is provided, which is annoying.
<enquora>
un-maintained, in otherwords
<whitequark>
un-maintainer?
<enquora>
reading the patoline docs now - "Camlimages is a great image library, Patoline depends on it for reading external images. Therefore, it is possible that all documents will not compile the same on all systems, depending on the C libraries installed." lol
<Drup>
well, seems like you will have a motivation to implement a pure ocaml version then :]
<enquora>
an aside - is darcs the most popular version control system in the ocaml world? I was dragged along with the git undertow when it appeared and haven't used darcs since, but miss it
<Drup>
not really
<Drup>
patoline happen to used it, that's all
<Drup>
the compiler uses svn + a git mirror
<Drup>
a good amount of library are on github or the ocaml forge (which provides most cvs I think)
<Drup>
ocsigen used to be on darcs, but we moved to github for social and advertising reasons
<Drup>
(and it has been quite profitable)
zarul[afk] has quit [Ping timeout: 240 seconds]
shinnya has quit [Ping timeout: 255 seconds]
<enquora>
is anyone here using ocaml for a non-trivial html + javascript application? if so, how is the presentation layer handled?
<Drup>
enquora: add the ocsigen project to your week-end reading list
_0xAX has quit [Quit: Leaving]
<enquora>
by html + javascript, I mean a standalone, fully-distributed app capable of running offline. The osigen docs seem to suggest that it's not that?
<Drup>
it has been successfully used like that
<enquora>
k, i do see references to reactive DOM management
Kakadu has joined #ocaml
tane has quit [Quit: Verlassend]
thomasga has joined #ocaml
dsheets has quit [Ping timeout: 250 seconds]
zarul has joined #ocaml
avsm1 has joined #ocaml
thomasga has quit [Quit: Leaving.]
Hetu has joined #ocaml
avsm has quit [Ping timeout: 240 seconds]
waneck_ has joined #ocaml
zarul has quit [Ping timeout: 240 seconds]
waneck has quit [Ping timeout: 240 seconds]
so has joined #ocaml
<Drup>
whitequark: did you see my question on ppx_deriving from yesterday ?
<whitequark>
Drup: about dynlink? I think I answered it
Gonzih has joined #ocaml
<Drup>
oh indeed, it was not in my backlog
avsm1 has quit [Quit: Leaving.]
<whitequark>
so have you found the answer?
<Drup>
yeah
<Drup>
the "avoid a situation where you have silently ignored annotations" makes sens
Thooms has joined #ocaml
<whitequark>
I agree that Dynlink can be seen as somewhat heavyweight for that purpose
<whitequark>
but I still like it more
thomasga has joined #ocaml
<Drup>
(my idea was "just ignore @@deriving if you don't know the thing that follows and let an eventual other deriving library handle it", but as you said, the silent ignoring might be confusing for the user)
<Drup>
How would you go at having a deriving library with a runtime component then ? creates the ppx deriving library, a runtime library that depends on "ppx_deriving" and let it dynlink the ppx part ?
<whitequark>
ppx_deriving would also enforce uniform syntax
<whitequark>
I don't understand your proposal
zarul has joined #ocaml
<Drup>
how would you design a ppx that needs a runtime part ?
thomasga has quit [Quit: Leaving.]
<Drup>
(the ocamlfind design, I mean)
<whitequark>
oh!
<Drup>
I'm not very experience with Dynlink, so not sure how it would work
<Drup>
+d
<whitequark>
you'd need to require the runtime component separately
<whitequark>
and manually
<Drup>
(I'm writing the Eq deriving, just to try things out, and I wanted to provide specialized eq for the base data types in a runtime library, instead of redefining them)
<whitequark>
hmmm
<Drup>
that's annoying
<whitequark>
yes
<whitequark>
but compare with the separate design: you always need to require the runtime component, and, in case of OASIS, write XMETARequires:
<whitequark>
err to require all components explicitly
<Drup>
true
<whitequark>
talking about Eq, I would provide specialized equality functions in the generated code, so that they will be inlined
<Drup>
you mean, copy them everytime I see a base type ?
<whitequark>
yes
<whitequark>
that's what I use for Show, essentially
<Drup>
hmm
<Drup>
I don't think it would help that much for inlining
<Drup>
(assuming cmxFOO, of course)
ygrek has quit [Ping timeout: 245 seconds]
<whitequark>
I did it mainly for simplicity, i.e. avoidance of a runtime component
<whitequark>
I see how it could in principle bloat code, but I'd rather solve that problem when it appears
<Drup>
yeah, that why I wanted the runtime part originally
<whitequark>
I really think it's premature optimization at this point
FreeArtMan has joined #ocaml
<whitequark>
especially for Eq, with tiny bodies
<Drup>
and also, some ppx will need a runtime part anyway, so better solve the problem early
<whitequark>
well, it has a solution, I just told it to you
<Drup>
yep
<whitequark>
I don't think there is a better one.
Averell has quit [*.net *.split]
inr has quit [*.net *.split]
def` has quit [*.net *.split]
hyPiRion has quit [*.net *.split]
dmbaturin has quit [*.net *.split]
hbar has quit [*.net *.split]
esden has quit [*.net *.split]
<Drup>
(also, I'm not sure how I feel about the findlib name guessing based on the deriving used)
hbar has joined #ocaml
Averell has joined #ocaml
<whitequark>
why not?
<Drup>
slightly too implicit for my tastes, you don't see the dependency in the command line/oasis/whatever description
dmbaturin has joined #ocaml
esden has joined #ocaml
<whitequark>
hrm.
<whitequark>
well, you have to guess the path/name of dynlink plugin *somehow*
<Drup>
oh yeah, with dynlink, you don't have the choice :p
divyansr__ has joined #ocaml
<whitequark>
if OASIS was not crap, it'd be possible to use something like -ppxopt 'deriving,show,eq'
<Drup>
:D
<whitequark>
maybe I could add a ppxopt field to findlib
<whitequark>
yes, that may be a great idea
<Drup>
to findlib ? that sounds weird
<whitequark>
it's really not, it already has that for camlp4
<Drup>
(and how would that help ? It doesn't seems to be a findlib issue)
<whitequark>
it's a dependency discovery issue.
<Drup>
how would you use it here ?
<whitequark>
basically I want an entry in BuildDepends: to effect something else except adding -ppx option
<whitequark>
I really want it to pass an option to the -ppx ppx_deriving invocation
<Drup>
so you would create a ppx_deriving_show that would contain no code but would add the option --ppxopt "show" to ppx_deriving ?
BitPuffin has quit [Ping timeout: 240 seconds]
<whitequark>
more like @ppx_deriving_show/ppx_deriving_show.cmo
<whitequark>
but yes
<whitequark>
it would pass an equivalent of -ppxopt ppx_deriving,@ppx_deriving_show/ppx_deriving_show.cmo to the ocamlfind c invocations
<whitequark>
I actually already have that mechanism in place for testing
<Drup>
one advantage I see is that one package could define multiple deriving
<Drup>
(and the dependency would be explicit too)
<Drup>
it's slightly convoluted, though
<whitequark>
know a better option?
Gonzih has quit [Ping timeout: 240 seconds]
<Drup>
not with the Dynlink thingy
ygrek has joined #ocaml
<Drup>
you will probably need to provide a way to statically compile a ppx with all the various library statically linked, I'm sure some big project will want that, to avoid dynlink around at each ppx invocation
mort___ has quit [Quit: Leaving.]
<whitequark>
I don't really see a problem with Dynlink.
Hannibal_Smith has joined #ocaml
<Drup>
is it available everywhere ?
<whitequark>
probably not
<whitequark>
but the right way to fix that is to make it available.
<whitequark>
I don't believe there is a hosted platform where OCaml runs which doesn't have dlopen().
<Drup>
(my remark has more to do with #mustbuildfaster, I'm sure someone will want that, even if I personnaly care only midly)
Simn has joined #ocaml
<whitequark>
it's not slow on non-Windows, and even Alain doesn't know how slow exactly it is on Windows
<Drup>
x)
<Hannibal_Smith>
Someone has benchmarked SML code compiled with MLton vs same code ported to Ocaml?
<Drup>
probably MLton people
nirvdrum has joined #ocaml
BitPuffin has joined #ocaml
alpounet has quit [Remote host closed the connection]
alpounet has joined #ocaml
<nirvdrum>
Hi. I'm on Ubuntu 14.04 and seem to be having a lot of trouble getting camlp4 to install anything useful. It looks like for 4.01.0 the package doesn't install anything, but other packages rely on the camlp4o binary. Am I just going about this wrong?
<Drup>
camlp4 is packaged separately on debian-based systems.
<Drup>
probably in a package called "camlp4" or something
<nirvdrum>
Okay. I tried that too, but it looked the various packages were expecting something else as well. I'll dig into that more.
<nirvdrum>
Thanks.
FreeArtMan has quit [Remote host closed the connection]
alpounet has quit [Ping timeout: 256 seconds]
mort___ has joined #ocaml
<Drup>
You're not the first one to stumble upon this one
<nirvdrum>
Well, once I started hitting stuff like: W: Field 'pkg_camlp4_extend' is not set: Command ''/home/nirvdrum/.opam/system/bin/ocamlfind' query -format %d camlp4.extend > '/tmp/oasis-835ffa.txt'' terminated with error code 2
<nirvdrum>
I figured maybe the package managed version wasn't right either.
<nirvdrum>
It looks like ocamlfind doesn't know about the system-installed stuff. I'll peck away at that.
<Hannibal_Smith>
This is the only "updated" thing that I found on the argument
<Drup>
considering that the author is not in the ocaml community anymore (and is very happy to remind it to everyone), It's probably outdated too ;)
<Hannibal_Smith>
I read some of its blog post some times ago, seems like that he migrated to F#
<Hannibal_Smith>
Sorry, my english is terrible
englishm has quit [Quit: Leaving.]
martintrojer has joined #ocaml
hhugo has joined #ocaml
<nirvdrum>
Ahh. I need to install the system ocaml-findlib package. But installing core also install ocamlfind. The system one knows about the system camlp4, the one installed from opam does not. Looks like I just need to get creative with my PATH.
<Drup>
nirvdrum: alternative solution, just throw away the system compiler and use an opam installed one with "opam switch 4.01.0"
<Unhammer>
(I know I should use opam and such, but I prefer to not depend on too much stuff that can't be apt-getted when I'm writing stuff that my boss has to install =P)
Hetu has quit [Ping timeout: 256 seconds]
hhugo has quit [Quit: Leaving.]
q66 has quit [Quit: Leaving]
q66 has joined #ocaml
Gonzih has quit [Ping timeout: 255 seconds]
ivan\ has joined #ocaml
so has joined #ocaml
Hannibal_Smith has quit [Quit: Sto andando via]
alpounet has joined #ocaml
Simn has quit [Quit: Leaving]
axiles has quit [Remote host closed the connection]