adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml 4.09 release notes: https://caml.inria.fr/pub/distrib/ocaml-4.09/notes/Changes | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
Haudegen has quit [Ping timeout: 244 seconds]
oriba has quit [Quit: https://quassel-irc.org - Chat comfortably. Anywhere.]
ollehar has quit [Ping timeout: 256 seconds]
ollehar has joined #ocaml
vicfred has joined #ocaml
waleee-cl has quit [Quit: Connection closed for inactivity]
dborisog__ has joined #ocaml
malc_ has joined #ocaml
malc_ has quit [Remote host closed the connection]
vikfret has joined #ocaml
malc_ has joined #ocaml
swapnilraj[m] has joined #ocaml
mbuf has joined #ocaml
C-16 has joined #ocaml
snowpanda has quit [Quit: Leaving...]
malc_ has quit [Ping timeout: 256 seconds]
_whitelogger has joined #ocaml
ggole has joined #ocaml
Haudegen has joined #ocaml
malc_ has joined #ocaml
dborisog__ has quit [Ping timeout: 246 seconds]
vikfret has quit [Quit: Leaving]
tane has joined #ocaml
_whitelogger has joined #ocaml
<Serpent7776> there is unused variable warning for `let ... in`, but not for plain `let x = 1`. Is there a way to have it for the latter too?
osa1 has joined #ocaml
<theblatte> if you have a .mli file ocaml will warn you about unused values but won't warn you if you export `val x : ...`
<theblatte> if you build with dune then you might be interested in the global dead code analysis in https://github.com/reason-association/reanalyze#dce-reports
<Serpent7776> I have a single file ml script, so I don't want to create mli file. Dead code analysis looks awesome, but probably overkill for my silly script.
<theblatte> haha, yes :) if it's just an executable then I would still advise to create an empty .mli file, that way you'll get dead code warnings!
<theblatte> in the single-file case ocamlc detects almost all the dead code (but not dead exceptions and some other stuff)
<flux> Serpent7776: just create an empty .mli
<flux> oh, what theblatte said :)
nullcone has quit [Quit: Connection closed for inactivity]
<Serpent7776> what are cmi files? They sometimes seem to be generated and sometimes not.
<flux> aren't they generated always?
<flux> .cmi files are basically the binary representation of .mli
<flux> in lieu of .mli, .ml is used
<flux> so it tells the interface of the module
<flux> in your case there is no interface you need to expose, as the module does the work by itself
<Serpent7776> cmi is not regenerated when I `rm *.cm*`, I need to `ocamlc -c file.mli` then
<flux> well `rm` doesn't generate any files 🤔, but if I do `ocamlc -c file.ml` it creates both file.cmo and file.cmi, correct?
<Serpent7776> Yes, but after `rm`, ocamlc doesn't regenerate them and complain that they connot be found
<flux> ocamlc only touches to files directly related to its parameters, so you need a build system like dune of OCamlMakefile to do that
<Serpent7776> I also get an error "could not find cmi" when compiling from other directory
<flux> "or" not "of"
<flux> well yes, so you need the .cmi files to access other modules
<flux> and build systems handle that for you
<flux> and ocamlc is just a compiler, not a build system
<Serpent7776> Sure, but I'd expect not to need build system for single source script :)
<flux> so if you created an .mli file, it needs to be compiled with ocamlc
<flux> you can achieve that in one go with `ocamlc -c foo.mli foo.ml`
<flux> but if you don't have an .mli file, then `ocamlc` will create both .cmi and .cmo in one shot
<flux> btw, there's a tool called `ocamlscript` that might interest you
<flux> oh, it's probably now obsolete, it's unmaintained
osa1 has quit [Ping timeout: 256 seconds]
<Serpent7776> seems so, too bad
<Serpent7776> Anyway I'm still not getting the warning when I add empty mli file
<theblatte> ocamlc -w32
<theblatte> sorry, -w +32
artymort has quit [Ping timeout: 265 seconds]
artymort has joined #ocaml
<Serpent7776> theblatte: that works, thanks
leah2 has quit [Ping timeout: 260 seconds]
<flux> might just as well go and enable all warnings and disable ones that don't apply
<malc_> flux: neither list is stable
<flux> during the development it's fine.
<malc_> ok
<flux> obviously for the release build one should never use -warn-error
<malc_> flux: i disagree
<flux> malc_: you enjoy your packages becoming uncompialable when OCaml adds a new warning, even though you don't know what that warning is?
<flux> as a user, I absolutely hate it :)
<malc_> flux: i know that when they add new warning it means that something has changed and i OUGHT to inspect things
<malc_> happened before
<malc_> and i'd rather it'd be incompatible than wrong
<malc_> i also can understand your stance
<malc_> i just thing it's a wrong one
<malc_> s;g;k
<flux> actually I was really talking about `-warn-error=a`
<malc_> i just use -warn-error=@A
<flux> malc_: exactly, it's nice when you find new mistakes in your code
<flux> it sucks when you find it on others
<flux> what is @A?
<flux> ah, it's the all
<flux> I wonder if you enjoy when you `opam install` something with a new compiler and it doesn't compile, because apparently OCaml has a warning new warning. the new warning could for example be about partial pattern matching which it learned at some point.
<malc_> i do not use opam :)
<flux> do you use other people's code?
<malc_> yes
<malc_> i use locally prepared and bundled lablGL
<flux> but it's nice opportunity to get to do some development first if a new warning pops up?-)
<flux> you've done llpp? I've enojyed that, thanks!
<malc_> you are welcome :)
<flux> nevertheles, what do you expect users to do if they install llpp but it doesn't compile?
<flux> I mean arguably this is even more important to end-user apps than just library code
leah2 has joined #ocaml
<flux> (well, actually both are important)
<malc_> flux: i expect them to notify me... but given how llpp's build systems is structured it's rather unlikely to happen in practice
<malc_> -s
<flux> llpp downloads a certain version of OCaml compiler..?
<malc_> ye-
<malc_> s;-;s
<malc_> sorry can't type today... too damned hot
<flux> malc_: what is the upside of enabling warnings for user-facing compilations, though?
<flux> (warning-as-errors that is)
<malc_> flux: the upside is that when they do release new version of the compiler it might trigger some legit issue with a warning level i know nothing about (i.e. the + number) happened at least once in the past
<flux> malc_: well it sounds like you should revise your process to make a release build before relase 🤔
<flux> in the meanwhile the user is either an OCaml developer or is left with no program to run
<malc_> i refuse to change, change is for wussies, real coders with balls of steel never change once they do something (stupidity of the old-ways notwithstanding)
<flux> :)
ahf has quit [Ping timeout: 264 seconds]
ahf has joined #ocaml
waleee-cl has joined #ocaml
raver has quit [Remote host closed the connection]
osa1 has joined #ocaml
sarna has joined #ocaml
<sarna> hey, are containers now really more popular than async?
<sarna> lol brainfart - I meant core/core_kernel
<sarna> 2667 downloads for containers last month, 1030 for core_kernel
sarna has quit [Remote host closed the connection]
sarna has joined #ocaml
sarna has quit [Client Quit]
sarna has joined #ocaml
_whitelogger has joined #ocaml
leah2 has quit [Ping timeout: 260 seconds]
sarna has quit [Quit: Connection closed]
<Serpent7776> Let's say I have functions f and g, and f calls g. Then g needs to be defined before f. Is there any way to define f first and then g? Specifying signatures in mli file doesn't seem to help.
<theblatte> if several functions are in a mutual recursion cycle they need to be defined with "let rec g = ... and f = ..."
<theblatte> assuming that's what you mean by "g needs to be defined before f"
<octachron> if they are not mutually recursive we can make f take a "q" argument
<Serpent7776> functions are not mutually recursive
<Serpent7776> so I guess it's not possible without rewriting f?
<Serpent7776> because there's no forward declarations in OCaml
<simpson> You can use `let rec ... and ...` even when they're not mutually recursive.
<simpson> `let rec f x = g (x + 1) and g x = x * 2;;` works for me at toplevel.
<Serpent7776> hmm, a bit hacky, but would work, thanks
Hrundi_V_Bakshi has joined #ocaml
_whitelogger has joined #ocaml
leah2 has joined #ocaml
nullcone has joined #ocaml
catern has quit [Excess Flood]
catern has joined #ocaml
<flux> hacky? well till you see this! let g = ref (fun -> assert false) let f = .. !g 4 2 let g = g := (fun a b -> a + b); !g
<flux> s/well/& wait/
<malc_> flux: that's not valid ocaml still (afaics)
<flux> true, fun is missing a parameter and .. needs to be replaced with fun () ->
<flux> but otherwise it is valid
<flux> utop # let g = ref (fun _ -> assert false) let f () = !g 4 2 let g = g := (fun a b -> a + b); !g;;
<flux> val f : unit -> int = <fun>
<flux> val g : int -> int -> int = <fun>
<Serpent7776> whoa, nice :D
raver has joined #ocaml
<zozozo> it's surprising code but I don't see much problem with it
<zozozo> then again, maybe I'm too accustomed to crazy examples that break the compiler, XD
<flux> it makes use of the OCaml weak types. (not that ocaml's types are weak, but these particular types are weak types)
<flux> so it ties the type later
<zozozo> yes sure
<zozozo> it's just a more complicated example than the usual (and very useful) `let r = ref None let main () = let x = parse_some_things () in r := Some x; blabla ....`
malc_ has left #ocaml ["ERC (IRC client for Emacs 28.0.50)"]
<zozozo> note however that thee type that the weak polymorphic variable is bound to must be declare at the point of definition of the weak variable, so the following example will not work : `let r = ref None type t = A let () = r := Some A`
<zozozo> (and you'll get the very helpful "type would escape its scope" error message, :p)
mbuf has quit [Quit: Leaving]
osa1 has quit [Remote host closed the connection]
snowpanda has joined #ocaml
ggole has quit [Quit: Leaving]
averell has quit [*.net *.split]
stux|RC has quit [*.net *.split]
emias has quit [*.net *.split]
wagle has quit [*.net *.split]
dckc_ has quit [*.net *.split]
towel has quit [*.net *.split]
jmct has quit [*.net *.split]
ocabot has quit [*.net *.split]
companion_cube has quit [*.net *.split]
maker has quit [*.net *.split]
nore has quit [*.net *.split]
Armael has quit [*.net *.split]
dmbaturin has quit [*.net *.split]
rks` has quit [*.net *.split]
rntz2_ has quit [*.net *.split]
sagax has joined #ocaml
<ollehar> (typestate and references is hard!)
dmbaturin has joined #ocaml
rntz2 has joined #ocaml
rks` has joined #ocaml
stux|RC has joined #ocaml
emias has joined #ocaml
wagle has joined #ocaml
Armael has joined #ocaml
maker has joined #ocaml
ocabot has joined #ocaml
companion_cube has joined #ocaml
towel has joined #ocaml
nore has joined #ocaml
averell has joined #ocaml
jmct has joined #ocaml
dckc_ has joined #ocaml
dmbaturin has quit [*.net *.split]
rntz2 has quit [*.net *.split]
catern has quit [*.net *.split]
copy has quit [*.net *.split]
_tjr_ has quit [*.net *.split]
tianon has quit [*.net *.split]
dmbaturin has joined #ocaml
rntz2 has joined #ocaml
tianon has joined #ocaml
catern has joined #ocaml
copy has joined #ocaml
_tjr_ has joined #ocaml
snowpanda has quit [*.net *.split]
sz0 has quit [*.net *.split]
neheist2 has quit [*.net *.split]
jeroud has quit [*.net *.split]
terrorjack has quit [*.net *.split]
mrallen1 has quit [*.net *.split]
interruptinuse has quit [*.net *.split]
eterps has quit [*.net *.split]
cemerick has quit [*.net *.split]
farn_ has quit [*.net *.split]
Fardale has quit [*.net *.split]
bronsen has quit [*.net *.split]
strmpnk has quit [*.net *.split]
bacam has quit [*.net *.split]
clockish has quit [*.net *.split]
sim642 has quit [*.net *.split]
haesbaert has quit [*.net *.split]
RalfJ has quit [*.net *.split]
Manis[m] has quit [*.net *.split]
ec has quit [*.net *.split]
d_bot has quit [*.net *.split]
stylewarning has quit [*.net *.split]
eterps has joined #ocaml
jeroud has joined #ocaml
snowpanda has joined #ocaml
Fardale has joined #ocaml
terrorjack has joined #ocaml
mrallen1 has joined #ocaml
cemerick has joined #ocaml
interruptinuse has joined #ocaml
sz0 has joined #ocaml
bronsen has joined #ocaml
neheist2 has joined #ocaml
farn_ has joined #ocaml
bacam has joined #ocaml
sim642 has joined #ocaml
strmpnk has joined #ocaml
clockish has joined #ocaml
neheist2 has quit [Max SendQ exceeded]
farn_ has quit [Max SendQ exceeded]
terrorjack has quit [Max SendQ exceeded]
haesbaert has joined #ocaml
RalfJ has joined #ocaml
ec has joined #ocaml
Manis[m] has joined #ocaml
d_bot has joined #ocaml
stylewarning has joined #ocaml
oturtle has quit [*.net *.split]
swapnilraj[m] has quit [*.net *.split]
aecepoglu[m] has quit [*.net *.split]
bglm[m] has quit [*.net *.split]
rom1504 has quit [*.net *.split]
Duns_Scrotus has quit [*.net *.split]
jun has quit [*.net *.split]
ec has quit [Max SendQ exceeded]
d_bot has quit [Excess Flood]
Duns_Scrotus has joined #ocaml
swapnilraj[m] has joined #ocaml
aecepoglu[m] has joined #ocaml
bglm[m] has joined #ocaml
oturtle has joined #ocaml
rom1504 has joined #ocaml
jun has joined #ocaml
farn_ has joined #ocaml
troydm has quit [*.net *.split]
haskell_enthusia has quit [*.net *.split]
rak has quit [*.net *.split]
tizoc has quit [*.net *.split]
schlaftier has quit [*.net *.split]
runciter has quit [*.net *.split]
Ankhers has quit [*.net *.split]
lobo has quit [*.net *.split]
jgkamat has quit [*.net *.split]
jerith has quit [*.net *.split]
abc_ has quit [*.net *.split]
_habnabit has quit [*.net *.split]
kit_ty_kate has quit [*.net *.split]
runciter has joined #ocaml
troydm has joined #ocaml
haskell_enthusia has joined #ocaml
rak has joined #ocaml
schlaftier has joined #ocaml
tizoc has joined #ocaml
jerith has joined #ocaml
Ankhers has joined #ocaml
jgkamat has joined #ocaml
lobo has joined #ocaml
abc_ has joined #ocaml
_habnabit has joined #ocaml
kit_ty_kate has joined #ocaml
sz0 has quit [Ping timeout: 260 seconds]
rak has quit [Max SendQ exceeded]
d_bot has joined #ocaml
penguwin has quit [*.net *.split]
vesper has quit [*.net *.split]
c4rc4s has quit [*.net *.split]
ansiwen has quit [*.net *.split]
White_Flame has quit [*.net *.split]
Exagone313 has quit [*.net *.split]
Leonidas has quit [*.net *.split]
kandu has quit [*.net *.split]
SquidDev has quit [*.net *.split]
valtr has quit [*.net *.split]
lnxw37d4 has quit [Ping timeout: 246 seconds]
jimt[m] has quit [Ping timeout: 246 seconds]
peddie has quit [Ping timeout: 246 seconds]
stylewarning has quit [Ping timeout: 250 seconds]
penguwin has joined #ocaml
vesper has joined #ocaml
kandu has joined #ocaml
c4rc4s has joined #ocaml
White_Flame has joined #ocaml
Exagone313 has joined #ocaml
Leonidas has joined #ocaml
ansiwen has joined #ocaml
valtr has joined #ocaml
SquidDev has joined #ocaml
aecepoglu[m] has quit [Ping timeout: 260 seconds]
bglm[m] has quit [Ping timeout: 260 seconds]
rks` has quit [*.net *.split]
Hrundi_V_Bakshi has quit [*.net *.split]
sagax has quit [*.net *.split]
ArthurStrong has quit [*.net *.split]
ollehar has quit [*.net *.split]
theblatte has quit [*.net *.split]
so has quit [*.net *.split]
Niamkik has quit [*.net *.split]
Madars has quit [*.net *.split]
trn has quit [*.net *.split]
mal`` has quit [*.net *.split]
cthuluh has quit [*.net *.split]
Exagone313 has quit [Max SendQ exceeded]
c4rc4s has quit [Max SendQ exceeded]
vesper has quit [Max SendQ exceeded]
penguwin has quit [Max SendQ exceeded]
c4rc4s has joined #ocaml
flux has quit [Ping timeout: 246 seconds]
ec has joined #ocaml
dash has quit [Ping timeout: 244 seconds]
rak has joined #ocaml
penguwin has joined #ocaml
jbrown has quit [*.net *.split]
webshinra has quit [*.net *.split]
cqc has quit [*.net *.split]
pgiarrusso has quit [*.net *.split]
mjvoge02 has quit [*.net *.split]
cbarrett has quit [*.net *.split]
SrPx has quit [*.net *.split]
adi_________ has quit [*.net *.split]
ollehar has joined #ocaml
Niamkik has joined #ocaml
sagax has joined #ocaml
theblatte has joined #ocaml
so has joined #ocaml
trn has joined #ocaml
mal`` has joined #ocaml
ArthurStrong has joined #ocaml
Madars has joined #ocaml
Hrundi_V_Bakshi has joined #ocaml
rks` has joined #ocaml
cthuluh has joined #ocaml
Exagone314 has joined #ocaml
jbrown has joined #ocaml
cqc has joined #ocaml
webshinra has joined #ocaml
pgiarrusso has joined #ocaml
mjvoge02 has joined #ocaml
cbarrett has joined #ocaml
SrPx has joined #ocaml
adi_________ has joined #ocaml
SrPx has quit [Max SendQ exceeded]
ahf has quit [*.net *.split]
tane has quit [*.net *.split]
C-16 has quit [*.net *.split]
vicfred has quit [*.net *.split]
infinity0 has quit [*.net *.split]
Serpent7776 has quit [*.net *.split]
tmhoang has quit [*.net *.split]
rwmjones has quit [*.net *.split]
ziman has quit [*.net *.split]
cranix has quit [*.net *.split]
rak has quit [Excess Flood]
Manis[m] has quit [Ping timeout: 240 seconds]
foocraft[m] has quit [Ping timeout: 246 seconds]
stephe has quit [Ping timeout: 244 seconds]
rfv has quit [Ping timeout: 244 seconds]
tmhoang has joined #ocaml
vicfred has joined #ocaml
rwmjones has joined #ocaml
infinity0 has joined #ocaml
ziman has joined #ocaml
cranix has joined #ocaml
tane has joined #ocaml
C-16 has joined #ocaml
Serpent7776 has joined #ocaml
ahf has joined #ocaml
vesper11 has joined #ocaml
inkbottle has quit [*.net *.split]
Jesin has quit [*.net *.split]
delysin_ has quit [*.net *.split]
reynir has quit [*.net *.split]
Amaan has quit [*.net *.split]
kini has quit [*.net *.split]
cross has quit [*.net *.split]
landonf has quit [*.net *.split]
tobiasBora2 has quit [*.net *.split]
srax has quit [*.net *.split]
ksft has quit [*.net *.split]
greenbagels has quit [*.net *.split]
zq has quit [*.net *.split]
asm89 has quit [*.net *.split]
pippijn has quit [*.net *.split]
Khady has quit [*.net *.split]
sepp2k has quit [Ping timeout: 244 seconds]
camlriot42 has quit [Ping timeout: 244 seconds]
aspiwack[m] has quit [Ping timeout: 246 seconds]
damienkrine[m] has quit [Ping timeout: 246 seconds]
lubegasimon[m] has quit [Ping timeout: 244 seconds]
rak has joined #ocaml
heredoc has quit [*.net *.split]
cgenie[m] has quit [*.net *.split]
bytesighs has quit [*.net *.split]
higherorder has quit [*.net *.split]
wildsebastian has quit [*.net *.split]
rgrinberg has quit [*.net *.split]
chewbranca has quit [*.net *.split]
conjunctive has quit [*.net *.split]
mgsk has quit [*.net *.split]
l1x has quit [*.net *.split]
JSharp has quit [*.net *.split]
artart78 has quit [*.net *.split]
delysin_ has joined #ocaml
inkbottle has joined #ocaml
Amaan has joined #ocaml
ksft has joined #ocaml
Jesin has joined #ocaml
reynir has joined #ocaml
cross has joined #ocaml
Khady has joined #ocaml
pippijn has joined #ocaml
greenbagels has joined #ocaml
landonf has joined #ocaml
zq has joined #ocaml
tobiasBora2 has joined #ocaml
srax has joined #ocaml
asm89 has joined #ocaml
kini has joined #ocaml
greenbagels has quit [Max SendQ exceeded]
inkbottle has quit [Max SendQ exceeded]
heredoc has joined #ocaml
JSharp has joined #ocaml
rgrinberg has joined #ocaml
cgenie[m] has joined #ocaml
chewbranca has joined #ocaml
conjunctive has joined #ocaml
bytesighs has joined #ocaml
higherorder has joined #ocaml
wildsebastian has joined #ocaml
l1x has joined #ocaml
artart78 has joined #ocaml
mgsk has joined #ocaml
zebrag has joined #ocaml
vicfred has quit [Remote host closed the connection]
stux|RC has quit [*.net *.split]
artymort has quit [*.net *.split]
Ekho has quit [*.net *.split]
CcxWrk has quit [*.net *.split]
taharqa has quit [*.net *.split]
h11 has quit [*.net *.split]
eagleflo has quit [*.net *.split]
octachron has quit [*.net *.split]
def has quit [*.net *.split]
notnotdan has quit [*.net *.split]
rpcope has quit [*.net *.split]
hannes has quit [*.net *.split]
cross has quit [Max SendQ exceeded]
vicfred has joined #ocaml
bitonic has quit [Ping timeout: 272 seconds]
jnavila has quit [*.net *.split]
bartholin has quit [*.net *.split]
simpson has quit [*.net *.split]
Drup has quit [*.net *.split]
breitenj has quit [*.net *.split]
rdivyanshu__ has quit [*.net *.split]
caasih has quit [*.net *.split]
angerman has quit [*.net *.split]
robmyers has quit [*.net *.split]
j14159_ has quit [*.net *.split]
sspi__ has quit [*.net *.split]
lopex has quit [*.net *.split]
Boarders has quit [*.net *.split]
adrianbrink has quit [*.net *.split]
banjiewen has quit [*.net *.split]
ipavlo has quit [*.net *.split]
gahr has quit [*.net *.split]
zozozo has quit [*.net *.split]
theglass has quit [*.net *.split]
xvilka has quit [*.net *.split]
vodkaInferno has quit [*.net *.split]
delucks has quit [*.net *.split]
so has quit [Max SendQ exceeded]
artymort has joined #ocaml
Ekho has joined #ocaml
CcxWrk has joined #ocaml
stux|RC has joined #ocaml
h11 has joined #ocaml
taharqa has joined #ocaml
hannes has joined #ocaml
eagleflo has joined #ocaml
def has joined #ocaml
rpcope has joined #ocaml
octachron has joined #ocaml
notnotdan has joined #ocaml
CcxWrk has quit [Max SendQ exceeded]
stux|RC has quit [Max SendQ exceeded]
Ekho has quit [Max SendQ exceeded]
greenbagels has joined #ocaml
nullcone has quit [Ping timeout: 244 seconds]
cbarrett has quit [Ping timeout: 246 seconds]
labor[m] has quit [Remote host closed the connection]
prsafont[m] has quit [Remote host closed the connection]
swapnilraj[m] has quit [Remote host closed the connection]
cgenie[m] has quit [Remote host closed the connection]
Ekho- has joined #ocaml
stephe has joined #ocaml
CcxWrk_ has joined #ocaml
CcxWrk_ is now known as CcxWrk
rdivyanshu__ has joined #ocaml
caasih has joined #ocaml
simpson has joined #ocaml
jnavila has joined #ocaml
Drup has joined #ocaml
bartholin has joined #ocaml
breitenj has joined #ocaml
robmyers has joined #ocaml
j14159_ has joined #ocaml
angerman has joined #ocaml
sspi__ has joined #ocaml
Boarders has joined #ocaml
zozozo has joined #ocaml
lopex has joined #ocaml
delucks has joined #ocaml
xvilka has joined #ocaml
theglass has joined #ocaml
ipavlo has joined #ocaml
gahr has joined #ocaml
adrianbrink has joined #ocaml
banjiewen has joined #ocaml
vodkaInferno has joined #ocaml
robi has quit [*.net *.split]
p4bl0 has quit [*.net *.split]
engil has quit [*.net *.split]
johnel has quit [*.net *.split]
p4bl0 has joined #ocaml
robi has joined #ocaml
engil has joined #ocaml
johnel has joined #ocaml
bytesighs has quit [Ping timeout: 244 seconds]
conjunctive has quit [Ping timeout: 244 seconds]
JSharp has quit [Ping timeout: 244 seconds]
higherorder has quit [Ping timeout: 244 seconds]
wildsebastian has quit [Ping timeout: 244 seconds]
ebb has quit [*.net *.split]
thizanne has quit [*.net *.split]
iZsh has quit [*.net *.split]
stux|RC has joined #ocaml
chewbranca has quit [Ping timeout: 244 seconds]
iZsh has joined #ocaml
thizanne has joined #ocaml
ebb has joined #ocaml
rgrinberg has quit [Ping timeout: 244 seconds]
madroach has quit [*.net *.split]
vsiles has quit [*.net *.split]
runawayfive has quit [*.net *.split]
TC01 has quit [*.net *.split]
dx has quit [*.net *.split]
DanielRichman has quit [*.net *.split]
adrien has quit [*.net *.split]
rfv has joined #ocaml
vsiles has joined #ocaml
madroach has joined #ocaml
TC01 has joined #ocaml
DanielRichman has joined #ocaml
runawayfive has joined #ocaml
dx has joined #ocaml
adrien has joined #ocaml
cross has joined #ocaml
ksft has quit [Ping timeout: 260 seconds]
stylewarning has joined #ocaml
stylewarning has joined #ocaml
stylewarning has quit [Changing host]
bytesighs has joined #ocaml
Manis[m] has joined #ocaml
andreas303 has quit [Remote host closed the connection]
bitonic has joined #ocaml
ksft has joined #ocaml
so has joined #ocaml
nullcone has joined #ocaml
rgrinberg has joined #ocaml
angerman has quit [Ping timeout: 272 seconds]
wildsebastian has joined #ocaml
chewbranca has joined #ocaml
cbarrett has joined #ocaml
andreas303 has joined #ocaml
conjunctive has joined #ocaml
higherorder has joined #ocaml
SrPx has joined #ocaml
terrorjack has joined #ocaml
angerman has joined #ocaml
JSharp has joined #ocaml
rks` has quit [*.net *.split]
Hrundi_V_Bakshi has quit [*.net *.split]
sagax has quit [*.net *.split]
ollehar has quit [*.net *.split]
ArthurStrong has quit [*.net *.split]
theblatte has quit [*.net *.split]
Niamkik has quit [*.net *.split]
Madars has quit [*.net *.split]
mal`` has quit [*.net *.split]
trn has quit [*.net *.split]
cthuluh has quit [*.net *.split]
sagax has joined #ocaml
Madars has joined #ocaml
ArthurStrong has joined #ocaml
rks` has joined #ocaml
mal`` has joined #ocaml
Niamkik has joined #ocaml
trn has joined #ocaml
cthuluh has joined #ocaml
theblatte has joined #ocaml
ollehar has joined #ocaml
Hrundi_V_Bakshi has joined #ocaml
aecepoglu[m] has joined #ocaml
bglm[m] has joined #ocaml
aspiwack[m] has joined #ocaml
flux1 has joined #ocaml
camlriot42 has joined #ocaml
jimt[m] has joined #ocaml
peddie has joined #ocaml
lnxw37d4 has joined #ocaml
prsafont[m] has joined #ocaml
dash has joined #ocaml
labor[m] has joined #ocaml
lubegasimon[m] has joined #ocaml
cgenie[m] has joined #ocaml
foocraft[m] has joined #ocaml
sepp2k has joined #ocaml
swapnilraj[m] has joined #ocaml
damienkrine[m] has joined #ocaml
sz0 has joined #ocaml
jnavila has quit [Quit: Konversation terminated!]
tane has quit [Quit: Leaving]
Ekho- is now known as Ekho
hannes has quit [Remote host closed the connection]
<ollehar> how come flow-sensitive languages never made it mainstream?
<dash> Probably because nobody tried to make it happen
<companion_cube> what do you call flow sensitive in this case?
<companion_cube> aren't typescript and kotlin somewhat flow sensitive in their typing?
malc_ has joined #ocaml
<ollehar> hm, maybe they are now
<ollehar> "Since this introduction, other languages have made use of it, namely Ceylon,[5] Kotlin,[6][7] TypeScript[8] and Facebook Flow.[9] "
<ollehar> huh, didn't know flow still existed, since they made reasonml
<companion_cube> :p
Hrundi_V_Bakshi has quit [Ping timeout: 264 seconds]
Haudegen has quit [Ping timeout: 256 seconds]
webshinra has quit [Remote host closed the connection]
webshinra has joined #ocaml
artymort9 has joined #ocaml
artymort has quit [Ping timeout: 265 seconds]
artymort9 is now known as artymort