ollehar has quit [Remote host closed the connection]
Thooms has quit [Quit: WeeChat 1.0.1]
lyxia has quit [Ping timeout: 245 seconds]
ygrek_ has joined #ocaml
simnus has quit [Quit: Leaving]
bytbox has joined #ocaml
pyon has quit [Ping timeout: 255 seconds]
milosn has quit [Ping timeout: 272 seconds]
myyst has joined #ocaml
bytbox has quit [Remote host closed the connection]
milosn has joined #ocaml
<companion_cube>
whitequark: I think there is a bug in Ppx_deriving.attr regarding qualified attributes
pyon has joined #ocaml
<companion_cube>
type t = { x:int [@printer fun fmt -> Format.fprintf fmt "<%d>"] } [@@deriving show];;
<companion_cube>
works
<pippijn>
companion_cube: this stuff is so ugly!
<companion_cube>
but type t = { x:int [@show.printer fun fmt -> Format.fprintf fmt "<%d>"] } [@@deriving show];; doesn't (it is supposed to, isn't it?)
<companion_cube>
pippijn: ?
<pippijn>
@@@@
Tekk_` has joined #ocaml
<pippijn>
@_@
<pippijn>
I find @ exceedingly ugly
<companion_cube>
bah, it's kind of really useful, and less ugly than camlp4
<pippijn>
no way
<companion_cube>
yes way :p
lyxia has joined #ocaml
<pippijn>
type t = A | B | C with sexp
<companion_cube>
it doesn't reimplement its own parser
<pippijn>
type t = A | B | C deriving (Show)
<companion_cube>
it's well integrated with the AST
<pippijn>
you're telling me [@@deriving show] is prettier?
<pippijn>
you're insane
<companion_cube>
and it works with merlin
<companion_cube>
it's not prettier, it's simpler and saner
<companion_cube>
more sane*?
<companion_cube>
also, ppx_deriving is awesome
<pippijn>
saner works
<pippijn>
yes, I'm sure it is
<pippijn>
I think this stuff has a bright future
<pippijn>
if only it were less ugly
<def`>
+1
swgillespie has joined #ocaml
<pippijn>
compiler plugins are definitely the way to go
<Drup>
I agree to the fact that the syntax is ugly
<pippijn>
additional custom optimisation and static analysis passes
<Drup>
but try to see it from the other way
<pippijn>
I'd love to see that happening and becoming easy to use
<Drup>
do you have a syntax that doesn't break *anything* in OCaml ?
<Drup>
and that can be attached to arbitrary sub expressions
<companion_cube>
[@@warning +42] is neat imho
AltGr has joined #ocaml
<companion_cube>
it really looks like annotations
<companion_cube>
I can see [@@inline "always"] and other similar stuff
<Drup>
(and that keeps the grammar LALR, obviously)
<pippijn>
Drup: well
<pippijn>
there are a number of things that make parser extensions hard
<pippijn>
for one, extending the parser means you need to compile the parse tables at runtime
<pippijn>
every time
<Drup>
pippijn: no but let's ignore everything and try to figure out a syntax that works in ocaml pre-ppx
<Drup>
for annotations
<companion_cube>
you also need to have the parser extensions cooperate
<Drup>
and that isn't "ugly @@@@@@#
<pippijn>
companion_cube: right
<companion_cube>
{@| |@} !!!
<Drup>
companion_cube: {| ... |} is the one thing that, imho, could have been simpler
<companion_cube>
I have no opinion
<pippijn>
that's even harder, given that it needs to be LR(1)
<Drup>
by not requiring {foo| to be closed by |foo} (and |} instead)
<companion_cube>
I just happen to really like ppx_deriving and its plugin interface
<companion_cube>
and ease of use
<pippijn>
or LALR(1)
<companion_cube>
and soon, serialization will cease to be a problem :>
<Drup>
pippijn: exactly
<pippijn>
if we could accept GLR in the presence of extensions, the problems would go away
<Drup>
if you start from a fresh start, you could have designed the whole syntax to be better
<companion_cube>
e.g. match ... end
<companion_cube>
pls
<Drup>
but given the OCaml as it is today
<Drup>
there was no really other possibilities than ugly [@ ... ]
<Drup>
( @@@ is over the top, though)
<pippijn>
seriously? there is a @@@?
<companion_cube>
agreed, @@@ is too much
<Drup>
yes
<pippijn>
:|
* pippijn
cries
<companion_cube>
but then it's useful too, isn't it?
<Drup>
not that much.
<pippijn>
the resyntaxed ocaml didn't go anywhere
<companion_cube>
bah.
<pippijn>
maybe I'll resyntax it again
<companion_cube>
there's also a resyntax based on whitespace
<companion_cube>
and indentation
<pippijn>
I'll make my own syntax extensions! with black jack and hookers!
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
<companion_cube>
well, forget about the black jack!
* pippijn
smokes cigar
<companion_cube>
and syntax extension!
<companion_cube>
(I see you have good references)
<companion_cube>
hmm, on my todolist: "remove crap from containers"
<pippijn>
it had to be there :)
<companion_cube>
I should do it
<companion_cube>
to make Drup happy
* pippijn
continues writing an email to the core ML
<pippijn>
(ML being mailing list)
<pippijn>
Jenga is nice
<Drup>
pippijn: note that I'm much less indulgent for rust's syntax.
<pippijn>
but too limited to be useful in practice
<pippijn>
Drup: rust's syntax is..
<Drup>
ugly as fuck and not even consistent
<pippijn>
like my colleague, who likes rust a lot, said:
lyxia has quit [Ping timeout: 252 seconds]
<pippijn>
"putting everything we love from good language design into braces and semicolons"
<Drup>
:D
<companion_cube>
well, at least their pattern matching has a terminating delimiter
<Drup>
I wouldn't mind if it was just that, actually
<companion_cube>
and I don't see why it's so ugly
<pippijn>
the type system seems quite sane
<Drup>
but || and ::<>
lyxia has joined #ocaml
<pippijn>
I like it
<companion_cube>
it's verbose, but because the language is very explicit
<Drup>
ugh
NoNNaN has quit [Remote host closed the connection]
<Drup>
(especially ::<>)
<pippijn>
I like a lot how it gives you a lot of control over resource management
<companion_cube>
ok ok, that part is ugly
<Drup>
(even the smiley is screaming ...)
<pippijn>
haha
<companion_cube>
but I don't know how you could write it anyway
<companion_cube>
it's pretty C++-ish
<pippijn>
it looks a lot like C++
<pippijn>
just slightly prettier
<companion_cube>
except, no .h
<companion_cube>
and sane design
<pippijn>
C++ is really pretty terrible
<pippijn>
syntactically
<Drup>
not really like C++
<companion_cube>
I find rust to be very reasonable on the syntax side
<pippijn>
the dynamic semantics of C++ are a mess
<Drup>
C++ parsing is not decidable because template.
<pippijn>
but the static semantics are reasonably sane
<companion_cube>
it's an ok mix of ML and C++
<thizanne>
i don't really see why people complaing against match not having a terminating delimiter
<pippijn>
especially template semantics
<companion_cube>
thizanne: nested matches are a pain
<thizanne>
I mean, most of the case it's shorter, and when you need it just use `begin match` instead of `match`
<companion_cube>
"begin match" is so ugly :(
<pippijn>
thizanne: match foo with | A -> ... | B -> try ... with | Failure e -> ... | ... uhh
<companion_cube>
I use this, but still
<Drup>
thizanne: it would make scoping more explicit with a pretty negligible cost
<companion_cube>
right pippijn, try ... with ... end too
<pippijn>
companion_cube: yeah, I do that, and every time I'm happier if I end up needing to do let ... = match ... in
<thizanne>
yeah, I see why people want to have this `end`
<companion_cube>
pippijn: exactly
<pippijn>
I don't like how resyntaxed ocaml solved it
<thizanne>
I just think that using `begin match` when you need it is at least as cheap as putting `end` where you don't need it
<pippijn>
with [] around the cases
<Drup>
thizanne: if they are both equally cheap, the explicit case is always better
<companion_cube>
thizanne: I disagree, but it's a matter of taste
<pippijn>
I'd prefer to always put an end instead of sometimes putting it and sometimes not
<Drup>
(especially if you consider beginners in the equation)
<companion_cube>
and of course, if could also afford an "end"
<pippijn>
and later, you rewrite some code, add some stuff, and suddenly you need to add begin/end to something
<Drup>
(I mean, beginners *always* got it wrong ..)
<pippijn>
or you remove it again (because it's prettier without)
<thizanne>
maybe I think this because, when I began, I never used nested matches
<pippijn>
that's overhead
<companion_cube>
Drup: care to take a look at {ppx_deriving_,}cconv? ;à
<Drup>
companion_cube: not today
<companion_cube>
heh
<companion_cube>
sure
<companion_cube>
I'm going to sleep anyway
<pippijn>
I need to finish my email
<Drup>
companion_cube: and probably in the imediate future, given that I don't know ppx_deriving all that much.
<Drup>
you probably know it more than I do, if you implemented one :p
<companion_cube>
I've suggested ppx_deriving_irmin to thomasga ;)
bytbox has joined #ocaml
<Drup>
what would it derive ? the merge ?
<Drup>
it seems weird
<companion_cube>
Drup: just try it, no need to look at the code
<Drup>
ah
<Drup>
I don't have any use case at the moment
<companion_cube>
yes, it would compose basic combinators to get complex mergeable structures
<pippijn>
hmm
<pippijn>
I want plugins at every stage of the compiler, but most importantly: after lexing/before parsing, after parsing/before scope binding, after scope binding/before typing, after typing
<pippijn>
*most* importantly: after scope binding
<pippijn>
I'm assuming this is a separate step from typing, purely from observations of compiler diagnostics
<Drup>
unfortunatly
<Drup>
by scope binding you mean name resolution, right ?
<pippijn>
yes
<Drup>
you can't separate type checking and name resolution
<Drup>
not anymore
<pippijn>
oh right
<pippijn>
because of the ADL thing
<Drup>
ADL ?
lyxia has quit [Ping timeout: 255 seconds]
<pippijn>
argument dependent lookup
<Drup>
?
<pippijn>
it's a C++ thing
<pippijn>
I mean the ocaml equivalent
<Drup>
there is no ocaml equivalent, it's a different feature
<pippijn>
where you do foo.bar and bar is looked up in foo's scope as well as the current scope
lyxia has joined #ocaml
<pippijn>
foo's type's scope
<Drup>
yeah, so no, it's not like that
<Drup>
it's just record desambiguation
<pippijn>
I don't understand that feature
<pippijn>
Drup: also type constructors
<pippijn>
but the feature issues a warning
<Drup>
yes, it's the same
<pippijn>
so it's like "here you got a fancy new feature, but don't use it"
<Drup>
and also modules.
<Drup>
(with open)
<Drup>
(especially local open + first class modules)
<Drup>
(you really can't say anything about name resolution without some typechecking)
<pippijn>
I consider this a design bug
<Drup>
It's not that simple
<Drup>
this is in fact a very restrictive constraint
<pippijn>
C is unparsable without scope binding
<pippijn>
but it doesn't require any type checking for scope binding to work
<Drup>
1) "C is unparsable without scope binding" <- I consider this a much worse design bug
<Drup>
2) C doesn't have inferce.
<Drup>
inference*
<pippijn>
unlike C++
manizzle has joined #ocaml
<pippijn>
Drup: right, but you see..
<pippijn>
type inference would normally be a thing that *requires* scope binding to be a separate step
<Drup>
(I would argue C barely have typechecking really)
<pippijn>
otherwise, type inference becomes a lot more complex
<Drup>
pippijn: depends of the type system and the typechecking algorithm
<pippijn>
lexing -> parsing -> scope binding -> generate type equations -> solve equations -> done, typed program
lyxia has quit [Ping timeout: 252 seconds]
<Drup>
small letter at the bottom of your scheme : work only for stupidly trivial type systems.
<pippijn>
:)
<pippijn>
where do first class modules create a problem?
<Drup>
you don't even need first class modules really
<Drup>
it just worse with them
lyxia has joined #ocaml
<Drup>
but a simple functor will show the issue
<pippijn>
different question, same intent: what part of ocaml 3.12 is a problem for separate scope binding?
<Drup>
since you need to typecheck the functor application before doing the name resolution
<Drup>
you could say "but, I just need to typecheck the module language before the expression language"
<pippijn>
right
<Drup>
which become false with first class modules.
<pippijn>
why?
<Drup>
because it's not a different language anymore.
<pippijn>
show me
<Drup>
I'm trying to come up with a nice example and it's hard at 2 in the morning
lyxia has quit [Ping timeout: 272 seconds]
<Drup>
hell, I don't need something complicated in fact
<pippijn>
no, make it simple
<Drup>
pippijn: "let f (module M : S) x = let open M in x ;;"
<pippijn>
yes
<pippijn>
now all lookups will consider module type S
alkoma has quit [Ping timeout: 245 seconds]
<Drup>
you can make it a bit more involved to make it even more annoying to typecheck but that's the basic idea
ZenosDance has joined #ocaml
<pippijn>
how is this different from having a file "M.mli" containing: include S
<Drup>
hum
<Drup>
(I'm assuming S is defined in the same file)
<pippijn>
does it matter?
<Drup>
well, if you really want to separate name resolution and typechecking for a whole file, yes
<pippijn>
ok, how is it different from having: module M : S = struct ... end
<pippijn>
scope binding will go to S, never to M, because it's restricted to being of module type S
<Drup>
yes, it's not really in this case in this case, let me see.
<pippijn>
ok
<Drup>
I don't remember the last example, postponed for tomorrow.
lambdahands has quit [Ping timeout: 264 seconds]
<pippijn>
okay
<Drup>
(record disambiguation is enough, though ;)
<pippijn>
yes, and that's new, and is a mistake for exactly that reason
<mfp>
I'll just drop these 4 lines, bear with me
<pippijn>
I still don't believe that the module system poses a problem for untyped scope binding
<mfp>
module type S = sig val x : int end
<mfp>
module type T = sig val x : string end
<mfp>
type _ hah = S : (module S) -> int hah | T : (module T) -> string hah
<mfp>
let f : type a. a hah -> a = function S (module X) -> X.x | T (module X) -> X.x
<Drup>
pippijn: it's extremely useful for writing multiple asts and transformations
<Drup>
(in compilers, for example)
<pippijn>
mfp: yeah
<pippijn>
good example
<pippijn>
mfp: that doesn't depend on GADTs, though
<pippijn>
it would break the same way with normal ADTs
<pippijn>
thanks
<pippijn>
Drup: I believe you now
<Drup>
mfp: ah, thanks, I was trying to come up with something like that but couldn't manage to do it
<mfp>
wanted GADTs to stress that it's inferring the type of the X modules
<pippijn>
mfp: unnecessary
ygrek_ has quit [Ping timeout: 245 seconds]
<mfp>
well yes, but you couldn't have the -> a though, which provides extra laughter
lyxia has joined #ocaml
<pippijn>
:)
lambdahands has joined #ocaml
<pippijn>
it took me 2 hours to write an email >_>
<Drup>
I like the fact that the TL;DR is half the email.
<pippijn>
yeah :\
<pippijn>
well, the very short version is
<pippijn>
TL;DR: jenga necessarily uses the shell to do anything complex, I want it not to
<pippijn>
I'm not good at writing short emails
<mfp>
ocaml-core? huh, I've been missing out
<pippijn>
mfp: that's jane street's Core
<pippijn>
mfp: you haven't been missing out
<mfp>
ah ok, looked like a general ML at first
<pippijn>
it's low traffic, mostly filled with announcements of the next new shiny
reem_ has joined #ocaml
<pippijn>
I'm producing more traffic in 2 days than it has had in 2 months
reem has quit [Read error: Connection reset by peer]
<pippijn>
(which is not hard, because it had 3 emails in 2 months)
lambdahands has quit [Ping timeout: 240 seconds]
<pippijn>
ah no, 4
<Drup>
pippijn: I wouldn't be surprised if you were the first non-jst jenga user
<Denommus>
is there more than one indentation option for tuareg-mode?
<Denommus>
I don't like the default :-/
<mfp>
haha, just looked at the top posting dates and it looked quite active indeed
<Drup>
Denommus: use ocp-indent anyway
<pippijn>
Drup: it's quite likely, although there are some github issues
<pippijn>
Drup: I'm probably the first one who seriously considers using it for serious work
<pippijn>
(I'm being serious here)
<pippijn>
OMake's complexity and power is amazing
<pippijn>
it's a marvellous piece of engineering
<pippijn>
it's easily the most powerful build system out there
lyxia has quit [Ping timeout: 276 seconds]
<pippijn>
which is less surprising considering the people who made it usually spend their time making proof assistants
<pippijn>
jenga is very very primitive by comparison
<pippijn>
but if it had a few more basic tools, I could build something on top of it that might rival the things I did with omake
<pippijn>
one thing I like: you can have separate build schemes that are all processed in every directory, and they can decide whether to produce rules in that directory or not
<pippijn>
what I don't like: there doesn't seem to be a way to communicate information between schemes (probably not a big problem, it keeps them nicely separate)
<pippijn>
bigger problem: there also doesn't seem to be a way to communicate information from a parent directory to a subdirectory
lordkryss has joined #ocaml
<pippijn>
this problem can be solved with sufficient hackery, but I'd like that to be in the jenga core
lyxia has joined #ocaml
<pippijn>
OMake has everything :) for example: topological sort of files by some custom criterion (e.g. dependency order), necessary for ocaml linking
BitPuffin has quit [Ping timeout: 264 seconds]
<Denommus>
Drup: does it work well with Eliom's special syntax?
<Drup>
Denommus: it works ok, slightly better than tuareg
jwatzman|work has quit [Quit: jwatzman|work]
lyxia has quit [Ping timeout: 245 seconds]
srcerer has joined #ocaml
lyxia has joined #ocaml
<jpdeplaix>
Does somebody have ever tried to use bind a C function using ctypes in which the signature contains a type external to the library but available as an ocaml type (in my case: cairo_t <=> Cairo.context)
<jpdeplaix>
?*
<pippijn>
I've never used ctypes
<pippijn>
but I'm curious: how well does it perform compared to "external"?
lambdahands has joined #ocaml
<Denommus>
is there a library available for OCaml that can be used on the front-end similar to React?
<Denommus>
... sorry, I mean ReactJS
<Denommus>
damn ambiguity
<Denommus>
what I want to do is to have my screen to be a React behavior, pass it to the ReactJS-like library and it would be able to apply only what has changed
<pippijn>
screen?
<Denommus>
sorry, I meant view
<Denommus>
that is, my whole page is a time-varying value - a React behavior
<pippijn>
ah, web stuff
<pippijn>
no idea
<Denommus>
I thought it would be more obvious when I mentioned ReactJS
<Denommus>
ah, React calls behaviors "signals"
lyxia has quit [Remote host closed the connection]
lyxia has joined #ocaml
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
<Drup>
Denommus: it's done in eliom's reactive done
<Drup>
reactive Dom*
<Drup>
there is a tutorial about it, I'll let you read it
<Denommus>
Drup: I wasn't sure what to look for, thanks!
IbnFirnas has quit [Read error: Connection reset by peer]
ggherdov has quit [Read error: Connection reset by peer]
strmpnk has quit [Ping timeout: 245 seconds]
lyxia has quit [Ping timeout: 240 seconds]
kapil__ has quit [Ping timeout: 272 seconds]
lyxia has joined #ocaml
lambdahands has quit [Ping timeout: 244 seconds]
tnguyen has quit [Quit: tnguyen]
huza has joined #ocaml
tnguyen has joined #ocaml
tnguyen has quit [Client Quit]
tnguyen has joined #ocaml
tnguyen has quit [Client Quit]
tnguyen has joined #ocaml
tnguyen has quit [Client Quit]
strmpnk has joined #ocaml
kapil__ has joined #ocaml
lyxia has quit [Ping timeout: 265 seconds]
strmpnk has quit [Ping timeout: 272 seconds]
kapil__ has quit [Ping timeout: 245 seconds]
JuggleTux has quit [Remote host closed the connection]
cdidd_ has quit [Remote host closed the connection]
enitiz has quit [Remote host closed the connection]
cdidd has joined #ocaml
IbnFirnas has joined #ocaml
manizzle has quit [Ping timeout: 252 seconds]
strmpnk has joined #ocaml
nullcat has joined #ocaml
kapil__ has joined #ocaml
rossberg has quit [Ping timeout: 244 seconds]
vanila has joined #ocaml
ggherdov has joined #ocaml
rossberg has joined #ocaml
enitiz has joined #ocaml
pyon has quit [Ping timeout: 245 seconds]
lordkryss has quit [Quit: Connection closed for inactivity]
badkins has quit []
pyon has joined #ocaml
ygrek has quit [Ping timeout: 276 seconds]
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
mcc has joined #ocaml
<mcc>
whitequark: was it mentioned you implemented the Compl feature in sedlex? is there a reason it does only single-character regexps, although Cset.t appears to have a general compl operation?
<mcc>
whitequark: this is another way of asking "if i try to make Compl work for general character sets, am i sticking my arm in a bear trap"
matason has joined #ocaml
nullcat has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
IbnFirnas has quit [Read error: Connection reset by peer]
IbnFirnas has joined #ocaml
<whitequark>
I honestly don't remember
<whitequark>
try it, then try to break it, i guess
<mcc>
i did: opam pin add merlin [GARBAGE] (result: error, GARBAGE is GARBAGE]); opam update (result: it updated some things then failed on GARBAGE); opam remove pin (it did a bunch of stuff that looked like merlin was being *uninstalled*, like it wanted to DOWNGRADE a bunch of stuff)
<mcc>
like "you made silly decisions" is one thing, "i'm downgrading ocamlp4" is way weirder
<mcc>
The former state can be restored with opam switch import "/Users/mcc/.opam/4.02.1/backup/state-20150021060743.export" << OH WOW WOW WOW I REALLY LIKE THIS FEATURE
<mcc>
hm. if merlin started and volunteered "failed to load some packages 'containers'"
<mcc>
is that alarming at all
<mcc>
oh no n/m
<mcc>
it's because i don't have containers anymore
<mcc>
go... figure
<whitequark>
you have containers in .merlin likely
<whitequark>
and they are not installed
lyxia has quit [Ping timeout: 245 seconds]
lyxia has joined #ocaml
mcc has quit [Ping timeout: 256 seconds]
ygrek has joined #ocaml
lyxia has quit [Ping timeout: 255 seconds]
lyxia has joined #ocaml
mcc has joined #ocaml
<mcc>
i said a couple things but i think then i got disconnected and i do'nt know what sent. um, i'm getting a compile failure when i try to install containers 0.7. what would be the right thing to do? bother companion_cube? file an issue? https://gist.github.com/mcclure/8a3229bebe80b38ba014
<mcc>
this is from opam install containers
<whitequark>
might need an emergency intelligence incinerator
<whitequark>
sigh
<whitequark>
i know what the problem is
<whitequark>
the problem is that os x is a piece of crap. their ar can't create empty archives, they know about it since, like, 2007, and they do not give a fuck
<whitequark>
the short answer is that i think rolling back to containers 0.6 will fix it
<whitequark>
the long answer is that this needs to be fixed within containers, please open an issue
<mcc>
should i consider it an opam bug that when i did opam upgrade, and the containers 0.7 build failed, it silently uninstalled containers instead of like giving me an error or rolling back to the previous version?
<mcc>
yes, that sounds like my experience of apple's handling of bugs related to unix standards compliance
<mcc>
this would be done using... some kind of pin add?
<whitequark>
hm. opam install containers.0.6 will work *once*
<whitequark>
i am not actually sure how to make it persistent.
<whitequark>
i know that if you make emily itself into an opam package, you can make it so that it conflicts with newer containers version
<mcc>
maybe i don't need it persistent.
lyxia has quit [Ping timeout: 245 seconds]
<mcc>
i think that probably one way or another this problem can be resolved before i either complete the emily opam package, or next run opam upgrade. i apparently had not done that since the start of the project.
<mcc>
oh. while we're talking about this.
<mcc>
i had a … um … interesting conversation with someone who tried to install emily on cygwin
<mcc>
apparently opam doesn't work on windows at all ...?
<whitequark>
opam works on POSIX systems, and cygwin is a POSIX system
<whitequark>
it is not expected that opam will not work on cygwin. it should.
lyxia has joined #ocaml
<whitequark>
(although for various reasons related to GPL and redistribution of cygwin's components, i think you want to build emily binaries using mingw32 on unix and distribute .exe files)
ygrek has quit [Remote host closed the connection]
ygrek has joined #ocaml
<whitequark>
mcc: i can work through opam on cygwin or emily on mingw32 issues for you, but later
mcc has quit [Ping timeout: 252 seconds]
ggole has joined #ocaml
lyxia has quit [Remote host closed the connection]
lyxia has joined #ocaml
lyxia has quit [Remote host closed the connection]
lyxia has joined #ocaml
Simn has joined #ocaml
psy_ has quit [Ping timeout: 246 seconds]
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
swgillespie has joined #ocaml
jgjl has joined #ocaml
lyxia has quit [Ping timeout: 264 seconds]
lyxia has joined #ocaml
psy_ has joined #ocaml
lyxia has quit [Ping timeout: 246 seconds]
lyxia has joined #ocaml
matason has quit [Ping timeout: 265 seconds]
lambdahands has joined #ocaml
Haudegen has quit [Ping timeout: 244 seconds]
Haudegen has joined #ocaml
madroach has joined #ocaml
ZenosDance has quit [Ping timeout: 245 seconds]
<companion_cube>
o/
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
<companion_cube>
whitequark: how am I supposed to fix this bug in containers? :(
<companion_cube>
no idea it generated empty archives for a start
<whitequark>
companion_cube: don't make empty libraries
<whitequark>
i.e. every OASIS Library should have at least one Module
lyxia has quit [Ping timeout: 272 seconds]
lyxia has joined #ocaml
<companion_cube>
but it's the case?
<whitequark>
... i don't even.
<companion_cube>
I'm looking at my _oasis file, and every sublibrary in containers has >= 1 module
<whitequark>
yes, i'm looking at it too
<companion_cube>
did I miss something?
<whitequark>
waitwaitwait
<whitequark>
commented in the issue
<companion_cube>
oh, ok
<companion_cube>
good thing, because I have no way to get my hands on an OS X device
<whitequark>
... you can install os x in virtualbox
<whitequark>
it is extremely painful
<whitequark>
but it is possible
<whitequark>
you will wish you'd have put your hands in an oven and waited for them to roast, but you *will* be able to compile ocaml code
<companion_cube>
yay! :D
<companion_cube>
next step is: cleaning up containers by removing some low quality stuff
lambdahands has quit [Ping timeout: 276 seconds]
manizzle has joined #ocaml
dsheets has quit [Ping timeout: 256 seconds]
lyxia has quit [Ping timeout: 255 seconds]
Submarine has quit [Remote host closed the connection]
ygrek has quit [Ping timeout: 240 seconds]
moei has quit [Quit: Leaving...]
moei has joined #ocaml
lyxia has joined #ocaml
oscar_toro has joined #ocaml
manizzle has quit [Read error: Connection timed out]
oscar_toro has quit [Ping timeout: 245 seconds]
oscar_toro1 has joined #ocaml
manizzle has joined #ocaml
lyxia has quit [Ping timeout: 264 seconds]
lyxia has joined #ocaml
mort___ has joined #ocaml
matason has joined #ocaml
chinglish has joined #ocaml
oscar_toro1 has left #ocaml [#ocaml]
oscar_toro1 has joined #ocaml
oscar_toro1 has quit [Quit: Leaving.]
oscar_toro has joined #ocaml
jgjl has quit [Ping timeout: 246 seconds]
huza has quit [Ping timeout: 276 seconds]
ollehar has joined #ocaml
zwer_b has joined #ocaml
zwer has quit [Ping timeout: 250 seconds]
Kakadu has joined #ocaml
dsheets has joined #ocaml
Haudegen has quit [Ping timeout: 240 seconds]
yomimono has joined #ocaml
Haudegen has joined #ocaml
<engil>
is there any painless way of downgrading a package, in Opam ?
<engil>
(other than: uninstall, pin, reinstall, I mean.)
<whitequark>
opam install pkg.0.1
AltGr has left #ocaml [#ocaml]
<engil>
awesome, thanks :)
<nicoo>
pippijn: IIRC, ctype can now produce external-style bindings (rather than the runtime purple magic that was going on), so it should be quite similar to external
<chris2>
when i use a locally scoped int ref in a function e.g. in a for loop, will ocaml unpack it into a machine register?
oriba has joined #ocaml
dsheets has quit [Ping timeout: 255 seconds]
<companion_cube>
sometimes, ocamlbuild -clean seems to block; do you also observe this?
avsm has joined #ocaml
<oriba>
someone here who useses ocamlnet 4.0.1? I had problems compiling my code.
_andre has joined #ocaml
jonludlam has joined #ocaml
siddharthv_away is now known as siddharthv
avsm has quit [Quit: Leaving.]
govg has quit [Ping timeout: 276 seconds]
govg has joined #ocaml
c74d has quit [Ping timeout: 265 seconds]
IbnFirnas has quit [Read error: Connection reset by peer]
manizzle has quit [Ping timeout: 252 seconds]
ggole has quit [Ping timeout: 276 seconds]
elfring has joined #ocaml
<ollehar>
oriba: you should post your error message
<oriba>
ollehar, it's a short one, so I post it here directly:
badon has quit [Remote host closed the connection]
oriba has quit [Quit: oriba]
lyxia has quit [Remote host closed the connection]
lyxia has joined #ocaml
thibm has joined #ocaml
lyxia has quit [Ping timeout: 245 seconds]
lyxia has joined #ocaml
lambdahands has joined #ocaml
lambdahands has quit [Ping timeout: 244 seconds]
c74d has joined #ocaml
siddharthv is now known as siddharthv_away
lyxia has quit [Ping timeout: 272 seconds]
matason_ has joined #ocaml
lyxia has joined #ocaml
matason has quit [Ping timeout: 246 seconds]
lyxia has quit [Ping timeout: 255 seconds]
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
siddharthv_away is now known as siddharthv
jonludlam has quit [Ping timeout: 244 seconds]
larhat has joined #ocaml
jonludlam has joined #ocaml
booly-yam-6137 has joined #ocaml
dsheets has joined #ocaml
reem has joined #ocaml
lyxia has joined #ocaml
<pippijn>
nicoo: ok, that's nice
<companion_cube>
so it's more efficient?
<pippijn>
the same, I suppose?
<pippijn>
I read that as "generates the same C code as you would write by hand"
<companion_cube>
I meant, compared with the dynamic stuff you usually get with ctypes
<pippijn>
ah yes
<pippijn>
presumably so
<ollehar>
can I write an apache plugin with ocaml?
<companion_cube>
no idea, but it sounds painful
<pippijn>
probably a lot of work
<flux>
sounds feasible, but you need to bind the parts you want to use from apache yourself
<flux>
in principle it would happen the same way you can put ocaml runtime in a library you use from C
<flux>
in other words: no idea how :-)
<pippijn>
you'll probably need a PIC version of the runtime
darkf has quit [Quit: Leaving]
lyxia has quit [Ping timeout: 264 seconds]
leowzukw has joined #ocaml
Denommus has joined #ocaml
Haudegen has quit [Ping timeout: 244 seconds]
lyxia has joined #ocaml
Thooms has joined #ocaml
Haudegen has joined #ocaml
Denommus has quit [Read error: Connection reset by peer]
Denommus has joined #ocaml
mbac has joined #ocaml
<adrien_znc>
companion_cube: imho, ctypes ability to generate code that is compiled statically rather than going through libffi is not in efficiency
<adrien_znc>
imagine you mess up the api description
<adrien_znc>
which safety do you get when going through libffi?
<adrien_znc>
but if you call gcc/clang to compile, you have warnings
<adrien_znc>
ollehar: you definitely can
<flux>
ah, I forgot about that ocamlnet comes with some apache module stuff
<flux>
not sure about its abilities though, ie. can it hook into stuff like authentication?
<flux>
(not sure = completely unaware)
lyxia has quit [Ping timeout: 264 seconds]
psy_ has quit [Read error: No route to host]
psy_ has joined #ocaml
psy_ has quit [Max SendQ exceeded]
psy_ has joined #ocaml
<engil>
Playing around with mirage, I have this list of bytes, of three elements according to List.length, but List.nth will just fail if I try to access the third element.
<engil>
any idea on how something like this is possible ?
<ggole>
zero indexed.
booly-yam-6137 has quit [Ping timeout: 255 seconds]
<engil>
:)
booly-yam-6137 has joined #ocaml
<flux>
accessing the third element should work fine, accessing the element number three should not work at all :)
<engil>
its not where the problem is
<engil>
the code is basically awful strings manipulations, resulting in a list of strings, which is supposed to be three elements long
<engil>
and it is, at least in a basic toplevel on my system
<engil>
but when using it in a mirage code, compiling to unix target, it fails when accessing the third element
<ggole>
As in, List.nth list 3?
<ggole>
Or as in List.nth list 2?
<engil>
as in List.nth list 2
<ggole>
Hmm.
<adrien_znc>
wrapped in a try ... with :P
<ggole>
I guess it's just a bug in mirage.
<adrien_znc>
for List.nth?
<ggole>
I mean that it is probably generating a shorter list on that system
<adrien_znc>
ah
<adrien_znc>
well, simplest is to give up List.nth and pattern-match and log
<adrien_znc>
probably more efficient code actually
<engil>
ok that was my fault, i'm just really bad at copy-pasting code between shells.
psy_ has quit [Ping timeout: 240 seconds]
Denommus has quit [Ping timeout: 272 seconds]
mbac has quit [Ping timeout: 265 seconds]
psy_ has joined #ocaml
keen__________38 has joined #ocaml
booly-yam-6137 has quit [Remote host closed the connection]
reem has quit [Remote host closed the connection]
keen__________37 has quit [Ping timeout: 264 seconds]
booly-yam-6137 has joined #ocaml
reem has joined #ocaml
enitiz has joined #ocaml
Thooms has quit [Quit: WeeChat 1.0.1]
reem has quit [Remote host closed the connection]
mort___1 has joined #ocaml
mort___1 has quit [Read error: Connection reset by peer]
mort___1 has joined #ocaml
mort___ has quit [Ping timeout: 272 seconds]
reem has joined #ocaml
booly-yam-6137 has quit [Remote host closed the connection]
booly-yam-6137 has joined #ocaml
reem has quit [Remote host closed the connection]
dsheets has quit [Ping timeout: 255 seconds]
uris77 has joined #ocaml
badkins has joined #ocaml
dsheets has joined #ocaml
mbac has joined #ocaml
George__ has joined #ocaml
booly-yam-6137 has quit [Ping timeout: 245 seconds]
vanila has quit [Quit: Leaving]
George__ has quit [Ping timeout: 246 seconds]
pyon has quit [Ping timeout: 276 seconds]
pyon has joined #ocaml
George__ has joined #ocaml
mort___1 has quit [Quit: Leaving.]
mort___ has joined #ocaml
booly-yam-6137 has joined #ocaml
ggole has quit []
struktured has quit [Ping timeout: 245 seconds]
shinnya has joined #ocaml
IbnFirnas has joined #ocaml
leowzukw has quit [Ping timeout: 246 seconds]
leowzukw has joined #ocaml
BitPuffin has joined #ocaml
aviraldg has joined #ocaml
aviraldg has quit [Read error: Connection reset by peer]
lambdahands has joined #ocaml
reem has joined #ocaml
oriba has joined #ocaml
rand000 has joined #ocaml
slash^ has joined #ocaml
lambdahands has quit [Ping timeout: 256 seconds]
lambdahands has joined #ocaml
<oriba>
where does opam store packages? how can they be used (is the eval-stuff needed always)? can opam save packages in any dir I want?
booly-yam-6137 has quit [Ping timeout: 252 seconds]
<mcc>
I'm trying to get back to some kind of minimally working state (meaning: I have sedlex + containers installed) before i get on a plane in just a few hours
<ggole>
mcc: yikes
<ggole>
Does opam switch work?
<flux>
well, regardless how you try to fix it, I would suggest concurrently making a new opam tree
<flux>
of course, you could also restore from backups :P
<flux>
mcc, btw, do you have the external solver installed?
<mcc>
Do I have backups? Please see the start of the gist-- I have a "you can revert" switch which opam gave me, but it gives a resolving failure
<mcc>
flux: i do not, do you think that would make the import work? that's aspcupd or... something, right?
<def`>
mcc: maybe pinning camlp4 to the version that was working? opam pin add camlp4 4.02.1+1
<flux>
aspcud is definitely worth a shot
<flux>
I think opam resolver might even be broken somehow, so much does aspcud seem to help
<mcc>
whitequark last night mentioned that opam should not be expected to work great without aspcud
olauzon has quit [Ping timeout: 245 seconds]
<mcc>
trying the pin now, thanks...
tane has joined #ocaml
<mcc>
a big part of my problem is this VERY old mac i'm developing on (hoping to replace it soon, so soon...), which makes it very hard to install software, and the hardness of installing means i've got everything installed via a patchwork of ports + homebrew (you are NOT supposed to run both of those on the same system)
<mcc>
so, "install aspcud" is... well... that could be opening a new can of worms.
<mcc>
it is possible that whatever broke is not ocamlp4, but actually something that changed in ports or brew from my failed attempt to upgrade ghc a couple weeks ago D:
<mcc>
very seriously: i am in the process of switching to linux, but i need new hardware, and i am having a cashflow problem right now which inhibits the purchase of any new hardware.
<mcc>
you can install linux on a mac, but not this one, because the hard drive is full :P
<Drup>
bah, external hard drive is much cheaper than you new pc
<flux>
mcc, there is a cloud-version of aspcud
<flux>
mcc, it may be easier to install
<mcc>
drup: oh gosh wow! that's cool
<mcc>
flux: oh, i think i heard about that :O
<mcc>
drup: i feel like the idea of running the OS off an external hard drive might be tricky... at least when one is on a train...
<Drup>
mcc: no, I mean, clean up your hard drive using the external one, format, install linux, done.
<seliopou>
avsm, dsheets: how are the mirage folks feeling about about ocaml-ssh?
<mcc>
short version: rewinding ocamlp4 failed with the shockingly unhelpful error ranlib; malformed object
oriba has quit [Quit: oriba]
<dmbaturin>
mcc: I'm using linux on a mac right now. I haven't booted OS X since the last time I wanted to test ocaml on OS X.
<def`>
mcc: wow, so pinning as nothing to do. your previous install had a valid ranlib, this no longer has
<dsheets>
seliopou needs to be updated
<mcc>
maybe restarting with a new opam/ocaml install is the way to go
<seliopou>
figured :P
<flux>
yes, you should be doing it regardless :)
<dsheets>
seliopou, should probably use nocrypto and if it uses melange, have that removed/updated to something new
<mcc>
def`: okay. ranlib is a system tool, correct? it has nothing to do with ocaml or opam?
<def`>
(so "opam pin remove camlp4" to get back to normal setup, and then… maybe gnu ranlib is being shadowed?! try to find which ranlib binaries are on your system)
<dsheets>
but we definitely want it :-)
<def`>
mcc: but there might be a gnu and an osx version
<mcc>
yeah. so i do `which ranlib`
reem_ has joined #ocaml
<mcc>
it finds /usr/bin/ranlib-- i.e., the os x version, which is what i expect
reem has quit [Read error: Connection reset by peer]
<def`>
and it is invoked during linking
<def`>
(of static archives only, i guess?)
<mcc>
i expect that if homebrew had somehow screwed me over by installing a new ranlib it would be in /usr/local/bin/ranlib
<def`>
which --all ranlib
<ggole>
mcc: locate might list a few more
<def`>
on linux, not sure what the command does on osx
<ggole>
(Does OS X have that?)
<mcc>
drup: if i do not resolve my cashflow problem soon, i will definitely be looking at either that, or just buying a cheaper laptop.
<mcc>
def`: hm. apparently not there. i'll look for one through other means
<mcc>
ggole: funny story, os x has locate, but last i remember it doesn't run updatedb automatically
lyxia has quit [Ping timeout: 244 seconds]
<mcc>
i'll resort to good old find
<ggole>
I have a gcc-ranlib, hmm.
<companion_cube>
mcc: hi
<mcc>
companion_cube: hi! the problem i was having last night was not your fault at all! sorry about that!
<companion_cube>
yeah, I saw. No problem :)
<dmbaturin>
Another emergency solution: setup a linux VM. :)
<mcc>
that's... not out of the question. the problem here is basically "how close to working can i get by the time my plane leaves at 1:30 PM?"
<ingsoc>
this suggests "Batteries Included" is required for list comprehensions
<mcc>
i have put myself in a situation where i am limited enough on time and hard drive space that some of the more straightforward options might not work :/ ugh
<ingsoc>
this suggests it is included in standard ocaml
<ingsoc>
I couldn't get the example to work
<Drup>
ingsoc: list comprehension is not in batteries anymore
<ingsoc>
# #require "camlp4.listcomprehension";;
<ingsoc>
this errors
<ingsoc>
[ x / 2 | x <- [ 2;4;6] ];;
<companion_cube>
ingsoc: list comprehensions aren't that nice, now that |> is standard
<seliopou>
dsheets readme says there's a client in there, but I'm not seeing it
<companion_cube>
you can live pretty well without them
<Drup>
do "#camlp4o ;;" before the require
<seliopou>
i assume the docs are wrong, as opposed to my grepping skillz?
<dsheets>
seliopou, probably docs are wrong, maybe file an issue and avsm will see it?
booly-yam-6137 has joined #ocaml
PM has quit [Ping timeout: 252 seconds]
<seliopou>
rgr
<ingsoc>
Drup: OK, I noticed what you asked me to type is printed in the banner on starting utop
<ingsoc>
#camlp4o;; to load camlp4 (standard syntax)
<ingsoc>
list comprehensions now work after doing that, then doing...
<ingsoc>
#require "camlp4.listcomprehension";;
<ingsoc>
what does all this mean
<ingsoc>
:)
badkins has quit []
<ingsoc>
companion_cube: and why do you say you don't need them now there's "|>"
<companion_cube>
ingsoc: it's easy to write [2;4;6] |> List.map (fun x -> x/2) |> List.filter (fun x -> x > 3) |> ....
<companion_cube>
well, easy enough for my taste, obviously it's a matter of taste
blandflakes has joined #ocaml
<Drup>
ingsoc: it loads a syntax extension
<ingsoc>
"|>" so this pipes the result of the left hand expression to an additional argument to the expression onthe right
<ingsoc>
aplogies for the noob questions btw
<ingsoc>
its just a new set of terminology and tools
<ingsoc>
so what is the difference with
<ingsoc>
#camlp4r;; to load camlp4 (revised syntax)
<ingsoc>
the revised syntax
<ingsoc>
and how do you find out what it adds
<ingsoc>
and what "require" needs it
<companion_cube>
ingsoc: yes, x |> f is like f x
<companion_cube>
but precedence makes it easy to chain
<companion_cube>
x |> f |> g |> h is h (g (f x))
<mcc>
update: I only have one ranlib named `ranlib`, I have some alternate ranlibs but they're all namespaced (llvm-ranlib, etc...)
<mcc>
i think... i think i'm gonna try to back out my whole opam
<mcc>
if i just move ~/.opam out of the way and start over, that will basically blow away EVERYTHING, right?
swgillespie has joined #ocaml
<Drup>
yeah
<mcc>
actually even my ocaml is in ~/opam...
<Drup>
you will just have to recompile everything, annoying but no big deal.
<mcc>
long as i can make my flight :)
<ingsoc>
ok last question for now
hekmek has joined #ocaml
<ggole>
You could try a simple switch first
<ingsoc>
#require "camlp4.listcomprehension";;
<ingsoc>
#require "package";; to load a package
<ggole>
eg back to 4.02.0 or something
<ingsoc>
what is a package v a module
<mcc>
4.02.1 is the first version that worked for me, and i think i need it... was ppx added for 4.02 or 4.02.1?
swgillespie has quit [Client Quit]
<ingsoc>
#require "camlp4.listcomprehension";; verses open Core.Std
<Drup>
mcc first
<ingsoc>
package V module
<ggole>
Ah, never mind then
<mcc>
drup: you mean, it was added for 4.02? ok
<mcc>
thank you all so much for the help
<def`>
ingsoc: a module is an entity of the language (like a type, an expression, etc)
jwatzman|work has joined #ocaml
<ingsoc>
def`: anda package ?
<def`>
ingsoc: a package is… hmm, some settings for the toolchain
<ingsoc>
: /
<ingsoc>
:)
<ingsoc>
How do i know when to choose either of the following...
<ingsoc>
#camlp4o;; to load camlp4 (standard syntax)
<ingsoc>
#camlp4r;; to load camlp4 (revised syntax)
<ingsoc>
and why
<def`>
ingsoc: usually to setup a path to find the files needed to compile and link a module, or some syntax extensions…
<ingsoc>
lol
<def`>
always use standard syntax
<def`>
easy, so usually, you don't touch #camlp4…;; settings
<ingsoc>
def`: what i don;t understand is why I had to do...
<ingsoc>
#camlp4o;;
<ingsoc>
before...
<ingsoc>
#require "camlp4.listcomprehension";;
<ingsoc>
to get list comprehensions working
<ingsoc>
if #camlp4o;; is standard which i presume default
<ingsoc>
oh ok camlp4 is some kind of preprocessor ?
<def`>
yes
<ingsoc>
like macro type interpreter thing
<ingsoc>
?
<def`>
(it's deprecated, the new way to get a similar effect is to use ppx, which has no effect on the surface language but instead use java-like annotations)
<def`>
it's a tool to extend the syntax and desugar extensions to plain ocaml
<mcc>
it's just... very mysterious to me. containers does not seem to be doing anything unusual at all.
chinglish has quit [Quit: Nettalk6 - www.ntalk.de]
<ggole>
malformed object (unknown load command 3) is a bit suspicious
<mcc>
yes
<mcc>
i wish i knew how to interpret that
<ggole>
That's the system linker, not the ocaml tool chain (I think)
<ggole>
Did you do something with XCode recently?
<mcc>
it is indeed the system linker
<mcc>
i didn't do anything with xcode, however, i did a bunch of stuff with brew
<ggole>
Hmm
<ggole>
I get hits for a tool called install_name_tools
<ggole>
But I don't know what that is.
<mcc>
install_name_tool is a ... it's like an extension of otool. there's these things that are sort of like environment variables that get embedded into dylibs, and install_name_tool can modify them
<mcc>
and... I know Misty, so maybe i can beg her for help >_>
<mcc>
Maybe I just won't work on Emily this trip
<mcc>
or make a branch without containers, although that seems very silly
enitiz has quit [Quit: Leaving]
<ggole>
Huh, small world
<mcc>
sorry about all this, thanks all for the help
<companion_cube>
oh right, you're the author of Emily? the language with prototypes and call/cc ? :)
<ggole>
Yeah, no worries
<Drup>
it's not really call/cc
<mcc>
companion_cube: hahaha... yes >_> it uses containers. thanks! and i'm REALLY UNCERTAIN i should have added call/cc
<mcc>
it's not call/cc but you can implement call/cc on top of it.
Haudegen has quit [Ping timeout: 265 seconds]
<companion_cube>
well, if you have call/cc you won't need to implement many other things :D
<companion_cube>
including exceptions and the like
<mcc>
i am hoping to implement exceptions on top of this or something like this.
<mcc>
however, i'm nervous, because to me an important part of exceptions is finally{}
<mcc>
and i don't understand how finally{} is compatible with continuations of any kind
<companion_cube>
no idea, sorry
<companion_cube>
but the literature on call/cc related to scheme is large
Haudegen has joined #ocaml
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
psy_ has quit [Read error: No route to host]
<mcc>
it's true :O
<companion_cube>
if you want your brain destroyed, lookup "amb operator" or something similar
<ggole>
I think finally is just sugar around the catch primitive
<Drup>
companion_cube: amb is the precise reason why I don't think call/cc is such a good idea ...
<companion_cube>
:)
<companion_cube>
I'd rather mention performance, but well
<Drup>
that too
<Drup>
I think all the continuation manipulation functions are much too hard to understand and you can do most of their uses with simpler features
<ingsoc>
so considering "ppx" or whatever is the new way of doing what camlp4 does. Is it wise to do what i did to get list comprehensions working. are list comprehensions not used as much in ocaml compared to other languages ?
<ingsoc>
just wondering about idiomatic ocaml
<Drup>
ingsoc: almost nobody uses list comprehensions
<ingsoc>
Drup: this kinda explains the hoops i seem to have gone through to get the feature
<ingsoc>
:)
<Drup>
basically, it's not useful
<companion_cube>
in general, syntax extensions see disparate adoption
<companion_cube>
a few (code generators) are widely used though
<Drup>
you have equivalent and native way to do the same thing without yet-another piece of syntax
<ingsoc>
I see |> as a recent addition to tha core language/lib
<ingsoc>
is this deemed useful
<companion_cube>
yes it is
<mcc>
anything i might have done with list comprehensions, it seems to me one can do with map and filter
<companion_cube>
exactly
<mcc>
list comprehensions are a feature i think of as being most useful in languages where higher-order functions are awkward to use
<ggole>
Comprehensions give you fusion without compiler magic
<mcc>
but if you like the syntax you like the syntax
<Drup>
mcc: things starting with . are tags, in emily, right ?
<ggole>
Which is... not really all that crushingly important
<Drup>
ggole: it doesn't really
<companion_cube>
if you need high performance with lists enough to justify fusion, you can write a recursive function manually
<mcc>
drup: the term i'm using is atoms, but tags sounds right? .fish is a value and .fish is always == .fish and .fish is never == "fish"
<ggole>
Depends on how they are implemented, I guess
<Drup>
mcc: so yes, tags
<mcc>
ingsoc: i use @@ more often but ... @@ does something weird around constructors.
<mcc>
drup: what language/community does the "tags" terminology come from?
<Drup>
mcc: or unary polymorphic variant :p
<ggole>
mcc: you use those for fields?
<Drup>
tag is pretty common I think
<mcc>
ggole: in Emily, yes
<ggole>
They look a bit like keyword symbols in Lisp
<Drup>
I've seen it used in functional and imperative communities
<mcc>
ggole: they are a lot like keyword symbols in lisp, and i'm thinking about trying to steal Common Lisp's keyword namespacing at some point
<mcc>
ggole: Emily is modeled a lot after lua/js which use strings for field names, but then horrible problems like dropbox crashing because you named a folder __PROTOTYPE__ occur...
<ggole>
Ah, yeah
<mcc>
also atoms are known at compile time, so i can intern them later...
<Drup>
mcc: and what is the namespace story ?
<mcc>
drup: at the moment there is no namespace story... but you mean, namespacing for atoms?
<Drup>
yes
<mcc>
All atoms share one namespace. I anticipate this becoming a problem at some point.
<Drup>
they are global for the whole word and that's all ?
<mcc>
Yes. They really are just specially typed interned strings.
<ingsoc>
mcc: this is true, and also the same in other languages but people have found that for certain stuff it has been a nicer syntax that warrants addition like for simple operations on list members and filtering etc without having to define functions jsut to perform them
jonludlam has joined #ocaml
<Drup>
so basically like polymorphic variant :p
<ggole>
Usually in the table/object languages namespaces are just another table.
<mcc>
ingsoc: yes
<ggole>
Eg math.sin in lua is a table lookup.
<ingsoc>
but i spose ocaml syntax for decalring funs etc is less cluttered
<companion_cube>
erlang has interesting things, as a dynamic language
<mcc>
So one thing I am thinking about is, like... it should be possible for unique atoms to be created, or created in macros, or something
<Drup>
mcc: and why are symbols not allowed to be tags name ?
<ggole>
mcc: oh, a symbol that is guaranteed nonequal to any other symbol?
<Drup>
rewriting + in .plus seems rather arbitrary.
<mcc>
ggole: yeah
<ggole>
That's a bit like Lisp too
<ggole>
Which has a gensym construct you are expected to use to make your macro-generated names not collide.
<mcc>
At this point I could have, like, an enum object, you have an enum K, and there are four or five fields on it, each of which is a unique atom... once i have some fancier stuff in place you could imagine a magical Namespace object that creates a new atom each time a new field is accessed on it...
<mcc>
Then I have namespacing without having to add a new syntax construct
<mcc>
Drup: The difference between + and .plus is precedence.
yomimono has quit [Ping timeout: 264 seconds]
<Drup>
ok
<Drup>
(you should drop the ^)
<Drup>
(really.)
<mcc>
Drup: I agree I should drop the ^. What I want to try in the next version is ruby flavored { x | x + 1 } methods
<ingsoc>
is there a way to get arguments required and types and/or documentation from a utop top level
<ingsoc>
for modules and functions
<Drup>
ingsoc: "f ;;"
<Drup>
no doc, though
<ggole>
#show for modules and types
<ggole>
The documentation support is patchy, unfortunately
<ggole>
No docstrings.
<ggole>
mcc: are you gonna have docstrings?
psy_ has joined #ocaml
<mcc>
ggole: docstrings are super nice but i don't know how to fit them into the language.
<mcc>
ggole: I guess ocaml has that too now, with ppx. [@ mleh ] or something
<Drup>
mcc: anyway, as I told you, /me is waiting for the type system.
<mcc>
drup: EXTREMELY reasonable, IMO.
<Drup>
no, I mean, not to use it
<Drup>
to have an opinion :p
<mcc>
Also reasonable!
<mcc>
ggole: anyway the problem is, if i have docstrings, how are they extracted? I mean, do you want them extractable at runtime?
<ggole>
Hmm, depends on what kind of language you are after.
<ggole>
Available at runtime is what Python and Lisp do.
<mcc>
How does LISP associate docstring data with a function?
<mcc>
I mean, like, how does the runtime manage that information?
<ggole>
Traditionally by stashing in plists
<mcc>
so like, you have an anonymous function-- can it have a docstring?
<ggole>
(Which are an associative list hanging from each symbol.)
<ggole>
In a lot of lisps an anonymous function is just a bunch of conses, so the docstring lives in those
<whitequark>
ew
<ggole>
If you have proper structures for functions, you would have a slot for the docstring.
<ingsoc>
are there any ocaml features that a noob should take extra notice of such as something that is different from most(all?) other languages ? or any other feature that is really cool and why you use ocaml
leowzukw has quit [Ping timeout: 246 seconds]
leowzukw has joined #ocaml
<ggole>
ingsoc: the structural typing bits, probably
siddharthv is now known as siddharthv_away
<mcc>
at the moment i do not have proper structures for functions, which is the problem.
<Drup>
I don't think the structural typing bits are a good thing to introduce to beginneres
<Drup>
-e
leowzukw has quit [Client Quit]
<ggole>
ingsoc: those are complicated enough that you should probably take a look at them after you are a bit more familiar with the basics, though
<mcc>
ingsoc: i think the first thing i'd say is, match
<Drup>
ingsoc: just follow RWO, you'll see things in the order
<ggole>
Gah, plists aren't involved at all: I was thinking of indentation specs in emacs
<ggole>
Stupid memory.
<mcc>
ingsoc: haskell and hax and a couple other things have ML-like match things, but well, they got it from ML :)
<ggole>
It's getting around now
<mcc>
ingsoc: the other thing I like is stuff like "+" and "while" and all those other syntax contstructs being only functions
<ggole>
Swift and Rust and some other newish things
<mcc>
ingsoc: the reason I like this is it means I can just like… run "map" or something on +. Which I can't do in python
<ingsoc>
mcc: ok that is interesting and kinda negates creating a anon fun to do simple stuff over a set/list
<ingsoc>
which you would otherwise use list comp
alkoma has joined #ocaml
<mcc>
Yeah, although like… uh, let's see. ocaml will let you do like List.map (3+) list but not List.map (+3) list, right? That's a haskell specialty?
<ggole>
List.map ((+) 3)
<ggole>
But that's a bit different: it passes 3 as the *first* argument to +
<ggole>
Haskell's sections are a bit slicker than that
<mcc>
reverse a b c = a c b;; List.map (reverse (+) 3)
<mcc>
There
<mcc>
ggole: anyway about what you said a minute ago-- i guess... there is this question of what kind of language i'm trying to make. and maybe i got a little confused about this at some point. originally the goal was "i want gradually typed Lua with better C++ interop". less ambitious goal.
<ggole>
Hmm, typed lua
<mcc>
there *is* a typed lua project, by the way
<mcc>
very exciting
<ggole>
I think there is a... right
* whitequark
pesters mcc about reading about typed racket
dsheets has quit [Ping timeout: 272 seconds]
<Drup>
whitequark: +1
<mcc>
i wanna read about typed rackettt
<mcc>
ok maybe that'll be what i do on the plane since i can't write ocaml :P
<whitequark>
you can't?
<ggole>
It's pretty cool. They have some nifty stuff like variadic functions.
<whitequark>
ggole: latent predicates!
<Drup>
arguably, you not being able to code and do your reading homework instead is a good thing for the language :D
<whitequark>
one of the best parts imo
<mcc>
drup: haha
<mcc>
whitequark: i never fixed my ranlib problem, so i can write ocaml, but only as long as i don't need to use containers, camlp4, or anything that uses ranlib/ar in compiling itself D:
<ggole>
I've been wondering lately about the link between GADTs and gradual typing
<whitequark>
oh
<whitequark>
did not the xcode thing work?
<mcc>
which xcode thing? my xcode is literally four or five years old and hasn't been touched since.
<whitequark>
ok
<whitequark>
apple is aggravating :/
<mcc>
yes. they are.
<mcc>
the problem here is probably not apple but that brew or ports broke something.
elfring has quit [Read error: Connection reset by peer]
<Drup>
ggole: I hate haskell's partial application on infix operator with all my heard
elfring has joined #ocaml
<ggole>
It seems to me that if you have a dynamic language where values are type _ t = Int : int -> int t | Float : float -> float t | ..., then gradual type checking is a lot like providing a witness that a given term is a foo t
<Drup>
( + 3) being the + applied on the **SECOND** argument is
enitiz has joined #ocaml
MrScout has quit [Ping timeout: 245 seconds]
<Drup>
so fucking confusing
<ggole>
Drup: but it's nicer for (< x)!
<ggole>
(Yeah, it's a bit automagical.)
<Drup>
ggole: (>) x
<Drup>
.
<mcc>
ggole: anyway, at some point, the "point" of Emily wound up being this everything's-a-combinator idea, which really just means "everything can be a function application", and I seem to be chasing that rabbit occasionally more so than thinking about what exactly the practical benefits are.
<mcc>
ggole: but the everything's-a-function-application makes things weird cuz like, i can just haul off and define the function (x ^b = b + 1), and you can't like... get a field out of x, if you said x.docstring it tries to add 1 to docstring
<Drup>
mcc: I await with great impatience the point at which you will want to optimize your language
<Drup>
because "only function + tags" is going to be slow as fuck.
<ggole>
Hmm, that's a brave approach to language design
<ggole>
(Probably more fun than reading fifty textbooks before you start though.)
<mcc>
ggole: i could have, like, some magic properties object, like you say (properties x).docstring. but! One of the reasons I'm doing this is *x might be a c++ object*
<mcc>
i.e., the language doesn't *know* what x is, until it does an application, unless there is type information in scope
<mcc>
oh and oops there's no type system in the language yet, so it's hard to guess what that means
<companion_cube>
mcc: you might find ideas in J, too :>
<mcc>
ggole: it's an experiment, and at some point it will have to get serious, and then i'll read "Types and Programming Languages" :P
<mcc>
Maybe!
<mcc>
drup: also oh my gosh it is slow. it is so INCREDIBLY slow. You have NO IDEA.
<ggole>
mcc: I see
<companion_cube>
Drup: who knows, "only functions" can be relatively fast if compiled to a stack machines?
<mcc>
I mean like lua runs sort of fast, but it doesn't use tags for like... ASSIGNING VALUES ON SCOPES.
MrScout has joined #ocaml
<companion_cube>
I mean, forth is only made of functions, in some sense, yet some compilation schemes make it fast
<mcc>
I'm assuming that there will be some intermediate AST where it figures out which additions are actually additions, pre-constructs scope objects etc
<Drup>
companion_cube: "3 + 4" is the function 3 applied to add that returns the function addition on 3 and apply it to 4
<mcc>
but that is gonna be WAY more complicated looking than the current interpreter
<ggole>
mcc: what do you mean? lua has a two-word tagged representation, doesn't it?
<ggole>
(But not luajit, which does its own crazy stuff.)
<Drup>
companion_cube: It's going to be slow without some clever execution scheme.
<mcc>
ggole: I don't know how Lua's implemented, actually. I just know it has a + operator :P i don't :P
mxv has joined #ocaml
<ggole>
There's a nice paper on the lua 5.2 internals if you're curious
<mcc>
i'll take a look, thank you
<mcc>
everything i've read by the lua people is just... really good. they thought very clearly about all their decisions in this language.
<ggole>
Yeah. It's pleasantly small, too.
<mcc>
yes.
olauzon_ has joined #ocaml
<mcc>
okay, so let's say since i can't do what i hoped to do, my goals for the trip are to read the typed racket manual on the plane :P
<ingsoc>
List.map (fun x -> (x:int) * 2) [1;2;3];;
<ingsoc>
in what circumstances is type annotating required
<mcc>
ingsoc: almost none
<mcc>
ingsoc: type annotating is usually done in the process of debugging
<mcc>
ingsoc: in my experience anyway. the type system is complaining "X should be Y, but instead it is Z". but you know Z is correct. this means something is wrong somewhere *else*, and the type inferrer made a wrong guess.
<ggole>
ingsoc: in signatures (which are optional)
lambdahands has quit [Ping timeout: 246 seconds]
<mcc>
ingsoc: so you just start adding type annotations to things until you find where the *real* bug (the thing that confused the type inferer into mis-guessing) is
<ggole>
There are some uncommon circumstances in which annotations are needed, but you can ignore those until you run into them.
<mcc>
hm. is it possible to download the racket docs onto my computer, i wonder...
<ingsoc>
i guess there are circumstances where a type of something cannot be determined if the only usage is from data outside the program. in this case the compiler would use a generic type ? and so annotating with the expecting input types would improve performance (not that I am thinking of premature optimisation, i am just asking)
<Drup>
mcc: or you use merlin to follow the types
<ingsoc>
i mean, the only parameters coming from external sources
<Drup>
slightly easier
<ingsoc>
not known to the compiler
<ingsoc>
if that is possible
<mcc>
Drup: Or that.
<Drup>
ingsoc: no, that don't happen, there is no such thing as "external sources of unknown types"
<ggole>
ingsoc: with some exceptions, annotation doesn't really affect performance
<Drup>
either you know or you check
enitiz has quit [Quit: Leaving]
enitiz has joined #ocaml
reem_ has quit [Remote host closed the connection]
badkins has joined #ocaml
booly-yam-6137 has quit [Ping timeout: 244 seconds]
hekmek has quit [Quit: Verlassend]
Thooms has quit [Quit: WeeChat 1.0.1]
malc_ has joined #ocaml
fds has joined #ocaml
fds has left #ocaml [#ocaml]
<mcc>
OK, I now have a copy of Racket installed and plans for what I'm gonna do on the airplane ^_^
WraithM has joined #ocaml
WraithM has quit [Client Quit]
jonludlam has quit [Quit: Coyote finally caught me]
badon has joined #ocaml
<struk|work>
mcc: how long is your trip?
mcc has quit [Ping timeout: 245 seconds]
slash^ has quit [Read error: Connection reset by peer]
elfring has quit [Read error: Connection reset by peer]
elfring has joined #ocaml
thibm has quit [Ping timeout: 264 seconds]
manizzle has joined #ocaml
mahem1__ has quit [Ping timeout: 256 seconds]
mort___ has joined #ocaml
_andre has quit [Quit: leaving]
tani has joined #ocaml
IbnFirnas has quit [Ping timeout: 244 seconds]
elfring has quit [Read error: Connection reset by peer]
reem has joined #ocaml
mxv has quit [Ping timeout: 264 seconds]
IbnFirnas has joined #ocaml
tane has quit [Ping timeout: 276 seconds]
elfring has joined #ocaml
elfring has quit [Ping timeout: 246 seconds]
elfring_ has joined #ocaml
ggole has quit []
lordkryss has joined #ocaml
elfring_ has quit [Ping timeout: 265 seconds]
rand000 has quit [Ping timeout: 240 seconds]
PM has joined #ocaml
mort___ has left #ocaml [#ocaml]
AlexRussia has quit [Ping timeout: 265 seconds]
Hannibal_Smith has joined #ocaml
reem has quit [Remote host closed the connection]
AlexRussia has joined #ocaml
enitiz has quit [Ping timeout: 245 seconds]
malc_ has quit [Quit: leaving]
rand000 has joined #ocaml
thibm has joined #ocaml
thibm has left #ocaml [#ocaml]
jwatzman|work has quit [Quit: jwatzman|work]
ingsoc has quit [Ping timeout: 240 seconds]
ingsoc has joined #ocaml
ousado has quit [Read error: Connection reset by peer]
ousado has joined #ocaml
ousado has quit [Changing host]
ousado has joined #ocaml
AlexRussia has quit [Ping timeout: 245 seconds]
AlexRussia has joined #ocaml
rock_neurotiko has joined #ocaml
rand000 has quit [Ping timeout: 276 seconds]
ingsoc has quit [Quit: Leaving.]
arj has quit [Quit: Leaving.]
enitiz has joined #ocaml
Thooms has joined #ocaml
rock_neurotiko has quit [Remote host closed the connection]
ebzzry has quit [Remote host closed the connection]
enitiz has quit [Excess Flood]
rand000 has joined #ocaml
enitiz has joined #ocaml
jonludlam has joined #ocaml
reem has joined #ocaml
enitiz has quit [Ping timeout: 245 seconds]
<moviuro>
Hi all! I'm running into some troubles with unison. Any chance that there are some contributors here?