adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml 4.07.0 release notes: https://caml.inria.fr/pub/distrib/ocaml-4.07/notes/Changes | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml | Due to ongoing spam, you must register your nickname to talk on the channel
JimmyRcom has quit [Ping timeout: 244 seconds]
JimmyRcom has joined #ocaml
Jesin has joined #ocaml
JimmyRcom has quit [Ping timeout: 244 seconds]
Jesin has quit [Quit: Leaving]
Algebr has quit [Ping timeout: 244 seconds]
zv has quit [Ping timeout: 244 seconds]
ziyourenxiang has joined #ocaml
silver has quit [Read error: Connection reset by peer]
cthuluh has quit [Ping timeout: 244 seconds]
cthuluh has joined #ocaml
neatonk has quit [Ping timeout: 244 seconds]
Jeanne-Kamikaze has joined #ocaml
Jeanne-Kamikaze has quit [Client Quit]
neatonk has joined #ocaml
cthuluh has quit [Ping timeout: 250 seconds]
mfp has quit [Ping timeout: 252 seconds]
kvda has joined #ocaml
cthuluh has joined #ocaml
tormen has joined #ocaml
tormen_ has quit [Ping timeout: 244 seconds]
rdivyanshu has joined #ocaml
rdivyanshu has quit [Read error: Connection reset by peer]
ziyourenxiang has quit [Ping timeout: 272 seconds]
neatonk has quit [Ping timeout: 272 seconds]
carlosdagos has joined #ocaml
JimmyRcom has joined #ocaml
JimmyRcom has quit [Max SendQ exceeded]
JimmyRcom has joined #ocaml
rdivyanshu has joined #ocaml
rdivyanshu has quit [Ping timeout: 252 seconds]
steenuil has quit [Remote host closed the connection]
rdivyanshu has joined #ocaml
jbrown has quit [Ping timeout: 250 seconds]
webshinra has quit [Remote host closed the connection]
webshinra has joined #ocaml
glass has joined #ocaml
theglass has quit [Ping timeout: 244 seconds]
jbrown has joined #ocaml
theglass has joined #ocaml
theglass has joined #ocaml
theglass has quit [Changing host]
glass has quit [Ping timeout: 250 seconds]
JimmyRcom has quit [Ping timeout: 272 seconds]
JimmyRcom has joined #ocaml
nopf has joined #ocaml
orbifx2 has joined #ocaml
orbifx2 has quit [Ping timeout: 252 seconds]
rdivyanshu has quit [Remote host closed the connection]
kvda has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
JimmyRcom has quit [Ping timeout: 252 seconds]
kvda has joined #ocaml
kalio has quit [Ping timeout: 264 seconds]
kalio has joined #ocaml
rdivyanshu has joined #ocaml
TC01 has quit [Ping timeout: 244 seconds]
TC01 has joined #ocaml
ollehar has joined #ocaml
ggole has joined #ocaml
Cypi has quit [Remote host closed the connection]
Cypi has joined #ocaml
TC01 has quit [Ping timeout: 252 seconds]
TC01 has joined #ocaml
rand__ has joined #ocaml
TC01 has quit [Ping timeout: 244 seconds]
TC01 has joined #ocaml
jaar has joined #ocaml
TC01 has quit [Excess Flood]
TC01 has joined #ocaml
maarhart has joined #ocaml
maarhart has quit [Client Quit]
kvda has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
kvda has joined #ocaml
rdivyanshu has quit [Ping timeout: 252 seconds]
rdivyanshu has joined #ocaml
mfp has joined #ocaml
dmiles has quit [Ping timeout: 268 seconds]
rntz has joined #ocaml
<rntz> I have a question about using GADTs in OCaml. I can't seem to get this code to type-check: http://sprunge.us/PTmZ14
<rntz> I'm using OCaml 4.05.00. Maybe upgrading would help.
nicoo has quit [Remote host closed the connection]
nicoo has joined #ocaml
<def`> rntz: the right syntax is 'let subtype : type a b. a tp * b tp -> (a,b) subtype option = function ...'
<def`> ('a 'b. ...) is for introducing universally quantified variables, which behave differently during inference.
carlosdagos has quit [Quit: Connection closed for inactivity]
dmiles has joined #ocaml
lostman has joined #ocaml
nicoo has quit [Ping timeout: 256 seconds]
nicoo has joined #ocaml
ziyourenxiang has joined #ocaml
gideonsmeding[m] has joined #ocaml
freyr69 has joined #ocaml
wilfredh has quit [Quit: Connection closed for inactivity]
Haudegen has quit [Remote host closed the connection]
<Leonidas> rixed: I really hope it won't degrade into this utter mess that threads are
<rntz> def`: what is "type a b." syntax for, then?
<rntz> er, to be clearer: if ('a 'b. ...) is syntax for "universally quantified variables", what is the name for the thing (type a b. ...) is syntax for?
<octachron> rntz, it is the combined short-hand for universally quantified and locally abstract types
<octachron> GADTs can only refine abstract types, thus you need to make the type that are observed in your match locally abstract. And going further in your implementation, you might need to make your function recursive, and in this case, the universal quantification is required too.
<rntz> is there any semantic difference between having a function (f: 'a. {something in terms of 'a}) and (f : type a. {something in terms of a})? or is this just necessary to clue in the typechecker?
<rntz> I've worked in a few other languaged with GADTs - Agda & Haskell - and never run across this distinction, which is why I'm slightly confused.
<octachron> There is some difference between the two in presence of subtyping
rdivyanshu has quit [Remote host closed the connection]
<rntz> ah, interesting. that would make sense, since neither Haskell nor Agda have subtyping.
<rntz> octachron: do you have an example of this difference? or somewhere I can read about it?
tautologico has quit [Quit: Connection closed for inactivity]
jaar_ has joined #ocaml
jaar_ has quit [Read error: Connection reset by peer]
neets has joined #ocaml
jaar has quit [Read error: Connection reset by peer]
rdivyanshu has joined #ocaml
<def`> rntz: GHC used to have a related problem, https://ghc.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7
<def`> (In particular, read the "Why make this change? ¶" and the referenced papers)
kvda has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
Haudegen has joined #ocaml
bronsen has quit [Ping timeout: 250 seconds]
bronsen has joined #ocaml
silver has joined #ocaml
JimmyRcom has joined #ocaml
frefity has joined #ocaml
neatonk has joined #ocaml
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 276 seconds]
JimmyRcom has quit [Ping timeout: 276 seconds]
groovy2shoes has joined #ocaml
spew has joined #ocaml
gareppa has joined #ocaml
frefity has quit [Quit: Ex-Chat]
nicoo has quit [Ping timeout: 256 seconds]
alphor has quit [*.net *.split]
dl3br[m] has quit [*.net *.split]
isaachodes[m] has quit [*.net *.split]
hdurer[m] has quit [*.net *.split]
_andre has quit [*.net *.split]
jack5638 has quit [*.net *.split]
bglm[m] has quit [*.net *.split]
FreeBirdLjj has joined #ocaml
_y has quit [Quit: .]
ollehar has quit [Remote host closed the connection]
alphor has joined #ocaml
jack5638 has joined #ocaml
ibnfirnas has quit [Quit: Good bye]
bglm[m] has joined #ocaml
JimmyRcom has joined #ocaml
dl3br[m] has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
hdurer[m] has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 250 seconds]
FreeBirdLjj has joined #ocaml
freyr69 has quit [Remote host closed the connection]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 244 seconds]
neets has quit [Quit: Leaving]
rand__ has quit [Ping timeout: 272 seconds]
al-damiri has joined #ocaml
demonimin has quit [Ping timeout: 252 seconds]
demonimin has joined #ocaml
bartholin has joined #ocaml
djellemah has quit [Ping timeout: 244 seconds]
djellemah has joined #ocaml
FreeBirdLjj has joined #ocaml
jnavila has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 245 seconds]
isaachodes[m] has joined #ocaml
_andre has joined #ocaml
ggole has quit [Quit: ggole]
<dexterfoo> rntz: i hope this isn't off-topic, but i would be interested in hearing your opinion on the advantages of ocaml over haskell
jack5638 has quit [Ping timeout: 252 seconds]
jack5638 has joined #ocaml
<ZirconiumX> dexterfoo: I'm not rntz, but I have a few things which might be worth talking about
<dexterfoo> ZirconiumX: i'm interested
<ZirconiumX> I'd say the semantics are one thing
fraxamo has joined #ocaml
<ZirconiumX> It's easier to predict what the eager semantics of OCaml will do, compared to the lazy semantics of Haskell
zv has joined #ocaml
pmetzger has joined #ocaml
<pmetzger> Ah, I see the discord bridge is broken. Repeating: generally, I find OCaml is less taxing to think about while still providing the functional experience most of the time. I get to decide when I want to violate pure functional style, though, and for how long, as well as the fact that eager semantics are indeed much easier to reason about.
<pmetzger> I think it's a mistake to ask "why is Haskell better than OCaml/why is OCaml better than Haskell". They're different, but still part of the same overall family. One can decide which of them one personally enjoys more.
<pmetzger> For me, I tried Haskell first and found I just couldn't quite feel comfortable in it, but OCaml fit like a glove very quickly.
<pmetzger> Other people may find they prefer Haskell though. There's no right answer.
<pmetzger> I think it's a big mistake to spend too much of your time asking "is X the perfect language/editor/window manager/operating system/etc". Different people will prefer different things, and even different things at different times. I wouldn't want to use either OCaml or Haskell for hard real time software, for example.
<pmetzger> And I find my taste in things like OS depends a great deal on what the context is.
<pmetzger> All in all, for things like hacking on language tools or compilers or what have you, OCaml suits me _very_ well, but the only way to know if it's good for you is to try.
<ZirconiumX> I really like OCaml, but I can only come up with a single case where it beats Rust for the same program
<ZirconiumX> I like currying, but I've seen it screw with a lot of people
<companion_cube> "beats" in performance, you mean?
<companion_cube> (cause in productivity, OCaml's GC helps a lot I think)
<ZirconiumX> Not only in performance
jnavila has quit [Ping timeout: 250 seconds]
<ZirconiumX> Well, I find myself fighting boxing quite a bit
<ZirconiumX> For example, I tried to write an interpreter for an emulator
demonimin has quit [Quit: bye]
<ZirconiumX> And had to use stdint to fight for that 64th bit
<pmetzger> You can just use int64
<companion_cube> there's Int64
<pmetzger> companion_cube: I see we had the same thought instantly. :)
<companion_cube> but yeah, if you write a low level interpreter rust seems pretty convenient
<companion_cube> if you write a compiler, otoh…
<ZirconiumX> Yes, it's good if you write a compiler
<pmetzger> Right now I think OCaml is the language to use if you can afford a GC and don't need every ounce of performance, and Rust is what I prefer for the case where you need really tight memory management and need that last milligram of performance.
<pmetzger> but that's my taste.
<ZirconiumX> But JIT requires you to trampoline through either C or asm
jnavila has joined #ocaml
<pmetzger> You can write an LLVM JIT in OCaml without any trampolining through anything.
<pmetzger> I think that's probably the right way to do it these days.
<ZirconiumX> LLVM is not very suitable for my use case
<pmetzger> Then don't use it. :)
<ZirconiumX> Good thing I'm not then
<companion_cube> for an interpreter I'd definitely go for rust, anyway
<pmetzger> It's my tool at the moment. I won't say I love it, but it does what I need more conveniently than alternatives.
<pmetzger> (LLVM that is.)
<companion_cube> a bytecode interpreter*
<companion_cube> for a debugging interpreter/evaluator, I'd still use OCaml since ASTs are awesome
<ZirconiumX> It's specifically a dynamic recompiling JIT
sspi__ has quit []
sspi__ has joined #ocaml
<pmetzger> LLVM is very good for that but I'll take your word for it that your case is different.
<ZirconiumX> I can elucidate if you want
<pmetzger> I won't object.
demonimin has joined #ocaml
<ZirconiumX> I'm writing an emulator; specifically a Dreamcast emulator
<pmetzger> You're emulating the CPU as well as the entire hardware stack I trust.
<ZirconiumX> It's entirely possible to turn the code into LLVM IR and then turn it into machine code through MCJIT
<ZirconiumX> Yes, I am
<ZirconiumX> One CPU is an SH4A (SuperH)
nicoo has joined #ocaml
<ZirconiumX> The other is an ARM7DI
<ZirconiumX> And I have a pretty crazy idea for getting it to work
<ZirconiumX> Which is to write most of the emulation stack in the IR
<ZirconiumX> (of the JIT)
<pmetzger> I remember the SuperH. Not an architecture that got a lot of long play. There was a NetBSD port to it though.
<ZirconiumX> Because this is an emulator that's got to run whatever I throw at it at 60FPS, it means my compilation time budget is very limited.
<ZirconiumX> Yeah, the SuperH architecture is quirky, but it works well enough for my purposes
<ZirconiumX> (The ARM chip is going to be hell)
JimmyRcom has quit [Ping timeout: 272 seconds]
<pmetzger> do you need cycle accurate emulation?
<ZirconiumX> And by "quirky", I mean "mostly fine except for the divide instruction"
<ZirconiumX> Cycle accuracy is not really feasible for hardware this new
<ZirconiumX> But I want to be reasonably high accuracy
<ZirconiumX> (I don't know if any of you have worked with ARM, but most of the instructions can be executed conditionally, which means branches all over the place)
<companion_cube> I know nothing about low level
themsay has quit [Ping timeout: 272 seconds]
<pmetzger> ARM conditional instruction execution is cool precisely because it allows conditional execution without branches, so you don't stall the pipeline.
<pmetzger> companion_cube: nothing? surely not nothing.
themsay has joined #ocaml
<bartholin> x86 has the CMOVcc instructions which mimics the MOV instructions of the ARM architecture
<companion_cube> -W -pedantic
<ZirconiumX> pmetzger: actually it introduces instruction dependencies that produce a lot of pipeline stalls
<pmetzger> companion_cube: I mean surely you've done some low level stuff. Most hackers have. Though I admit these days it is much less necessary. I used to do machine language coding quite regularly and the last big such thing I did was decades ago.
<pmetzger> ZirconiumX: I thought the whole point was not to branch so you don't have to worry about branch prediction etc., and that if you do register renaming it all ends up cool.
<companion_cube> honestly, not much. I have a few memories of a compilation course with a bit of MIPS, but apart from that, I'm not a fan of low level
<pmetzger> ZirconiumX: is the issue that ARM implementations are superscalar but don't do Tomasulo's Algorithm?
<companion_cube> I still can't read any realistic assembly language
<ZirconiumX> companion_cube: have a look at risc-v; it's very MIPSy
<pmetzger> companion_cube: I suppose that's a luxury you have these days. When I started it was hard to avoid. I even had to write a floating point library for the 8051 once.
Haudegen has quit [Read error: Connection reset by peer]
<pmetzger> RISC-V was designed by some of the MIPS people so that shouldn't surprise. :)
<ZirconiumX> pmetzger: the issue is that most ARM chips run on a phone and you don't have much silicon space for register renaming
<pmetzger> One of my required undergrad classes was an assembly language class. It was taught on the PDP-10 architecture, which was a 36 bit machine. :|
<pmetzger> ZirconiumX: I guess that makes sense.
<pmetzger> ZirconiumX: but whether you stall from a branch or a conditional execution, you can't avoid doing decisions in code, and at least this doesn't mess with the branch predictor.
<pmetzger> (The PDP-10 was very weird by current standards. _Very_ weird.)
<ZirconiumX> That and if when you resolve the condition it doesn't match, then you execute a nop
<ZirconiumX> Which isn't very efficient
<ZirconiumX> So less pipeline stalls, but more pipeline bubbles
<ZirconiumX> And compilers couldn't use it very effectively
Kitambi has joined #ocaml
<pmetzger> NOPs aren't bad things. MIPS tried to get rid of de facto pipeline NOPs with the branch delay slot and they ended up regretting that one.
rdivyanshu has quit [Remote host closed the connection]
pmetzger has quit []
rdivyanshu has joined #ocaml
rdivyanshu has quit [Ping timeout: 272 seconds]
tautologico has joined #ocaml
themsay has quit [Ping timeout: 252 seconds]
erkin has joined #ocaml
sspi__ has left #ocaml [#ocaml]
sspi has joined #ocaml
TheLemonMan has joined #ocaml
JimmyRcom has joined #ocaml
kvda has joined #ocaml
JimmyRcom has quit [Ping timeout: 268 seconds]
<crowley95> i'm implementing a MIPS processor for class rn
<crowley95> though without the branch delay slot
pepesza has quit [Quit: ZNC 1.6.3+deb1ubuntu0.1 - http://znc.in]
freusque has joined #ocaml
freusque has quit [Quit: WeeChat 2.0]
TheLemonMan has quit [Quit: "It's now safe to turn off your computer."]
kvda has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
fraxamo has quit [Quit: Leaving]
GreyFaceNoSpace has joined #ocaml
kvda has joined #ocaml
kvda has quit [Client Quit]
kakadu_ has joined #ocaml
orbifx2 has joined #ocaml
<companion_cube> ZirconiumX: I'm not particularly interested in hardware tbh
<companion_cube> for me rust is already super low level :°
<ZirconiumX> I've always found hardware quite interesting, but I understand that not everybody does
<companion_cube> all I want is for it to be fast :p
kakadu__ has joined #ocaml
ski has quit [Ping timeout: 252 seconds]
olopierpa has joined #ocaml
kakadu_ has quit [Ping timeout: 272 seconds]
orbifx2 has quit [Read error: Connection reset by peer]
rdivyanshu has joined #ocaml
orbifx2 has joined #ocaml
rdivyanshu has quit [Ping timeout: 246 seconds]
<rntz> dexterfoo: meh, I don't have strong feelings either way.
<rntz> ML-style module systems are more expressive, but Haskell's typeclasses are much more convenient and handle 90% of what you'd use the module system for.
<rntz> Haskell's purity gets in the way when you just want to do some effects (eg. exceptions, gensym, printing) but Haskell's syntax & library support for monads goes a long way. and if the effect you want isn't one OCaml natively supports (eg. nondeterminism), Haskell is easier.
<rntz> I'm an academic and tend not to work on large codebases, so there are probably plenty of pros/cons I'm missing.
<rntz> I'm mostly fiddling with OCaml now because (1) it has a nice compile-to-JS story (bucklescript) and (2) the module system fits better with Oleg's tagless-final style, which I'm trying to learn.
rdivyanshu has joined #ocaml
rdivyanshu has quit [Ping timeout: 250 seconds]
pepesza has joined #ocaml
gareppa has quit [Quit: Leaving]
bartholin has quit [Remote host closed the connection]
jnavila has quit [Remote host closed the connection]
spew has quit [Quit: going home]
kvda has joined #ocaml
<emily> rntz: (datafun is really cool!)
orbifx2 has quit [Ping timeout: 244 seconds]
nicoo has quit [Remote host closed the connection]
nicoo has joined #ocaml
orbifx2 has joined #ocaml
steenuil has joined #ocaml
nicoo has quit [Ping timeout: 256 seconds]
Jesin has joined #ocaml
Jesin has quit [Remote host closed the connection]
nicoo has joined #ocaml
Jesin has joined #ocaml
katyusha has quit [Quit: WeeChat 2.2]
orbifx2 has quit [Ping timeout: 244 seconds]
kakadu__ has quit [Remote host closed the connection]
<rntz> emily: thanks! :)
erkin has quit [Remote host closed the connection]
<dexterfoo> ZirconiumX, rntz: cool thank you
Jesin has quit [Quit: Leaving]
rdivyanshu has joined #ocaml
rdivyanshu has quit [Ping timeout: 252 seconds]