uncomfy has quit [Remote host closed the connection]
mal`` has quit [Quit: Leaving]
mal`` has joined #ocaml
<discocaml>
<bluddy5> objects really are the best abstraction here, as has come up time and again. So sad we never got proper nominal OOP.
<discocaml>
<bluddy5> why *did* JS want objects removed from Eio?
<companion_cube>
I have no idea! But I'd love to know.
waleee has quit [Ping timeout: 245 seconds]
chrisz has quit [Ping timeout: 245 seconds]
chrisz has joined #ocaml
TrillionEuroNote has quit [Ping timeout: 250 seconds]
TrillionEuroNote has joined #ocaml
kitzman has quit [Quit: C-x C-c]
kitzman has joined #ocaml
<discocaml>
<cemerick> companion_cube: objects are _absolutely_ the right tool for the IO job
<discocaml>
<cemerick> I'd hate to see anyone taking any lessons from eio's decisions. It seems to be in a truly unenviable position in a dozen different ways.
Serpent7776 has joined #ocaml
neuroevolutus has joined #ocaml
neuroevolutus has quit [Client Quit]
bartholin has joined #ocaml
bartholin has quit [Quit: Leaving]
mima has joined #ocaml
dnh has joined #ocaml
rgrinberg has joined #ocaml
rgrinberg has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<discocaml>
<vompura> Is it possible to make custom constructors for types? Say I have this type:
<discocaml>
<vompura> ```type position = Pos of int * int```
<discocaml>
<vompura> And I want the ints to always be positive and throw an exception if we try to construct with negative ordinates
<discocaml>
<vompura> ```Pos(-1, -1)```
<discocaml>
<deepspacejohn> That’s not possible on the type level. You can make the type private though and use a function to construct it which can throw the exception.
rgrinberg has joined #ocaml
<companion_cube>
I'd still like to know what was up with the change, for eio
<companion_cube>
Not that iostream would ever be used by jst
rgrinberg has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
dnh has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
rgrinberg has joined #ocaml
spip has quit [Ping timeout: 260 seconds]
mima has quit [Ping timeout: 255 seconds]
rgrinberg has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
rgrinberg has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
rgrinberg has joined #ocaml
ec has quit [Remote host closed the connection]
ec has joined #ocaml
<discocaml>
<leostera> ```ocaml
<discocaml>
<leostera> module Pos : sig
<discocaml>
<leostera> type t
<discocaml>
<leostera> val make : int -> int -> (t, error) result
<discocaml>
<leostera> end = struct
<discocaml>
<leostera> type t = Pos of int * int
<discocaml>
<leostera> let make x y =
<discocaml>
<leostera> if x > 0 && y > 0
<discocaml>
<leostera> then Ok(Pos(x,y))
<discocaml>
<leostera> else Error("something went wrong")
<discocaml>
<leostera> end
<discocaml>
<leostera> ```
<discocaml>
<._null._> In this case, it's easier to restrict to `type t = private Pos of int * int`, so that you can still use type `t` (in this case transparently). Also, `error` is nor a standard type (and you used a string)
yoyofreeman has quit [Remote host closed the connection]
<discocaml>
<vompura> Thanks guys
<discocaml>
<leostera> im aware
<discocaml>
<leostera> but i also figured @vompura would figure the rest out
<discocaml>
<leostera> 🙃
<discocaml>
<._null._> Also, try to not post multiline messages (especially code) as it gets sent one line at a time to IRC
ced2 has joined #ocaml
gralp has quit [Ping timeout: 246 seconds]
<companion_cube>
👍
ec has quit [Quit: ec]
daftaupe has joined #ocaml
gralp has joined #ocaml
gralp has quit [Client Quit]
oriba has joined #ocaml
xd1le has joined #ocaml
dnh has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
<companion_cube>
with this way we could have: 1. a `class virtual seekable` (with seek/pos), and a class `as_unix_fd` in a separate library (which implement In.t and Seekable)
<discocaml>
<cemerick> you have my interest now 🙂
<discocaml>
<regularspatula> i may have missed an earlier message, but was there pushback on using objects for that or something? it seems natural to use them right?
<companion_cube>
more like self censorship
<companion_cube>
some people hate objects (see initial Eio announcement — their rationale for objects was pretty good though!)
<companion_cube>
but yeah, here it fits realllllly well
<discocaml>
<regularspatula> gotcha
<discocaml>
<regularspatula> I skimmed that PR for poly variants to eio ...and didn't see any rationale for that change. Did I just miss that rationale?
<companion_cube>
JST asked for it
<discocaml>
<regularspatula> right, I meant why jst wanted it like that
<companion_cube>
I think they don't use objects at all internally
<discocaml>
<regularspatula> like, maybe it fits better with their compiler tweaks or something? (idk)
<companion_cube>
yeah possibly, but I'm totally in the dark
<companion_cube>
the other thing is that there's no objects in the stdlib… but well, it's not like we're going to change that
<discocaml>
<cemerick> minuscule runtime perf is the silliest possible rationale vis a vis IO
<discocaml>
<regularspatula> re the "some people hate objects"...do you think its because of the calling cost, or just like OO isn't cool now?
<discocaml>
<cemerick> there are some tooling weaknesses around them (which probably could be nipped and tucked), and many have aesthetic objections re: notation and such
<companion_cube>
I think objects are kind of hard to use sometimes, yeah
<discocaml>
<regularspatula> ah I didn't know about the tooling weakneses
<companion_cube>
but Eio had a good workaround for that: you're not supposed to call methods ever
<discocaml>
<regularspatula> i haven't really used the O in ocaml
<companion_cube>
there are wrapping functions
<discocaml>
<regularspatula> right right
<discocaml>
<regularspatula> i was wondering about the wrapping functions
<companion_cube>
they make error messages a lot better
<discocaml>
<cemerick> @regularspatula row-level polymorphism makes things like code completion an open-world problem, so tooling can't "eagerly" identify e.g. a concrete type when providing parameter hints, etc
<companion_cube>
I think tooling could still be better, it could complete known methods
<discocaml>
<regularspatula> makes sense
<companion_cube>
but I guess it's a whole section of the typechecker that merlin never really considered.
dnh has joined #ocaml
<discocaml>
<cemerick> companion_cube: I _think_ all tooling objections could be resolved if symbol analysis and lookup were sufficiently global within the scope of a given project/workspace
<companion_cube>
no I think here it could already be a lot better
<companion_cube>
but no one has done it
<discocaml>
<cemerick> maybe, I guess I'm thinking of the ultimate ideal
<discocaml>
<cemerick> similar to how javascript JITs identify unique object shapes over time and generates synthetic static types for each (up to some limit, etc)
<companion_cube>
tbh I annotate most types now, so nothing would have to be global anyway
<discocaml>
<cemerick> Right, you'd only need that for the worst/most polymorphic use cases
<companion_cube>
pff even at work in this thing, I have open recursion via records-of-functions that take the record as first argument (like Ast traversals in compiler-libs)
<companion_cube>
this would also be easier with objects
<discocaml>
<regularspatula> isn't open recursion like the classic use case for objects/classes? (im not a CS degree person)
<discocaml>
<cemerick> yes
<companion_cube>
it's a very good case indeed
<companion_cube>
see `visitors`
<discocaml>
<cemerick> it's also the only way you get row polymorphism in OCaml, which is _extremely_ useful
<discocaml>
<regularspatula> gotcha
<discocaml>
<cemerick> something you mostly only get in dynlangs
<discocaml>
<cemerick> or, I think in Haskell with the right mix of GHC extensions? I don't recall at this point
<discocaml>
<regularspatula> i think elm has row polymorphism on records (iirc)
<discocaml>
<regularspatula> could be misremembering that tho
xmachina has quit [Quit: WeeChat 4.0.4]
<discocaml>
<cemerick> ah, you're probably right
<discocaml>
<cemerick> Oh, scala too ☠️ 😆
Tuplanolla has joined #ocaml
dhil has joined #ocaml
<companion_cube>
it's purescript that has it
xmachina has joined #ocaml
<discocaml>
<cemerick> right, right
<discocaml>
<cemerick> basically defunct, last I knew
rgrinberg has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<discocaml>
<froyo> purescript is alive and well
<discocaml>
<cemerick> really! that's great
rgrinberg has joined #ocaml
<companion_cube>
it's Elm that's more or less dead, innit?
<discocaml>
<froyo> not many updates are coming from their side, IDK what evan is up to these days, no comment on its status
<discocaml>
<cemerick> I see it's getting updates, but the amount of activity is still very low vs. when paf31 was active 🤷
<discocaml>
<froyo> I could be wrong but ghc only supports row polymorphism in its effect types, so does koka.
<discocaml>
<froyo>
<discocaml>
<froyo> first time i hear of scala supporting it too
<companion_cube>
people forked Elm already, haven't they?
<discocaml>
<froyo> cemerick: we used purs at $company and at the time were constantly getting improvements in tooling (spago etc..). I admit last time I used it was months ago so maybe things slowed down in that time window
<discocaml>
<froyo> if an elm fork happened, it wasn't high profile enough for me to hear of it
<companion_cube>
hmm ok, maybe I confused with sth else
<companion_cube>
wouldn't be the first time
<discocaml>
<anmonteiro> I believe the speculation is that Evan is working on backend support for Elm
bartholin has joined #ocaml
rgrinberg has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<discocaml>
<nsmmrs> Basically, Elm hasn't been updated because it still works. People complaining about missing features or trying to fork it are usually people who haven't left their React knowledge at the door.
<discocaml>
<nsmmrs> The reason to use Elm should be that you like its developer's opinions and want to have the compiler force you to develop "the Elm way". Elm is better off not conforming to outside expectations, and prospective users who don't like The Elm Way are better off using some other option.
<discocaml>
<nsmmrs> It's a lot like htmx in that way.
<companion_cube>
it's a whole programming language though
dnh_ has joined #ocaml
<discocaml>
<nsmmrs> It's not general-purpose though. The only thing you can write with Elm is Elm apps.
dnh has quit [Ping timeout: 246 seconds]
<discocaml>
<nsmmrs> It's like if JavaScript was just React.
<discocaml>
<nsmmrs> (except good)
dnh_ has quit [Ping timeout: 246 seconds]
<discocaml>
<.korven.> like groovy but for web apps and better
rgrinberg has joined #ocaml
dhil has quit [Ping timeout: 246 seconds]
mima has quit [Ping timeout: 260 seconds]
azimut has quit [Ping timeout: 246 seconds]
waleee has joined #ocaml
dnh has joined #ocaml
gareppa has joined #ocaml
xmachina has quit [Quit: WeeChat 4.0.4]
xmachina has joined #ocaml
szkl has joined #ocaml
dnh has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
gareppa has quit [Quit: WeeChat 3.8]
<discocaml>
<JM> Like groovy? That's not really a selling point, it's like the worst language you can run on a JVM, and Java is on that list! 🙃
bartholin has quit [Quit: Leaving]
ced2 is now known as cedb
kurfen has quit [Ping timeout: 240 seconds]
kurfen has joined #ocaml
<discocaml>
<jumpnbrownweasel> There is also Roc, a new descendant of Elm, designed for backend.
<discocaml>
<jumpnbrownweasel> It's very early, I'm going to wait a while and look at it again.
Serpent7776 has quit [Ping timeout: 250 seconds]
<discocaml>
<_terence_> hey, how could I debug a "Sys_error("Bad file descriptor")" when using a formatter_out_of_channel ?
<discocaml>
<_terence_> ```ocaml
<discocaml>
<_terence_> fun f -> Format.(fprintf (formatter_of_out_channel f)) "%a" (fun f m -> Format.fprintf f "%a" (Format.pp_print_list ppPrintMethod) listofmethods)) m
<discocaml>
<_terence_> ```
<discocaml>
<._null._> `fprintf "%a"` is (pretty-much) identity, so you can already simplify that. `"Bad file descriptor"` is about a file, so probably check the file you're providing
<discocaml>
<octachron> Check also that the channel has not be closed by the time that you start start printing.
rgrinberg has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<discocaml>
<_terence_> Thanks, not very good with the prettyprinting stuffs.
<discocaml>
<_terence_> I'm using `Out_channel.with_open_text` so I should be good no ? filename is "module.mir_mono.debug"
<discocaml>
<_terence_> using `with_open_text` I shoudln't have to worry about it right?
rgrinberg has joined #ocaml
xmachina has quit [Quit: WeeChat 4.0.4]
<discocaml>
<octachron> no you can still accidentally capture the channel with `with_open_text`.
<discocaml>
<_terence_> here is the full function :
<discocaml>
<_terence_> ```ocaml
<discocaml>
<_terence_> let mir_mono_debug = fun m -> let+ m in Out_channel.with_open_text
<discocaml>
<_terence_> (fun f -> Format.(fprintf (formatter_of_out_channel f)) "%a" (fun f (m:Mono.out_body SailModule.t) -> Format.fprintf f "%a" IrMir.Pp_mir.(Format.pp_print_list ppPrintMethod) m.body.polymorphics)) m; m in
<discocaml>
<_terence_> ```
<discocaml>
<octachron> Yep, typically like this. The printing only starts when you provide the `m` argument thus after the execution of `with_only_text`.
masterbuilder has joined #ocaml
szkl has quit [Quit: Connection closed for inactivity]
<discocaml>
<_terence_> ahhhhh thank you very much !
wingsorc has joined #ocaml
<discocaml>
<_terence_> simplified and applied the function straight away and it works 🙂