<eeks_>
What I would like is to be able to write an unpack function of that sort:
<eeks_>
let unpack (module F : Z) = F.make
sh0t has joined #ocaml
<eeks_>
But the type system fails because the internal type of module F is not exported.
<eeks_>
When I use a non-parametric type, it works:
<eeks_>
let unpack (type s) (module F : Z with type t = s) = F.make
<eeks_>
val unpack : (module Z with type t = 'a) -> unit -> 'a = <fun>
mac10688 has quit [Ping timeout: 240 seconds]
<eeks_>
But I am scratching my head on how to write that type specification when the internal type is parametric
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
<def`>
eeks_: like yesterday, it is not possible
<eeks_>
def` oh yeah, I am just realizing now that the two issues are related :
<eeks_>
:/
<eeks_>
silly me
<eeks_>
thx
<eeks_>
why that by the way ? Is that by design ?
mahasamoot has joined #ocaml
sgnb` has joined #ocaml
sgnb has quit [Ping timeout: 265 seconds]
<def`>
eeks_: somehow "by design", by theoretical issues :)
<def`>
you can read lightweight higher kinded types
<eeks_>
Cool, thanks for the pointer. I'll got through it.
<def`>
polymorphism* sorry, by white and yallop, available online
<def`>
they describe the issue and offer a workaround
<def`>
if you really need it, you can use this encoding, but it is more a proof of concept than something you should use in production :)
<eeks_>
I found it :p
<eeks_>
Actually, it's not so much of a problem. It just make the end solution less elegant.
<eeks_>
I just wanted to make sure I was not missing something.
<eeks_>
Oh gosh yes I see why I should not use that workaround in production.
govg has quit [Ping timeout: 265 seconds]
<Algebr`>
Lwt_main.at_exit exectutes regardless of program exit, correct?
<Algebr`>
reason
<def`>
probably not in case of segfault :)
<Algebr`>
heh
<Algebr`>
I am seeing lots of people say they come to OCaml only after first failing at haskell. What can we do to make them come to OCaml first? :)
<def`>
ddos haskell.org?
<Algebr`>
I'm looking for long term solutions
<def`>
squat haskell.org domain
<Algebr`>
the haskell website is so beautiful. I like it better than ocamls
<def`>
sorry I am not in a serious mood :p
<Algebr`>
haha
<def`>
to answer your question about lwt: at_exit uses the "standard" infrastructure from stdlib
<Algebr`>
seriously, the haskell website has a repl immediately in your face and code to run flanked by videos
<def`>
exit handlers are run by the Std_exit module (which you should never have heard of)
<Algebr`>
I have never heard of this module
<def`>
which is the last linked one so will execute after initialisation of all your podules
<def`>
modules*
<Algebr`>
ha, clever.
<def`>
therefore the only way for an at_exit to not be honored, beside your process dying, is for a module to let an exception escape
<def`>
a top level exception shutdown everything after
govg has joined #ocaml
<def`>
(otherwise you would have an half initialised module, that would be unsafe... although in the case of stdexit it should be fine as it shouldn't not be possible to refer to anything after point of failurebut this is beyond knowledge of the typechecker)
nullremains has quit [Ping timeout: 264 seconds]
shinnya has quit [Ping timeout: 240 seconds]
<Algebr`>
def`: OKay so to be clear. at_exit will be called when program exits normally but not if uncaught exception bubbles up
<def`>
da
teknozulu_ has quit [Ping timeout: 265 seconds]
<def`>
this case can be caught by Printexc.set_uncaught_exception_handler iff you really need to clean things up
<def`>
(which in turn will work only if OCaml runtime initialization succeedee, and I am not going to tell you hownto work around that :))
<Algebr`>
def`: where is a hidden knowledge ocaml blog post
<Algebr`>
WHAT!! lablgtk2 now uses native OS X windows!?
kushal has joined #ocaml
rossberg has quit [Ping timeout: 264 seconds]
struk|desk2 is now known as struk|desk|away
skeuomorf has joined #ocaml
jeffmo has joined #ocaml
rossberg has joined #ocaml
kushal has quit [Ping timeout: 276 seconds]
kushal has joined #ocaml
kushal has quit [Ping timeout: 245 seconds]
Denommus has joined #ocaml
lostman_ has quit [Quit: Connection closed for inactivity]
copy` has quit [Quit: Connection closed for inactivity]
cg has joined #ocaml
cg is now known as cgx
kushal has joined #ocaml
sh0t has quit [Remote host closed the connection]
<cgx>
if I have two types, `type a = Foo | Bar of int` and `type b = Foo | Baz of bool`, how can I specify which `Foo` I want to construct?
<def`>
Traditional way: modules
<def`>
module A = struct type a = Foo | Bar of int end module B = struct .. end;;
<cgx>
gotcha
<Algebr`>
What is non traditional way, gadt?
<cgx>
so there's no way to be more explicit?
<def`>
No no, something much simple :), no need to change type declarations :P
<def`>
juste put a type annotation to disambiguate
<def`>
let x = (Foo : a);;
struk|desk|away is now known as struk|desk2
<cgx>
okay -- so what if I have a function, `let f a = match a with | Foo -> 0 | _ -> 1`
<cgx>
err wait, `let f a = match a with | Foo -> 0 | Bar _ -> 1`
<def`>
let f (a : a) = match a with Foo -> 0;;
<def`>
let f : a -> _ = function Foo -> 0
<def`>
let f = function (Foo : a) -> 0
<def`>
... choose your style :P
<cgx>
cool, thanks!
<def`>
(putting the annotation earlier is better wrt to "principality", the typechecker might complain that it is ambiguous to annotate only one branch if there is multiple ambiguities)
divyanshu has quit [Quit: Computer has gone to sleep.]
divyanshu has joined #ocaml
jeffmo has quit [Ping timeout: 250 seconds]
cg has joined #ocaml
cg has quit [Client Quit]
struk|desk2 is now known as struk|desk|away
Denommus has quit [Ping timeout: 245 seconds]
croma has joined #ocaml
<croma>
Hi
<nullcatxxx_>
hi
<croma>
I'm having a bit of trouble with the ocamldebug utility and I was hoping someone here would be able to help
<nullcatxxx_>
no experience with that, sorry :(
darkf has joined #ocaml
Guest50255 has quit [Ping timeout: 265 seconds]
MercurialAlchemi has joined #ocaml
divyanshu has quit [Quit: Computer has gone to sleep.]
jeffmo has joined #ocaml
divyanshu has joined #ocaml
govg has joined #ocaml
Haudegen has quit [Ping timeout: 245 seconds]
Algebr` has joined #ocaml
mort___ has joined #ocaml
Snark has joined #ocaml
ygrek_ has joined #ocaml
Simn has joined #ocaml
yawnt has joined #ocaml
freehck has joined #ocaml
govg has quit [Ping timeout: 256 seconds]
yawnt_ has joined #ocaml
Haudegen has joined #ocaml
divyanshu has quit [Quit: Computer has gone to sleep.]
Sim_n has joined #ocaml
f[x] has joined #ocaml
kansi has quit [Ping timeout: 240 seconds]
cat5e has quit [Ping timeout: 240 seconds]
Simn has quit [Ping timeout: 240 seconds]
ygrek_ has quit [Ping timeout: 240 seconds]
mietek has quit [Ping timeout: 240 seconds]
fluter has quit [Ping timeout: 240 seconds]
cat5e has joined #ocaml
mietek has joined #ocaml
fluter has joined #ocaml
Algebr` has quit [Ping timeout: 240 seconds]
mort___ has quit [Quit: Leaving.]
yawnt has quit [Disconnected by services]
yawnt_ is now known as yawnt
yawnt has quit [Changing host]
yawnt has joined #ocaml
govg has joined #ocaml
jeffmo has quit [Quit: jeffmo]
divyanshu has joined #ocaml
rand has joined #ocaml
rand is now known as Guest19980
f[x] has quit [Ping timeout: 265 seconds]
kakadu has joined #ocaml
kansi has joined #ocaml
sgnb` is now known as sgnb
silver has joined #ocaml
<yawnt>
quit
yawnt has quit [Quit: leaving]
yawnt has joined #ocaml
Algebr` has joined #ocaml
croma has quit [Quit: Page closed]
jwatzman|work has joined #ocaml
Algebr` has quit [Ping timeout: 240 seconds]
beginner_ has joined #ocaml
sillyotter has joined #ocaml
<beginner_>
how can i compile ocaml in such a way that i can put all the executables and libraries into one folder so that i can copy this folder to a different machine and it still finds all the dependent ml files in this folder
larhat1 has quit [Quit: Leaving.]
_andre has joined #ocaml
<def`>
relocatable build...
<def`>
under unix?
<silver>
static link all the things
<beginner_>
relative paths are not possible?
divyanshu has quit [Quit: Computer has gone to sleep.]
<def`>
is it unix and if it is, are the different machines running the same os?
<beginner_>
under linux yes, but i would need the same for windows
divyanshu has quit [Quit: Computer has gone to sleep.]
yawnt has quit [Ping timeout: 250 seconds]
Guest19980 has quit [Ping timeout: 240 seconds]
zpe has joined #ocaml
divyanshu has joined #ocaml
Haudegen has joined #ocaml
govg has quit [Ping timeout: 240 seconds]
yawnt has joined #ocaml
JacobEdelman has joined #ocaml
divyanshu has quit [Quit: Computer has gone to sleep.]
<flux>
nice!
Algebr` has joined #ocaml
Haudegen has quit [Ping timeout: 264 seconds]
govg has joined #ocaml
Stalkr_ has joined #ocaml
BitPuffin has joined #ocaml
divyanshu has joined #ocaml
<beginner_>
what is the current state for opam on windows?
Haudegen has joined #ocaml
wolfcore has quit [Ping timeout: 264 seconds]
Algebr` has quit [Ping timeout: 240 seconds]
wolfcore has joined #ocaml
divyanshu has quit [Quit: Computer has gone to sleep.]
BitPuffin has quit [Disconnected by services]
itPuffinB has joined #ocaml
FreeBird_ has joined #ocaml
itPuffinB is now known as BitPuffin
lostman_ has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 272 seconds]
FreeBird_ has quit [Ping timeout: 272 seconds]
zpe has quit [Remote host closed the connection]
wagle has quit [Remote host closed the connection]
zpe has joined #ocaml
wagle has joined #ocaml
octachron has joined #ocaml
silver has quit [Quit: rakede]
_andre has quit [Quit: leaving]
ldopa has joined #ocaml
rand has joined #ocaml
stomp_ has quit [Ping timeout: 276 seconds]
rand is now known as Guest51112
divyanshu has joined #ocaml
groovy2shoes has quit [Quit: Leaving]
MasseR has quit [Ping timeout: 264 seconds]
_andre has joined #ocaml
kakadu has quit [Remote host closed the connection]
stomp has joined #ocaml
badon_ has joined #ocaml
badon has quit [Disconnected by services]
badon_ is now known as badon
groovy2shoes has joined #ocaml
Algebr` has joined #ocaml
Algebr` has quit [Ping timeout: 245 seconds]
lokien_ has joined #ocaml
sh0t has joined #ocaml
govg has quit [Quit: leaving]
Stalkr_ has quit [Read error: Connection reset by peer]
govg has joined #ocaml
MasseR has joined #ocaml
eeks_ has joined #ocaml
hcarty has joined #ocaml
hcarty has quit [Quit: WeeChat 1.4]
struk|desk|away is now known as struk|desk2
mort___ has joined #ocaml
Algebr` has joined #ocaml
Algebr` has quit [Ping timeout: 250 seconds]
zpe has quit [Remote host closed the connection]
fraggle_ has quit [Remote host closed the connection]
MercurialAlchemi has quit [Ping timeout: 260 seconds]
mahasamoot has quit [Remote host closed the connection]
struk|desk2 is now known as struk|desk|away
jimt_ has joined #ocaml
mahasamoot has joined #ocaml
mahasamoot has left #ocaml [#ocaml]
jimt has quit [Ping timeout: 272 seconds]
sh0t has quit [Remote host closed the connection]
Sorella has joined #ocaml
struk|desk|away is now known as struk|desk2
mort___ has quit [Quit: Leaving.]
fraggle_ has joined #ocaml
mort___ has joined #ocaml
mort___ has quit [Quit: Leaving.]
ggole has joined #ocaml
Algebr` has joined #ocaml
Algebr` has quit [Ping timeout: 264 seconds]
ldopa has quit [Ping timeout: 276 seconds]
MercurialAlchemi has joined #ocaml
Quintasan has joined #ocaml
antkong_ has joined #ocaml
<Quintasan>
http://pastebin.com/1AbqJV69 ; ocaml interpreter says val f : 'a -> 'b -> ('b -> 'a -> 'a -> 'a) -> 'a -> 'a = <fun> . Where have I made a mistake?
jeffmo has joined #ocaml
<Drup>
Quintasan: z is used on 3 arguments.
antkong_ has quit [Ping timeout: 250 seconds]
<Quintasan>
Drup: okay, so z: ('b -> 'a -> 'a -> 'a), why it's not f : 'a -> 'b -> ('b -> 'a -> 'a -> 'a) -> 'a ?
<Drup>
because z is supposed to take 3 arguments :)
BitPuffin has quit [Ping timeout: 256 seconds]
<Quintasan>
Wait what.
<Drup>
f x y z = z x (z x y y)
<Drup>
the internal application of z is on 3 arguments
<Quintasan>
oh
<Drup>
so the typechecker infers that z should have 3 arguments
<Quintasan>
it's still going to wait on one argument?
<Drup>
yes
<Quintasan>
Many thanks.
<Quintasan>
I always seem to forget that a function can be a result as well.
struk|desk2 is now known as struk|desk|away
lokien has joined #ocaml
JacobEdelman has quit [Quit: Connection closed for inactivity]
slash^ has joined #ocaml
psy has joined #ocaml
psy has quit [Max SendQ exceeded]
groovy2shoes has quit [Quit: Leaving]
octachron has quit [Quit: Leaving]
psy has joined #ocaml
<beginner_>
can i tell menhir which path it should use to look for standard.mly?
groovy2shoes has joined #ocaml
<Drup>
--stdlib <directory> Specify where the standard library lies
<Drup>
(rtfm, all that :p)
lokien has quit [Quit: Leaving]
nullremains has quit [Ping timeout: 240 seconds]
virtualeyes has joined #ocaml
Algebr` has joined #ocaml
manizzle has quit [Read error: No route to host]
manizzle has joined #ocaml
lokien_ has quit [Quit: Connection closed for inactivity]
<lokien_>
what is this text library utop is using so it's that pretty?
BitPuffin has joined #ocaml
<rks`>
lambda-term (which itself uses zed)
hcarty has joined #ocaml
icicled has joined #ocaml
<lokien_>
thanks
skeuomorf has joined #ocaml
Guest38 has joined #ocaml
_andre has quit [Quit: Lost terminal]
Algebr` has quit [Ping timeout: 260 seconds]
pierpa has joined #ocaml
BitPuffin has quit [Ping timeout: 265 seconds]
shinnya has joined #ocaml
f[x] has joined #ocaml
jeffmo has quit [Quit: jeffmo]
vladb has joined #ocaml
<vladb>
Hi, I'm new to OCaml, and I have a question for the Oasis users. How do you deal with git merge conflicts in the oasis generated files: _tags, myocamlbuild.ml ?
<Drup>
when there is a conflict, you accept a random side and you regen oasis files
<vladb>
Thanks
skeuomorf has quit [Ping timeout: 260 seconds]
divyanshu has quit [Quit: Computer has gone to sleep.]
groovy2shoes has quit [Quit: Leaving]
groovy2shoes has joined #ocaml
divyanshu has joined #ocaml
Guest38 has quit [Read error: Connection reset by peer]
antkong_ has joined #ocaml
<sspi>
I've got a PPX dependency which has type information, however this only supports 1 file - currently I'm looking for a way to add s
<sspi>
support for multiple files
<sspi>
has this been done before? or are there any good hints that I can use?
<sspi>
Drup: it's an extension for modules to export the top level information
<Drup>
link ?
<sspi>
not published yet :)
<Drup>
right
kushal has quit [Quit: Leaving]
<sspi>
I'm crafting it privately for now
<sspi>
would like to release it once it's in a working state
<Drup>
because "an extension for modules to export the top level information" tells me aproximatly nothing, and even less what's the problem with multiple files is ...
lokien has joined #ocaml
<sspi>
right, so ppx runs over 1 file and I can get all the type information for this one file - however if my type is in another file, the call to get type information will fail (Unbound module etc.)
<Drup>
what's the goal ?
<sspi>
interop
<Drup>
No, what's the goal of getting the type information that way ?
<sspi>
not sure if I follow... it's the ppx step so by default there is no type information
<Drup>
Ok, my point is maybe not clear: You should not try to get the type informations that way unless you have a really god reasons :3
<Drup>
good*
<Drup>
So I'm asking what the reasons are
f[x] has quit [Ping timeout: 240 seconds]
mort___ has joined #ocaml
kushal has joined #ocaml
<sspi>
I've got really good reasons :P - I want to generate code in another language that uses this type information - but I'd like to use the PPX extensions to help with this
<sspi>
so I want the OCaml developer to say: I want this module to be bridged with a "simple" ppx wrapper
<sspi>
but what are the reasons not to get the type information?
sspi has quit []
sspi has joined #ocaml
<Drup>
sspi: ok, so you'll have to get the compiler options through the cookie mecanism
<Drup>
see Ast_helper for how it's done
<sspi>
cookie mechanism?
<Drup>
yeah, see ast_helper
<Drup>
then you have to look at that, load all the cmi that are passed on the cli before you call the typechecker
kdas_ has joined #ocaml
<Drup>
basically, you have to do the piece of work done by the frontend
<Drup>
that's why it's not really a great idea :D
<sspi>
doesn't matter - it's a fun challenge :)
<Drup>
fair enough
kushal has quit [Ping timeout: 240 seconds]
<Drup>
camlspotter has some stuff that do things like that, if you want
<Drup>
to look at it
mort___ has quit [Quit: Leaving.]
<sspi>
yeah I've read his stuff several times :) will do it some more I guess
<sspi>
the cookies are interesting - unfortunately not a lot of documentation :-/
mort___ has joined #ocaml
mort___ has quit [Client Quit]
kdas_ has quit [Read error: Connection reset by peer]
jeffmo has quit [Read error: Connection reset by peer]
jeffmo has joined #ocaml
<sspi>
Drup: thanks for the tips - I'll be exploring this direction :)
Guest14 has joined #ocaml
govg has quit [Ping timeout: 265 seconds]
kushal has joined #ocaml
lobo has quit [Quit: leaving]
f[x] has joined #ocaml
Denommus has joined #ocaml
mort___ has joined #ocaml
mort___ has quit [Client Quit]
ggole has quit []
Guest51112 has quit [Quit: leaving]
<yawnt>
day 3. and i'm still following the book
<yawnt>
i'm surprising myself
<yawnt>
\o/
<yawnt>
lokien: you still following the book?
<lokien>
yawnt: kinda. I'm trying to get my clojure to work
<lokien>
I'm at the beginning of "variables and functions"
<yawnt>
oh i can clojure, wassup?
<yawnt>
i'm at the module part
<lokien>
you mean, chapter 4?
<yawnt>
probably
<yawnt>
yes
Jane-PC has joined #ocaml
Jane-PC has quit [Changing host]
Jane-PC has joined #ocaml
<yawnt>
chapter 4
<lokien>
it's my second day though, forgive me my incompetence
<yawnt>
why incompetence, we are all learning, aren't we :)
jeffmo has quit [Quit: jeffmo]
jeffmo has joined #ocaml
<lokien>
I'm wandering in the darkness, actually
<lokien>
yawnt: which languages do you know?
ely-se has joined #ocaml
<yawnt>
lokien: i find that a hard question to answer
<yawnt>
i know pretty well Scala and JS
kansi has quit [Ping timeout: 265 seconds]
<yawnt>
i can write Ruby, Clojure, Go and Python
<lokien>
damn
<lokien>
if you wrote haskell, you would just say where the differences are
<lokien>
(so far they are very familiar, imo)
madroach has quit [Quit: leaving]
<yawnt>
i can read haskell
<yawnt>
but i've never written anything meaningful in it
<yawnt>
so far yes, they are pretty similar
<Drup>
"I can read haskell" :D
<lokien>
noone has /s
govg has joined #ocaml
<mspo>
only pandoc
lobo has joined #ocaml
<yawnt>
Drup: well, while studying Scala, there's a lot of people who take inspiration from Haskell
<yawnt>
so I thought it wise to be able to compare the two :P
<ely-se>
Some Scala programmers write Scala code as if it were Haskell code.
<lokien>
scala was too spooky for me, I went only through like 2 chapters and got annoyed
<lokien>
and some write it as a "better java" code
<ely-se>
It's incidentally also the most high-quality Scala code out there.
<yawnt>
ely-se: heh, yes, but it's also not nearly as nice as haskell
<Drup>
ely-se: not the most obscure ? :p
<yawnt>
Drup: plus, most of the applicatives/monads/functors are for haskell
<ely-se>
I've been enjoying Go and Perl 6 a lot lately.
<yawnt>
so it was hard to figure things out without knowing the syntax :D
<yawnt>
tutorials, i mean
<lokien>
some janestreet guy called ocaml obscure in a talk I was watching, it hurts right in my heart
<Drup>
yawnt: right
<Drup>
that's very simple reading, though
Denommus has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
<yawnt>
yeah, it is
Haudegen has quit [Ping timeout: 264 seconds]
<lokien>
yawnt: can you do clojurescript?
<Drup>
I find reading real haskell code much harder than writing it
<lokien>
Drup: let in a let in a let in a guard in a list comprehension
<yawnt>
lokien: yeah, i'm written some
<lokien>
yawnt: do you know svg by any chance?
<Drup>
lokien: that is ... not the main issue at all
lokien_ has quit [Quit: Connection closed for inactivity]
<yawnt>
lokien: yep
<lokien>
yawnt: oh man. can I show you some?
<Drup>
the main issue, similar to scalar, is that type classes are too implicits, it's hard to untangle when there is a lot of abstraction + typeclasses
<Drup>
scala*
<yawnt>
lokien: shoot
<ely-se>
ClojureScript gives you the great readability of Clojure with the nice semantics of JavaScript.
<Drup>
:D
<lokien>
and all that scary web stuff :^(
sh0t has joined #ocaml
<Drup>
Brad Cox and Tom Love create Objective-C, announcing "this language has all the memory safety of C combined with all the blazing speed of Smalltalk."
<lokien>
"When asked for a formal semantics of the formal semantics Milner's head explodes."
<lokien>
oh, well
<ely-se>
Milner is a Dutch brand of cheese.
lokien_ has joined #ocaml
<mspo>
ely-se: I think perl 6 has a lot of ocaml in it
<ely-se>
How so?
<mspo>
just the feel?
<mspo>
probably just took a lot from FP
<ely-se>
It features some facilities often found in functional programming language, but I don't feel like I'm writing OCaml code when programming in Perl 6.
<ely-se>
But of course, there's more than one way to do it, so YMMV.
<mspo>
yeah I didn't mean that
<mspo>
less awk more ocaml in p6, I guess ;)
<ely-se>
Sure.
teknozulu has joined #ocaml
<ely-se>
It still has BEGIN and END though :P
antkong has joined #ocaml
<mspo>
and many more phasers
darkf has quit [Quit: Leaving]
<mspo>
they are pretty damned handy
<ely-se>
You know you're designing Perl when your language documentation already features a page on traps to avoid before you even get to the first stable version.
antkong has quit [Ping timeout: 276 seconds]
Haudegen has joined #ocaml
rand has joined #ocaml
rand is now known as Guest2507
<mspo>
it's also the only language that's both 15 years and one month old
aantron has joined #ocaml
<ely-se>
No, it isn't.
<ely-se>
Every language that is 15 years old is also one month old.
slash^ has quit [Read error: Connection reset by peer]
<Drup>
You are both severely underestimating php.
<mspo>
inclusively you mean?
<ely-se>
In fact, everything that is N seconds is also M seconds old for any 0 <= M < N.
<mspo>
yeah I got the joke ;)
<lokien>
by the way. is anyone using sml today?
<Drup>
some univ in the US apparently
<aantron>
CMU uses it for research
pyon has joined #ocaml
<aantron>
and teaching
<Algebr>
Drup: I saw production haskell at Wagon, a haskell shop in San Francisco. It was very readable.
<lokien>
because people said ocaml was "more popular" than sml, and ocaml is quite unpopular
<Drup>
lokien: that should tell you something about sml :D
<lokien>
Drup: entire sml community is probably doing pair programming now
<ely-se>
I tired to use SML. I couldn't get the compiler to work.
<lokien>
but we have our shiny ocaml. let's make ml great again!
* lokien
puts his wig on
<ely-se>
make MLica great again
<mspo>
I think everyone is waiting for ocaml-MP
<aantron>
ml was great?
Ankhers has joined #ocaml
<lokien>
mspo: what is it?
<Algebr>
aantron: feature request. Make something can parse github markdown or emacs org mode files.
<lokien>
aantron: for few minutes, when I was reading about type inference
<mspo>
lokien: I mean ocaml that will run on many cpus
<aantron>
Algebr: you want a markdown parser as well? i was thinking about it, but what about omd?
<lokien>
mspo: real parallelism or distributed programming?
<ely-se>
yes
<lokien>
okay
<Algebr>
ahhh, didn't see that
<aantron>
but let me know if it has gaps.. or if you find better libraries. i would like to close them
<aantron>
havent really studied omd yet. still busy with work caused by lambda soup :p
<lokien>
will ocaml have green threads?
<aantron>
like lwt or async?
<lokien>
both
<Drup>
ocaml already has green threads
<adrien>
which is why COP21 was held in France
<adrien>
(ok, I'll shut up)
<ely-se>
No fun without green threads.
<lokien>
why don't we have parallelism then?
<Algebr>
aantron: ah, I will let you know of course. I'll be stressing the library for non trivial use, so we'll see.
<lokien>
hello adrien
<adrien>
morning :)
<ely-se>
still laughing every day at people who enjoy using promises/callbacks for EVERYTHING
<exm>
Hey! I'm starting to learn how to use oasis, and so I set up a unit test based on [this](1). But I'm getting a warning, "Warning: the tag "tests" is not used in any flag declaration". My code is at https://github.com/millere/osiris. According to the docs, tests is a predefined flag - any hints? [1]:https://ocaml.org/learn/tutorials/setting_up_with_oasis.html
<mspo>
lokien: start with parallelism
<Drup>
exm: you can ignore it
<mspo>
lokien: distributed programming doesn't seem related
<exm>
Drup: Yeah, it just seems a shame to start a new project and already have a warning :P
<lokien>
mspo: yeah, I'd be fine with 'only' parallelism
<mspo>
lokien: OTPcaml is very amibitious, though ;)
<lokien>
mspo: I wonder how ocaml programs run on four cores in language benchmark game
<lokien>
some hacky shenanigans?
<mspo>
fork?
<aantron>
multiprocessing probably
<lokien>
oh, okay.
<lokien>
mspo: I'll look at it
<mspo>
lokien: otpcaml? I just made that up
<mspo>
lokien: fork? definitely check it out :)
<lokien>
ah, that's why google showed only two unrelated articles.
<mspo>
as in erlang/otp
<lokien>
didn't know ocaml was *that* low level
<mspo>
the only distributed environment I know about
<lokien>
welp, thanks, didn't know you can do things like that
lokien has quit [Quit: Leaving]
mort___ has joined #ocaml
chindy has joined #ocaml
<chindy>
hi, i am trying to create a tailrecursive facutly function, can anyone explain where my thought/typing went wrong ? https://ideone.com/VrQn36
ryanartecona has joined #ocaml
yawnt has joined #ocaml
<aantron>
you want the accumulator to be a non-function value
<flux>
chindy, all if-expressions haev an else branch. if you don't provide it, it's "else ()"
<aantron>
you need something like "let rec helper accumulator ...more args..."
<chindy>
flux, ah...
<aantron>
ok very well, its a misleading name :)
<flux>
chindy, so do you see where the problem is?
<chindy>
yea
<chindy>
remove the second if
<chindy>
flux, thanks a lot. ... aantron what did you mean i am not so sure what you meant...
kakadu has joined #ocaml
<aantron>
chindy: the term "accumulator" usually refers to the parameter that is replaced with the value being computed by a helper function, not the helper function itself. of course, that value can be another function, but in this case it is not
<chindy>
ahh okay :(
<chindy>
well naming fail i guess next time.
<aantron>
in this case product is what is usually called the accumulator
<flux>
well, I don't think in this case 'accumulator' is really any worse than a common other choice, 'aux' ;-)
<aantron>
well they are two bad names, but each has a customary place :)
<flux>
"loop" "doit" "loopyloop"
<flux>
what would be a good name for it?
Guest14 has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<aantron>
how about "let rec accumulator loop i = ..." :p
<aantron>
im not proposing a good name, just saying that it should be the other way around if you use that name
<flux>
let accumulate accumulator index = ..
<flux>
but long variable names is just not the ocaml way ;)
<aantron>
x
<aantron>
i mean for good names it could be "let rec multiply product i = ..."
skeuomorf has joined #ocaml
<aantron>
then there is the age-old fac'
sh0t has quit [Quit: Leaving]
<flux>
' is the best ident-character
<flux>
when you need another same name, but you don't want to shadow. '.
<aantron>
especially when you reach x''''
<flux>
lesser languages need to go with _
<flux>
aantron, well, if x is the 4th derivative of x, then it's perfectly warranted for
<aantron>
it really helps if these variables differ in type though. otherwise good luck
<flux>
s/x/x''''/
<aantron>
true
freehck has quit [Remote host closed the connection]
ryanartecona has quit [Quit: ryanartecona]
chindy has quit [Remote host closed the connection]
hcarty has quit [Ping timeout: 250 seconds]
Guest2507 has quit [Quit: leaving]
orbitz has quit [Read error: Connection reset by peer]
sillyotter has joined #ocaml
larhat1 has joined #ocaml
<lokien_>
will I be beaten to death if I use x xs in my ocaml code?
<adrien>
no
<lokien_>
instead of hd tl (not sure if it was tl)
<lokien_>
ew, that's great. it's ten times more readable
mort___ has quit [Quit: Leaving.]
MercurialAlchemi has quit [Ping timeout: 272 seconds]
sillyotter has quit [Quit: leaving]
aantron has quit [Remote host closed the connection]
skeuomorf has quit [Ping timeout: 265 seconds]
lobo has quit [Quit: leaving]
eeks_ has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<Drup>
you should really not mix newline and boxes like that, you shouldn't be surprised to get non sensical indentation ...
<kakadu>
What should I use if I want to have line break even when the string fits in box width?
<Drup>
vertical boxes
zaquest has quit [Ping timeout: 245 seconds]
orbitz has joined #ocaml
Jane-PC has quit [Quit: Leaving]
<kakadu>
got it
Simn has quit [Quit: Leaving]
ely-se has quit [Quit: Leaving...]
zaquest has joined #ocaml
mac10688 has joined #ocaml
yawnt has quit [Ping timeout: 250 seconds]
<companion_cube>
aantron: you probably want to look at Printf.sprintf
<aantron>
companion_cube: why?
<companion_cube>
for your example above, generating system commands
<companion_cube>
^ gets old pretty quick
<aantron>
that was a paste from the link that was posted
<aantron>
i had the same thought that it would be clearer with sprintf
tane has quit [Quit: Verlassend]
Anarchos has joined #ocaml
<Anarchos>
Who uses bisect with ounit ?
<aantron>
i do
<Anarchos>
do they cooperate well with modules and functors ?
<aantron>
yes, but can you be more specific?
<Anarchos>
i wrote code highly modular with modules and functors. I am not sure if i will be able to get a 100%covergage by unit tests
<Anarchos>
they seem to be the best tools for that but i am looking for feedback of users.
<aantron>
well 100% coverage is always hard to reach. are you worried about something specific to modules, like functions that are not exposed in the signature?
<aantron>
they are very good tools.
<aantron>
in particular i was using bisect and ended up working on it. in a few days we will release a version that has much more thorough instrumentation and HTML that is easier on the eye
<Anarchos>
aantron yes this kind of problem with testing modules with functions not exposed
<Anarchos>
I wrote a formal demonstration verifier, so a 100
<aantron>
right. thats always a problem with any framework, except those that allow you to write tests inline in the module (pa_ounit?). you will have to either expose them, or write good test that reach them
damason has joined #ocaml
<Anarchos>
% coverage by unit tests would be cool
<aantron>
you may also be able to restructure your code so that the signature ascription doesnt apply when viewed by your unit tests.. but that is usually a pain
<Anarchos>
aantron you have been very helpful to confirm that bisect and ounit is the couple of tools to use for my testing :)
<Anarchos>
which kind of "make" tool do you use ? ocamlbuild, ocamlmakefile, plain makefile ?
<aantron>
i use a makefile and ocamlbuild together
<aantron>
there may be some testing framework out there similar to what pa_ounit did, that you can use to conditionally generate testing code right inside your modules, but i think either way for coverage bisect is the way to go
<Drup>
(side note: 100% test coverage doesn't mean your program is always correct)
<edwin>
there are some syntax extensions for inline tests (qtest and ppx_inline_test), do you recommend any of them?
<aantron>
right, coverage is visitation only. it doesnt test paths (history)
<aantron>
i have some limited experience with pa_ounit but maybe somebody else has better information
<Drup>
(some even argue that it means very little :p)
<aantron>
the coverage number may mean little, but i have some huge automata to test and the process of writing tests with a coverage tool makes me test very thoroughly
silver has quit [Quit: rakede]
<aantron>
far from perfect of course, but far more than i would test if i had to think of cases without aid
<aantron>
Anarchos: i think for build tools many people say oasis to drive everything, but i have no experience with it, so i cant say
<aantron>
perhaps someone else will comment
<Anarchos>
Drup sure i know
<aantron>
Anarchos: you may also want to look at alternative testing frameworks like alcotest, kaputt
<aantron>
s/alternative/other/
<Anarchos>
i have the hard prerequisite to compile all the frameworks from source ...
<Anarchos>
Cause i am on an alternative OS .
<aantron>
doesnt almost everyone always compile from source (opam)?
<companion_cube>
I use qtest and bisect_ppx
<companion_cube>
for inline testign and coverage
<Anarchos>
companion_cube what is the difference between ounit and qtest ?
<aantron>
qtest gives you inline testing so you can test unexposed functions
<aantron>
seems based on ounit
<aantron>
looks interesting :)
<companion_cube>
the main advantage is that tests are really close to the code
<aantron>
companion_cube: how does this interact with bisect_ppx? do you have to write an exclusion pattern?
<companion_cube>
so it's easier not to forget to update/write tests
<companion_cube>
I have to admit I don't use both at the same time :(
<aantron>
ill make myself a note to look into this
<companion_cube>
I use it in containers, it's very nice
icicled has quit [Quit: WeeChat 1.3]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]