<riaqn>
Hello, I 'm trying to install tuareg in emacs via ELPA, but it tells me "caml-3.12.0.1 is not available", anyone knows what happened?
<riaqn>
caml is a requirement of tuareg, and it's not in my 'list-package'
<Drup>
It is recommended to install tuareg with opam, not ELPA.
<riaqn>
Drup: I 'll try that, but still wonder why ELPA is not working..
<pierpa>
it worked for me. Why it should require opam
<riaqn>
pierpa: could you please tell me in which elpa repository can I find the 'caml-3.12.0.1'?
<riaqn>
currently I only have melpa-stabe.
<pierpa>
hmmm
seangrove has quit [Ping timeout: 276 seconds]
<pierpa>
no, I don't know
<riaqn>
pierpa: hmm..You can run list-package in emacs and see where 'caml' locates.
<riaqn>
pierpa: if it's convenient for you
<pierpa>
yes, that's what I'm doing right now
<pierpa>
I dont remember how I did exactly
<pierpa>
have tried installing separately the caml package and then tuareg?
<riaqn>
OK, then I guess I have to install tuareg by the package managers of my linux.
<pierpa>
*have you tried installing separately the caml package and then tuareg?
<riaqn>
yes, that 's my current situation. why I installed ocaml, the caml-mode for emacs was installed too, but not tuareg.
ousado_ is now known as ousado
<riaqn>
so now I 'm going to install tuareg by packages managers of my distribution.
ousado has quit [Changing host]
ousado has joined #ocaml
<pierpa>
btw, you don't need no fancy installer for installing these things, you just need a tarball wherewer you get it from, unpack it, compile the files, maybe read the comments in the main file
<riaqn>
yeah, but managed packages provides the benefits of updating.
<pierpa>
hmmm
silver has quit [Read error: Connection reset by peer]
yunxing has quit [Remote host closed the connection]
Kakadu has quit [Remote host closed the connection]
yunxing has joined #ocaml
yunxing has quit [Read error: Connection reset by peer]
yunxing has joined #ocaml
sh0t has quit [Ping timeout: 250 seconds]
seangrove has joined #ocaml
aantron has joined #ocaml
hunteriam has joined #ocaml
shinnya has quit [Ping timeout: 250 seconds]
jeffmo has quit [Quit: jeffmo]
GeorgeHahn has joined #ocaml
tennix has quit [Ping timeout: 260 seconds]
aantron has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
riaqn has left #ocaml ["ERC (IRC client for Emacs 24.5.1)"]
<yminsky>
I'm curious if anyone on the list has tried out opam-user-setup?
<yminsky>
I just played with it a bit, and it looks pretty promising.
<yminsky>
doing "opam install tuareg ocp-indent merlin utop user-setup" gets you pretty far in terms of having a solid tooling setup, I think.
sgnb`` has joined #ocaml
<yminsky>
Well, pretty good. Auto-completion doesn't appear to work for Merlin....
<Drup>
yminsky: I use it
<yminsky>
Cool. How has your luck been with it?
<Drup>
Installed it, PR to fix the obvious bug, then didn't really touched it, since the setup was done :p
<yminsky>
Hah!
<yminsky>
Did you use it for vim or emacs?
<Drup>
emacs
<Drup>
with basically everything enabled
sgnb` has quit [Ping timeout: 276 seconds]
<Drup>
(plus some custom more, that I should probably backport to opam-user-setup, in fact)
douglasc_ has joined #ocaml
douglasc_ has quit [Remote host closed the connection]
<def`>
yminsky: maybe it is not installing or enabling emacs packages (auto-complet &/| company-mode)
OnkV has joined #ocaml
damason_afk has joined #ocaml
maufred_ has joined #ocaml
jrslepak_ has joined #ocaml
lukky513_ has joined #ocaml
djellemah_ has joined #ocaml
systmkor_ has joined #ocaml
truncate has quit [Ping timeout: 248 seconds]
maufred has quit [Ping timeout: 248 seconds]
jrslepak has quit [Ping timeout: 248 seconds]
douglascorrea has quit [Ping timeout: 248 seconds]
damason has quit [Ping timeout: 248 seconds]
nicoo has quit [Ping timeout: 248 seconds]
djellemah has quit [Ping timeout: 248 seconds]
Johann has quit [Ping timeout: 248 seconds]
lukky513 has quit [Ping timeout: 248 seconds]
systmkor has quit [Ping timeout: 248 seconds]
Haudegen has quit [Ping timeout: 248 seconds]
<yminsky>
def`: I suspect something like that. Playing around.
truncate has joined #ocaml
<yminsky>
I'm trying to figure out how to get merlin to prefer company mode...
nicoo has joined #ocaml
Johann has joined #ocaml
seangrove has quit [Remote host closed the connection]
seangrove has joined #ocaml
yunxing has quit [Remote host closed the connection]
struk|desk|away is now known as struk|desk
aantron has joined #ocaml
<struk|desk>
yminsky: re: your article on inline records - do they work w/polymorphic variant types or just variants?
<yminsky>
Ordinary variants only.
<struk|desk>
dang, is there a particular strong reason to not support polymorphic variants too?
<aantron>
it probably has something to do with the scoping of the labels?
<yminsky>
Ordinary variants are nominal, and I think this only really makes sense for nominal types. Polymorphic variants are structural.
<yminsky>
struk|desk: do you know what nominal vs structural means in this conext?
<struk|desk>
no, I do not
<yminsky>
A nominal type is one that has a unique identity. So, for example, this type is structural: type z = int * int
<yminsky>
But this type is nominal: type w = { foo:int; bar:string }
<yminsky>
Meaning, if I create another type like z, say, "type z1 = int * int", then z and z1 are the same, because only the structure matters.
<yminsky>
But if I create another w-like type, "type w1 = {foo:int; bar:string}", w1 and w are different.
<struk|desk>
I get it. ok, and polymorphic variants, mostly due to their scope, must be structural
<yminsky>
If you put inline records into polymorphic variants, I think it would make the way one compares structures of different polymorphic variants more complicated.
<yminsky>
This is all guesswork, though. I don't really know the reason.
<yminsky>
But anyway, my broad recommendation is to mostly avoid polymorphic variants.
<yminsky>
They're a lot worse for catching errors in your code anyway. If you're using them for something complicated enough to benefit from inline records, you're probably better off with ordinary variants.
kansi has joined #ocaml
tennix has joined #ocaml
<struk|desk>
the idea honestly came from just inline records, sans variants. sometimes I just want to return a list of label:value pairs, without bothering to define a record, but perhaps that is just laziness
<struk|desk>
I suppose the same can be achieved with poly variants if you return a tuple of them, each with their corresponding values bound to them.
<struk|desk>
exactly
<yminsky>
Anonymous records would be nice, but sadly, aren't a thing. I generally just define record types when I have multi-argument returns that really need names.
<struk|desk>
like if it's a few floating pooint values, rather needs to be named for clarity
<yminsky>
Objects are another natural encoding for this, but again, I think more trouble than it's worth.
<struk|desk>
you mean create anonymous object with fields ?
<yminsky>
Yeah, I think just defining another record purely for the purpose of returning multiple values is the right way to go. Now that OCaml does constructor disambiguation, the syntactic overhead is very low.
<yminsky>
(Yes, anonymous objects with fields.)
darkf has joined #ocaml
<struk|desk>
ok, cool. I just define records purely for returning multiple values, guess I'll stick to that pattern. Thanks for your input and advice!
<def`>
you can return a polymorphic variant with a singlencase
<struk|desk>
yeah but they can't be matched on as easily in a tuple like it would with recrods
<def`>
val foo : unit -> [`Bar of int]
<struk|desk>
sure, but what about, say 3 fields?
<struk|desk>
then you need to match in same order on some structure holding them
<def`>
let `Bar bar, `Baz baz = f()
<struk|desk>
I guess it's not that bad. hm
<def`>
or CPS with labels
<def`>
f args @@ fun ~baz ~bar -> ...
<yminsky>
Ugh. I still think declaring a record type just isn't that bad.
<struk|desk>
yeah I am sticking with records but I might play with the object approach on a toy project to see how it plays it
<def`>
anyway, no solution is really satisfying, there is a unpleasant asymetry between labelled arguments
<def`>
and single bameless returns
<def`>
namekess*
<def`>
pfff... from my phone sorry.
struktured has joined #ocaml
<yminsky>
Hah!
<yminsky>
Yeah, I agree there is something missing here.
spacekitteh has joined #ocaml
<spacekitteh>
how can i add a breakpoint in ocamldebug to a .cmo file before i run the main executable?
gbarboza has quit [Ping timeout: 260 seconds]
_whitelogger_ has joined #ocaml
_whitelogger has quit [Ping timeout: 260 seconds]
tg has quit [Ping timeout: 260 seconds]
al-maisan has joined #ocaml
Drup has joined #ocaml
spion_ has joined #ocaml
tg has joined #ocaml
tg has quit [Excess Flood]
struk|desk is now known as struk|desk|away
<struktured>
spacekitteh: think I figured it out, maybe. compile with "-g" (debug symbols), if possible. "ocamldebug my_ocaml_executable" , then "break My_ocaml_executable.name_of_function" and "r"
<struktured>
(that's for top level function, for other modules, just apply a similar pattern,)
tg has joined #ocaml
tg has quit [Excess Flood]
<struktured>
ocamldebug seriously needs a facelift, or maybe I shouldn't be using it. tab completion of commands and ocaml in state symbols would be nice
tg has joined #ocaml
tg has quit [Excess Flood]
tg has joined #ocaml
tg has quit [Excess Flood]
<spacekitteh>
i'm trying to debug a coq plugin, god help me
tg has joined #ocaml
tg has quit [Excess Flood]
tg has joined #ocaml
tg has quit [Excess Flood]
tg has joined #ocaml
tg has quit [Excess Flood]
tg has joined #ocaml
tg has quit [Excess Flood]
tg has joined #ocaml
tg has quit [Excess Flood]
tg has joined #ocaml
tg has joined #ocaml
tg has quit [Excess Flood]
nicoo has joined #ocaml
douglascorrea has joined #ocaml
gbarboza has joined #ocaml
douglascorrea has quit [Remote host closed the connection]
hunteriam has quit [Quit: Connection closed for inactivity]
TheAuGingembre has joined #ocaml
zapu has joined #ocaml
struktured has quit [Ping timeout: 260 seconds]
srcerer_ is now known as srcerer
Algebr has joined #ocaml
def`_ is now known as def`
theblatte has quit [Ping timeout: 260 seconds]
seangrove has quit [Ping timeout: 264 seconds]
riaqn has joined #ocaml
johnelse has quit [Ping timeout: 260 seconds]
theblatte has joined #ocaml
aantron has quit [Remote host closed the connection]
keep_learning has joined #ocaml
johnelse has joined #ocaml
<spacekitteh>
i can't add the breakpoint before i start running the program, because the plugin hasn't even loaded yet
aantron has joined #ocaml
gbarboza has quit [Ping timeout: 246 seconds]
larhat has quit [Quit: Leaving.]
douglascorrea has joined #ocaml
ygrek has quit [Ping timeout: 246 seconds]
douglascorrea has quit [Ping timeout: 260 seconds]
gbarboza has joined #ocaml
yunxing has joined #ocaml
seangrove has joined #ocaml
seangrove has quit [Ping timeout: 248 seconds]
myst|fon has quit [Quit: Connection closed for inactivity]
djellemah_ is now known as djellemah
rwmjones has quit [Ping timeout: 260 seconds]
rwmjones has joined #ocaml
Sorella has quit [Quit: Connection closed for inactivity]
MercurialAlchemi has joined #ocaml
Algebr has quit [Remote host closed the connection]
Algebr has joined #ocaml
_whitelogger_ has quit [Excess Flood]
_whitelogger has joined #ocaml
rwmjones has quit [Ping timeout: 268 seconds]
rwmjones has joined #ocaml
malc_ has joined #ocaml
GeorgeHahn has quit [Read error: Connection reset by peer]
<asdf12z_>
so any function that takes multiple arguments can be a curry function??
Muzer has quit [Read error: Connection reset by peer]
riaqn has left #ocaml ["ERC (IRC client for Emacs 24.5.1)"]
<keep_learning>
Hello everyone
<keep_learning>
I have written a small code to factor numbers
copy` has quit [Quit: Connection closed for inactivity]
tg has joined #ocaml
tg has quit [Excess Flood]
larhat has joined #ocaml
tg has joined #ocaml
tg has quit [Excess Flood]
<sspi>
so, I'm playing with the effects branch - but I'm a bit stuck
<sspi>
I'm not sure how I should handle time based scheduling
tg has joined #ocaml
tg has quit [Excess Flood]
tg has joined #ocaml
tg has quit [Excess Flood]
freehck has joined #ocaml
tg has joined #ocaml
tg has quit [Excess Flood]
kushal has joined #ocaml
tg has joined #ocaml
tg has quit [Excess Flood]
tg has joined #ocaml
tg has quit [Excess Flood]
Algebr has joined #ocaml
butts_butts has joined #ocaml
slicefd has joined #ocaml
Simn has joined #ocaml
gbarboza has quit [Ping timeout: 268 seconds]
Haudegen has joined #ocaml
FreeBird_ has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 276 seconds]
seangrove has joined #ocaml
pierpa has quit [Ping timeout: 264 seconds]
butts_butts has quit [Ping timeout: 244 seconds]
_whitelogger has quit [Excess Flood]
_whitelogger has joined #ocaml
gbarboza has joined #ocaml
_whitelogger has quit [Excess Flood]
_whitelogger has joined #ocaml
companion_square is now known as companion_cube
Algebr has quit [Read error: Connection reset by peer]
Algebr has joined #ocaml
Cypi_ is now known as Cypi
douglascorrea has joined #ocaml
AlexRussia has quit [Ping timeout: 240 seconds]
douglascorrea has quit [Ping timeout: 250 seconds]
ontologiae has joined #ocaml
ia0_ has quit [Quit: reboot]
ia0 has joined #ocaml
kushal has quit [Quit: Leaving]
Algebr has quit [Ping timeout: 246 seconds]
Anarchos has joined #ocaml
sz0 has quit [Quit: Bye.]
antkong has joined #ocaml
jwatzman|work has joined #ocaml
butts_butts has joined #ocaml
kushal has joined #ocaml
<malc_>
infinity0: it basically means that you've paid money for your SMP system to only utilize one (or, more general, be a the mercy of sw scheduler)
<infinity0>
so lwt calls itself a "A cooperative threads library for OCaml" does anyone know what "cooperative" means
<Drup>
I have yet to see anyone pay a single cent for Lwt
<malc_>
I on the other hand am yet to see how it's related to my remark
<infinity0>
so in this context it means there is no scheduler in lwt
<Drup>
Sure there is a scheduler
<infinity0>
malc_: i guess he was taking "paid money" literally
<malc_>
oh there is... at least i assume there should be
larhat has quit [Quit: Leaving.]
<malc_>
infinity0: uhmm... i did mean literally, unless there's a free distribution of SMP systems somewhere (note - not Lwt) ... sign me in
<infinity0>
oh ok, wrong phrasing, i suppose it's the equivalent of that InterruptedExceptions don't happen
octachron has joined #ocaml
douglascorrea has joined #ocaml
<infinity0>
does anyone know off the top of their head, whether (t >>= f) executes f immediately after t completes (excluding other f' than might have been passed to t >>=) or could other things happen before f is executed?
<infinity0>
e.g. the sematics for Deferred.add_callback in python is the former, whereas JS's Promises have the latter semantics (the execution is merely "scheduled" to happen immediately in the next tick)
<Drup>
In Lwt; is t is already done, f is executed immediately. In Async, it yields regardless of the state of t
<infinity0>
ah ok thanks
<Drup>
If t is not done, though, it yields in both cases
<infinity0>
oh ok. but when t later becomes done, does it then execute f immediately or does it yield?
<Drup>
Pretty sure it's the later
douglascorrea has left #ocaml [#ocaml]
<Drup>
(Imagine if several things depends on t, one of the has to go first ...)
<Drup>
them
<infinity0>
yeah, that's why i mentioned "excluding other f' that miht have been passed to t >>=" before
<infinity0>
if several things depend on t, one has to go first, but we could guarantee that all of them collectively are executed immediately after t, and nothing else is
yunxing has quit [Remote host closed the connection]
<Drup>
It's not a great garantee to provide, in practice
<infinity0>
which is still a decent guarantee, especially if you know you're the only one that ever held a reference to t
<Drup>
fairness is more important
Kakadu has joined #ocaml
<infinity0>
this is in practise, i had to fudge extra complexity onto a JS program i wrote because it couldn't provide me that guarantee, whereas the python was simpler
<infinity0>
suppose you have receive-handler that executes for every packet, and you want to perform some async operations on it. if you can't provide that guarantee, then the receive handler for the next packet might fire before you finish all the async-operation callbacks
<infinity0>
but ideally you would finish processing each packet, in order, before starting processing for the next one
hxegon has quit [Quit: BRB]
<Drup>
You could provide that garantee with a stream
octachron has quit [Ping timeout: 264 seconds]
warp has joined #ocaml
warp has quit [Client Quit]
<infinity0>
Drup: er ok, maybe i'm not setting the stage clearly enough here
<infinity0>
i have a long-running process over several incoming packets, whose result is represented by t; and i have a bunch of callbacks {f} on t
<infinity0>
separately, there's a receive handler (which could be refactored into a loop that reads a stream i guess)
<infinity0>
part of the receive logic is to identify the final packet of the long-running operation, and then terminate t with success
<infinity0>
i'd like {f} to be guaranteed to be fired, before the next packet is processed
<Drup>
As I said, use a stream and Lwt_stream.iter_s
<Drup>
(_s as "sequential")
warp has joined #ocaml
<Anarchos>
Peut-être hors sujet, mais il ya un langage de programmation basé sur la logique linéaire ?
<infinity0>
Drup: but I still need something like Lwt to represent the long-running operation, which exists separately from the stream
octachron has joined #ocaml
<malc_>
Anarchos: agda? mercury?
<Drup>
infinity0: I don't see how that's an issue
<companion_cube>
agda has linear types?
kansi has quit [Read error: Connection reset by peer]
<Drup>
infinity0: I need a synthetic code example to see the problem
<malc_>
companion_cube: dependent ones, my bad
<infinity0>
yeah i think i will have to revisit this later, it's a little too complex to explain exactly precisely without context
Anarchos has quit [Ping timeout: 252 seconds]
<infinity0>
each packet may or may not trigger the separate long-running operation to be completed, and when that happens i'd like a guarantee that previous callbacks i added to the long-running operation be run, *before* the next packet is handled
<infinity0>
i wouldn't expect Lwt_stream to know about that long-running operation, to be able to serialise its calls in iter_s
<Anarchos>
isn't agda based on homotopy type theory instead of linear logic ?
_2can_ is now known as _2can
silver has joined #ocaml
<infinity0>
Drup: perhaps i can use Lwt.join to specifically wait for the long-running operation, will try that. i overlooked that earlier probably because it's impossible in JS. thanks for the pointers
<infinity0>
though that does raise the question of what js_of_ocaml translates Lwt.join into... hopefully not a busy loop heh
kushal has quit [Read error: Connection reset by peer]
gbarboza has quit [Ping timeout: 244 seconds]
dhil has joined #ocaml
<rks`>
Anarchos: I though akta was a lazy pure language
<rks`>
so I don't understand what you mean
dmbaturin_ is now known as dmbaturin
<mfp>
infinity0: maybe I'm misunderstanding... are you describing something like let rec go async_ops = match_lwt getpacket () with `Normal p -> go (async_op p :: async_ops) | `Final p -> lwt () = Lwt_list.iter_s (fun x -> x) @@ List.rev (async_op p :: async_ops) in go Q.empty launch async ops in response to packets, ensure they're all complete before processing packet after `Final one?
<mfp>
oops s/Q.empty/[]/
SimonJF_ is now known as SimonJF
_andre has joined #ocaml
gbarboza has joined #ocaml
_whitelogger has quit [Excess Flood]
_whitelogger has joined #ocaml
antkong has quit [Quit: antkong]
kushal has joined #ocaml
butts_butts has quit [Ping timeout: 268 seconds]
AlexRussia has joined #ocaml
arquebus has joined #ocaml
rand__ has joined #ocaml
kdas__ has joined #ocaml
kushal has quit [Ping timeout: 240 seconds]
kdas__ has quit [Read error: Connection reset by peer]
<infinity0>
mfp: no, something along the lines of this https://paste.debian.net/411347/ (no actual code yet, i'm just trying to reason through what i would eventually do)
<infinity0>
i'd like the guarantee that, when recv_pkt (Final _) executes, then do_extra_stuff_when_complete executes before any subsequent calls to recv_pkt
<mfp>
infinity0: you build the async computation when you collect the Initial packet, yet only launch it when you get the Final?
<infinity0>
oh no, it's supposed to be launched when you get the Initial packet. i'm not that familiar with Lwt yet
<infinity0>
the final packet is supposed to supply the last pieces of data needed to complete it though
slicefd has quit [Quit: WeeChat 1.4]
<infinity0>
https://paste.debian.net/411350/ might be a bit more accurate, assuming that "launch" is something that one can do ¬.¬
<mfp>
looks like you'll have to store a sleeper thread (at the tail of the) async computation + a wakener to pass the final params, when you get the Final packet you supply the params, and wait on the computation sleeper
<infinity0>
mfp: oh ok i think i roughly get the gist of that, will look into / think about it
<mfp>
the point is the "async computation" is not totally async, you do wait for it to complete before rcv_pkt returns after a Final pkt
<mfp>
(assuming you're running rcv_pkt in a loop)
<infinity0>
yeah or iter_s has a similar semantics to a loop i guess
kushal has quit [Quit: Leaving]
Haudegen has joined #ocaml
<Anarchos>
rks`: i am looking for a language based on linear logic (in curry howard correspondance)
copy` has joined #ocaml
larhat has quit [Ping timeout: 264 seconds]
sz0 has joined #ocaml
antkong_ has joined #ocaml
antkong_ has quit [Client Quit]
jgjl has joined #ocaml
tane has quit [Quit: Verlassend]
ggole has joined #ocaml
hcarty1 has joined #ocaml
mietek has quit [Ping timeout: 246 seconds]
kansi has joined #ocaml
ztennix has quit [Ping timeout: 246 seconds]
mietek has joined #ocaml
<rks`>
Anarchos: try Chrust, it's rust with dependent types
<rks`>
(I'll let you guess where the CH comes from ;))
<Anarchos>
rks`: curry homard ?
<rks`>
wow, that sounds tasty.
<Anarchos>
:)
jbrown has quit [Remote host closed the connection]
jgjl has quit [Ping timeout: 244 seconds]
hexhaxtron has joined #ocaml
jbrown has joined #ocaml
<hexhaxtron>
Where can I find lots of source code to read and test?
<haesbaert>
I might come out as a prick, but, github ?
<Anarchos>
rks`: google doesn't know about chrust
<MasseR>
hexhaxtron: true, you can search github by language
<MasseR>
not all of it is good
Algebr` has quit [Read error: Connection reset by peer]
Algebr` has joined #ocaml
<malc_>
hexhaxtron: code of what nature?
<rks`>
Anarchos: did you google "chrust language"
Sorella has joined #ocaml
<hcarty1>
hexhaxtron: opam.ocaml.org
sh0t has joined #ocaml
hxegon has joined #ocaml
hcarty1 is now known as hcarty
_whitelogger has quit [Ping timeout: 260 seconds]
_whitelogger has joined #ocaml
Mercuria1Alchemi has quit [Ping timeout: 244 seconds]
<Anarchos>
rks`: yes
<Anarchos>
rks`: it sends me to aramic pages (language of Jesus Christ :)
<rks`>
:D
<rks`>
I don't have the link at hand
<rks`>
I don't remember where I read about it, sorry
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBird_ has quit [Ping timeout: 244 seconds]
jeffmo has joined #ocaml
<Anarchos>
rks`: sad news
aantron has joined #ocaml
sh0t has quit [Ping timeout: 240 seconds]
Janni has joined #ocaml
<Janni>
Hello. Is it possible to use Unicode in writing OCaml code? I suppose it's not (after trying)...
<Janni>
(maybe some sort of extension or so?)
<companion_cube>
you mean using unicode identifiers?
<Janni>
Yes.
<Janni>
And operators! That would be neat!
rand__ has quit [Quit: leaving]
<Janni>
I can't find any operator with type ('b -> 'c) -> ('a -> 'b) -> 'a -> 'c in the standard library. Is point-free programming not commonly used in OCaml?
<ollehar>
but not possible to integrate into the compiler?
<flux>
I don't think it's enough to just decide that feature X should now go into the compiler, because it's great: it requires the actual writing of codes to be done as well :)
<Drup>
And the maintenance
<flux>
and I think in practice it goes like a person tries to implement a new feature, and if it is a success, it could be considered for inclusion..
<flux>
success being a) does it work b) is it complicated (maintenance) c) do people want it d) ..
<Drup>
ollehar: if it can exist out of the compiler, I don't see why it should automatically be merged
<ollehar>
to enforce it.
<Drup>
It's not a type system, it's an analyzer ...
<ollehar>
true.
<ollehar>
sigh.
<Drup>
And I'm sure it's slow as hell
<Drup>
(because those kind of analysis are hard)
<flux>
I don't think if there are that many actually tested solutions to the exception problem, that have turned out to be a success
<flux>
of course it would be great if ocaml had the first one, but I really don't mind that the most experimental are first tried elsewhere.
<flux>
example of a failure: java checked exceptions :P
<ollehar>
yes.
<ollehar>
just feel that ocaml should have a functional variant.
<ollehar>
like with objects.
<ollehar>
while algebraic effects going the other direction.
nicholasf has quit [Client Quit]
<Kakadu>
I suddenly caught an idea today that OCaml community usually forgets about GSoC deadlines...
<ollehar>
I also believe that the "linter should never have been separated from the compiler".
jwatzman|work has quit [Quit: jwatzman|work]
<flux>
as I understand it, lint-type programs often times give imprecise information
jwatzman|work has joined #ocaml
Anarchos has quit [Quit: Page closed]
hxegon is now known as hxegon_AFK
<flux>
so a perfectly valid program can produce lint diagnostics. it's like, "check here, there could be something interesting here"
jwatzman|work has quit [Client Quit]
<ggole>
That's equally true of the warnings that are in the compiler
<ollehar>
flux: false positives? hm.
<flux>
yes, that's lint-kind functionality, but as I understand ollehar wanted it for 'enforcing'?
<ollehar>
well, obviously you can't enforce false positives.
<flux>
so you need to add some kind of annotations to tell more precisely what you're doing to eliminate them..
<ollehar>
but compare with --pedantic in C. maybe not relevant to typed exceptions, though.
<flux>
and that is the research part of the whole deal.
<Drup>
ollehar: framaC is not in clang.
octachron has quit [Quit: Leaving]
<companion_cube>
ollehar: -w +a
<companion_cube>
it's already sufficient to catch many mistakes
<ollehar>
ocaml?
<companion_cube>
yeah
<companion_cube>
(well I use something like -w +a-4-44, but anyway)
seangrove has joined #ocaml
jwatzman|work has joined #ocaml
Algebr has joined #ocaml
aantron has quit [Remote host closed the connection]
_whitelogger has quit [Ping timeout: 260 seconds]
_whitelogger has joined #ocaml
sz0 has quit [Quit: My computer has gone to sleep. ZZZzzz…]
_whitelogger has quit [Excess Flood]
_whitelogger has joined #ocaml
hxegon_AFK is now known as hxegon
t4nk811 has joined #ocaml
jimt has quit [Ping timeout: 276 seconds]
aantron has joined #ocaml
tane has joined #ocaml
sh0t has joined #ocaml
kansi has quit [Read error: Connection reset by peer]
Janni has quit [Ping timeout: 244 seconds]
jimt has joined #ocaml
<seangrove>
Bah, how do I create a new opam switch? `opam switch 4.02.3 my_new_project_env` ?
<seangrove>
hannes: I talked a bit with Daniel Woelfel (a clojure hacker I work with a lot and really respect) about doing an ACME implementation in OCaml, we're mulling it over :)
<Drup>
That would be really cool
<seangrove>
The main idea being that you could use an OCaml library and or executable to provision the certs, right?
<seangrove>
Without the python code they distribute?
l1x has quit [Quit: Updating details, brb]
l1x has joined #ocaml
nicholasf has joined #ocaml
<flux>
(..are you talking about let's encrypt?)
ontologiae has quit [Ping timeout: 248 seconds]
<Drup>
he is
<companion_cube>
acme also refers to a text editor, so it wasn't totally obvious
<Drup>
acme refers to so many things ...
<hannes>
seangrove: ideally, I'd like to have a MirageOS unikernel which can provision itself (I'm ok to feed it its secret)
<seangrove>
hannes: But won't the rate-limiting affect it?
<seangrove>
Right now I build the unikernel with the LE cert, that way I only have to provision it every few weeks
ygrek has joined #ocaml
<hannes>
seangrove: didn't read up on rate limiting yet entirely, but they have those 90-day valid certs..
<hannes>
thus, auto-recreating after 90 days would be brilliant
<seangrove>
hannes: Would love to talk over this idea. Daniel and I debated it last night, but there are quite a few missing pieces for that to actually work I think.
<Drup>
Yeah, I had the exact same thing in mind
<hannes>
I've to head off...
<Drup>
which pieces are you missing ?
<seangrove>
e.g. unikernels can't build themselves, so you need to have another service that will build them (given the credentials). But then you need to answer the challenges on the production domain, so your unikernel needs to know 1. how to initial an ACME request, 2. how to respond to the challenge 3. where to put the resulting cert files (e.g. s3) 4. ping the service that will rebuild the unikernel (travis, circle, etc.) given the location of
<seangrove>
the cert files
<companion_cube>
why couldn't the unikernel store the cert in some local storage?
<Drup>
You don't need to rebuild the unikernel
<seangrove>
companion_cube: It can, but how does that help? The storage is local to the unikernel, and isn't around for the next deploy of the unikernel
darkf has quit [Quit: Leaving]
<Drup>
hum, you are assuming EC2, I guess
<seangrove>
Drup: Yeah, assuming any kind of deployment chain like that.
<Drup>
where you have no underlying storage at all
<seangrove>
But ideally e.g. Travis or CircleCI would never see them either
<seangrove>
It can definitely all be pieced together pretty easily (some build machine to build the post-CI artifact), but I'm having a tough time thinking of a universal, automatic, secure, simple updating mechanism
<seangrove>
Interesting challenge though
ollehar has joined #ocaml
<seangrove>
Hrm, I can't seem to get dbm to install on osx. Getting `NDBM not found, the "camldbm" library cannot be built.`, not sure what I need to install
<Algebr>
odd, i just installed it no prob, probably had somethign installed via brew previously
<seangrove>
Algebr: Yeah, it's *supposed* to be installed in osx by default, and `man dbm` works just fine
<struk|work>
why does "class foo = object val x = 5 end" create a signature like " class foo : object val x : int end " but "object val x = 5 end" creates a signature like this "< > = <obj>" ?
<struk|work>
specifically, why is the value x hidden in the 2nd the case/
<ggole>
struk|work: I believe it has to do with the former being accessible through inheritance
jwatzman|work has quit [Quit: jwatzman|work]
octachron has joined #ocaml
<struk|work>
ggole: I see, so its not like its accessible in either case from outside the classe's hierarchy then
<seangrove>
Algebr: Figured it out - had to install the xcode commandline tools
<seangrove>
(and open the new version of xcode, apparently)
<ggole>
Not directly, no
rand__ has joined #ocaml
Kakadu has quit [Quit: Page closed]
<struk|work>
so anonymous records don't exist, not even with objects. The closest I've seen is doing this let f () = object method x = 5 method y = "abc" end works, but I really dislike pattern matching on that, so I doubt I will ever use it
jgjl has quit [Ping timeout: 260 seconds]
<ggole>
Er, are you aware of the difference between val and method? val is *supposed* to be hidden.
bbarker has joined #ocaml
sh0t has quit [Ping timeout: 248 seconds]
butts_butts has joined #ocaml
<hannes>
seangrove: my deployments to not contain ec2, but I expected to have a local persistent file system to store certificates...
<struk|work>
ggole: yeah I am aware, but I was trying to find a work around to make anon records possible
<hannes>
(agreed, there are various scenarios with different tradeoffs)
dhil has quit [Ping timeout: 276 seconds]
nicholasf has quit [Ping timeout: 260 seconds]
slash^ has quit [Read error: Connection reset by peer]
nicholasf has joined #ocaml
nicholas_ has joined #ocaml
ggole has quit []
hexhaxtron has quit [Ping timeout: 276 seconds]
dmiller_ is now known as dmiller
nicholasf has quit [Ping timeout: 248 seconds]
<octachron>
struk|work, there is a polymorphic record ppx extension on opam that implements a form of anonymous record
<struk|work>
octachron: oh? got a link?
d0nn1e has joined #ocaml
<flux>
probably this one: ppx_poly_record -- PPX Polymorphic record
<octachron>
^ yep
<flux>
doesn't do pattern matching it semes, though
<flux>
and the syntax seems almost unwieldly, [%poly_record .. ]
jrslepak_ is now known as jrslepak
<octachron>
this is what tends to happens when you steal basic syntax for your ppx extension and don't want to erase the normal syntax
AlexRussia has quit [Ping timeout: 252 seconds]
AlexRussia has joined #ocaml
<flux>
well, ppx syntax extending is much more limited than camlp4 was, but more well-structured as well
<flux>
I don't know what kind of syntax would have been a realistic alternative, but [%pr .. ] would have been a nice start IMO :-)
sz0 has joined #ocaml
butts_butts_ has joined #ocaml
butts_butts has quit [Ping timeout: 244 seconds]
<octachron>
flux, with short names you expose yourself to name collisions, except if you have some kind of ppx scoping mechanism
<flux>
octachron, that is true, but I don't think it's in practice a big issue.
<flux>
at least, not yet ;)
<flux>
but I would like to be able to parametrize ppx's somehow. I don't know if that's possible..
hxegon is now known as hxegon_AFK
Kakadu has joined #ocaml
dhil has joined #ocaml
<octachron>
parametrize in what sense? Redefining the name of their extensions and attributes?
<Drup>
flux: ppx can take arguments
seangrove has quit [Ping timeout: 248 seconds]
monod has joined #ocaml
Haudegen has quit [Ping timeout: 264 seconds]
<flux>
octachron, for example
<flux>
drup, do ppx extensions also use them? does it work with ocamlbuild?
ollehar has quit [Quit: ollehar]
<Drup>
some ppx do, some don't
<Drup>
(lwt's ppx has some options, for example)
hxegon_AFK is now known as hxegon
lobo has joined #ocaml
mxv has joined #ocaml
jgjl has joined #ocaml
Haudegen has joined #ocaml
_andre has quit [Quit: leaving]
monod has quit [Quit: Sto andando via]
Anarchos has joined #ocaml
octachron has quit [Ping timeout: 240 seconds]
<aantron>
flux: its possible with ocamlbuild, the tag is ppxopt(extension_package,options)
<flux>
aantron, thanks, nice to know
seangrove has joined #ocaml
sz0 has quit [Quit: My computer has gone to sleep. ZZZzzz…]
<aantron>
perhaps i need to double check this..
octachron has joined #ocaml
octachron has quit [Client Quit]
jgjl_ has joined #ocaml
jgjl has quit [Ping timeout: 250 seconds]
<aantron>
flux: i may have been using some project with a custom tag. it works with basic ocamlbuild like this: -cflag -ppxopt -cflag "bisect_ppx,-foo"
_whitelogger has quit [Excess Flood]
_whitelogger has joined #ocaml
nicholas_ has quit [Remote host closed the connection]
sh0t has joined #ocaml
TheLemonMan has joined #ocaml
butts_butts_ has quit [Ping timeout: 244 seconds]
sz0 has joined #ocaml
<seangrove>
Interesting challenge for the channel: I want to create a preview of the first N words of a rendered markdown document, parse that using soup, and insert it into an existing soup parsed document.
<seangrove>
I can't just take N words from the markdown doc (splitting on whitespace), because I make split in the middle of e.g. [this is a link]()
<seangrove>
That may come out as `[this is`, which markdown won't turn into the right markup. I really want the first N tokens, I suppose.
spacekitteh has joined #ocaml
<seangrove>
But then if I render the markdown doc into html, and then try to take the first N words of that, I'm pretty much guaranteed to get bad html (missing tons of closing tags, etc.)
<seangrove>
Is there an obvious solution I'm missing?
<Drup>
Just count the parens.
<Drup>
(metaphorical parents, I mean tag opening)
nicholasf has joined #ocaml
<seangrove>
Of the rendered html markdown?
<Drup>
No, in the markdown
<aantron>
by soup, do you mean lambda soup?
<Drup>
And stop when you are at ground level
<seangrove>
aantron: Yeah, sorry, should have been more specific
<aantron>
what happens if you parse the rendered document, then use http://aantron.github.io/lambda-soup/#VALtexts to get the text content, and take the first N words of that? am i misunderstanding?
<seangrove>
aantron: But that would then drop e.g. any links as well, right?
bbarker has quit [Quit: Connection closed for inactivity]
nicholasf has quit [Remote host closed the connection]
<aantron>
yes
<aantron>
what do you want to keep? formatting elements and links?
<mfp>
seangrove: parse with omd, operate with the typed representation
nicholasf has joined #ocaml
<seangrove>
mfp: That sounds interesting
<Drup>
Ah yeah, I was assuming you were already using a typed representation
<seangrove>
You can see how things get messed up after the first post because of my approach now
<Drup>
I would tell you to add an end of preview marker
<Drup>
like a new tag
<Drup>
simpler, better control :)
<seangrove>
Drup: Also interesting. What would I add it to, and how would that help (I would like the preview generation to be automatic, though user-guided in the markdown file could be ok, I suppose)
<aantron>
seangrove: i guess you could also parse the rendered document using markup.ml, but terminate the input stream once you counted enough words in the `Text signals in the output stream. markup.ml will then close open tags for you, and you can pass that signal stream into lambda soup for assembly
<Drup>
Omd accept custom tags
<seangrove>
Cool, all very interesting proposals. I'll chew them over - thanks Drup, aantron, and mfp!
malc_ has quit [Quit: ERC (IRC client for Emacs 25.0.50.2)]
<aantron>
seangrove: if/when you are testing with markup.ml, i should note that you should call it with ~encoding:Encoding.utf_8 or some other encoding, to prevent a pre-scan of the input stream
<spacekitteh>
what's a good book about ocaml for haskell programmers?
MercurialAlchemi has quit [Ping timeout: 268 seconds]
<j0sh>
spacekitteh: real world ocaml is generally very good (whether you're coming from haskell or not)
<spacekitteh>
thanks j0sh
<spacekitteh>
does it cover debugging?
jgjl_ has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]