zolk3ri has quit [Remote host closed the connection]
sh0t has quit [Remote host closed the connection]
arthur_rainbow has joined #ocaml
Fare has joined #ocaml
granttrec has quit [Ping timeout: 256 seconds]
arthur_rainbow has quit [Read error: Connection reset by peer]
spew has joined #ocaml
pierpa has quit [Ping timeout: 260 seconds]
pierpa has joined #ocaml
granttrec has joined #ocaml
arthur_rainbow has joined #ocaml
spew has quit [Ping timeout: 260 seconds]
kvda has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
kvda has joined #ocaml
Fare has quit [Ping timeout: 276 seconds]
pierpal has joined #ocaml
<granttrec>
any idea where the let should go in this ocaml statment https://paste.ee/p/RHh1L ? Initially i thought use a single `let` and replace the `;` with `and` but that does not work
pierpal has quit [Ping timeout: 260 seconds]
silver_ has quit [Read error: Connection reset by peer]
<pierpa>
why don't you use a begin/end pair to make your intention explicit insted of relying on finicky precedence rules which confuse everybody?
<pierpa>
sorry, no, in this case is a different phenomenon at play :)
<pierpa>
use three let's one for each of the three first lines
sh0t has joined #ocaml
kvda has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
Fare has joined #ocaml
spew has joined #ocaml
<granttrec>
pierpa: I think its the point of the exercise I am trying to complete
<granttrec>
why is a let needed for the last line?
<pierpa>
not in the last line
sh0t has quit [Read error: Connection reset by peer]
gpietro has joined #ocaml
<pierpa>
you want: let v1 = e1 in let v2 = f(e1) in let v3 = g(e1) in h(v2,v3)
<pierpa>
Sigh. My ocaml is rusty. I mean: let v1 = e1 in let v2 = f e1 in let v3 = g e1 in h v2 v3
<granttrec>
hmm i'm still a bit lost, this is what I have:
<granttrec>
let big_ab = List.map up ab in
<granttrec>
let big_xy = List.map up xy in
<granttrec>
let up = Char.uppercase in
<granttrec>
big_ab @ big_xy
gpietro has quit [Ping timeout: 240 seconds]
sh0t has joined #ocaml
<pierpa>
should work. It doesn't?
<pierpa>
(assuming xy is defined somewhere else)
sh0t has quit [Remote host closed the connection]
sh0t has joined #ocaml
arthur_rainbow1 has joined #ocaml
pierpal has joined #ocaml
arthur_rainbow has quit [Ping timeout: 256 seconds]
<granttrec>
pierpa: nope doesn't work, I've been trying some things but no luck
<granttrec>
I may just have to get started on the book at this point
sh0t has quit [Ping timeout: 256 seconds]
<pierpa>
post the whole function?
Fare has quit [Ping timeout: 248 seconds]
<pierpa>
granttrec: and what does it means "doesn't work"? syntax error? does not compute what you intended? other?
<granttrec>
the error:
<granttrec>
Error: Unbound value xy
<granttrec>
File "", line 2, characters 27-29:
sh0t has joined #ocaml
<granttrec>
pierpa: I got it, needed to redo some preivous exercies
<pierpa>
of course. if the whole expression is what you have pasted, then xy and ab are not defined
<pierpa>
I assumed you pasted only a fragment of code
shinnya has quit [Ping timeout: 256 seconds]
<granttrec>
pierpa: thanks mate
<pierpa>
yw ;)
tormen_ has joined #ocaml
Fare has joined #ocaml
<Fare>
Is there a notion of covariance for functor arguments?
tormen has quit [Ping timeout: 264 seconds]
sh0t has quit [Remote host closed the connection]
sh0t has joined #ocaml
FreeBirdLjj has joined #ocaml
granttrec has quit [Quit: granttrec]
FreeBirdLjj has quit [Ping timeout: 240 seconds]
spew has quit [Ping timeout: 248 seconds]
mcspud has joined #ocaml
jao has quit [Ping timeout: 240 seconds]
mfp has quit [Ping timeout: 255 seconds]
arthur_rainbow1 has quit [Ping timeout: 260 seconds]
kvda has joined #ocaml
pierpa has quit [Quit: Page closed]
sh0t has quit [Remote host closed the connection]
shinnya has joined #ocaml
unyu has quit [Quit: Reboot.]
ygrek has joined #ocaml
unyu has joined #ocaml
<companion_cube>
contra-variance, rather
kvda has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
ziyourenxiang_ has quit [Quit: Leaving]
kvda has joined #ocaml
ygrek has quit [Ping timeout: 256 seconds]
mbuf has joined #ocaml
cbot has quit [Quit: Leaving]
Fare has quit [Ping timeout: 245 seconds]
ZirconiumX has quit [Quit: Love you all~]
kvda has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
kvda has joined #ocaml
ozzymcduff has joined #ocaml
unyu has quit [Quit: The end of the world is nigh. Bring as much popcorn as you can!]
kvda has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
FreeBirdLjj has joined #ocaml
pierpal has quit [Quit: Poof]
pierpal has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
ozzymcduff has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
webshinra has quit [Ping timeout: 256 seconds]
ozzymcduff has joined #ocaml
ozzymcduff has quit [Read error: Connection reset by peer]
Guest11101 has joined #ocaml
soupladler has joined #ocaml
shinnya has quit [Ping timeout: 260 seconds]
ozzymcduff has joined #ocaml
ozzymcduff has quit [Client Quit]
ozzymcduff has joined #ocaml
Guest11101 has quit [Read error: Connection reset by peer]
TheRuralJuror has joined #ocaml
TheRuralJuror is now known as Haudegen
ozzymcduff has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
hannes has quit [Remote host closed the connection]
webshinra has joined #ocaml
webshinra has quit [Ping timeout: 256 seconds]
ozzymcduff has joined #ocaml
argent_smith has joined #ocaml
<ELLIOTTCABLE>
This is gonna be such a dumb question
<ELLIOTTCABLE>
but — I'm kinda new to monads, functional programming, all this,
<ELLIOTTCABLE>
is there something that's sort of the inverse of `bind`?
<ELLIOTTCABLE>
i.e. a shorthand for running a series of functions until one of them *isn't* None
<ELLIOTTCABLE>
instead of running functions until one *is* None
Fare has joined #ocaml
webshinra has joined #ocaml
jaar has joined #ocaml
frefity has joined #ocaml
hannes has joined #ocaml
TarVanimelde has joined #ocaml
<reynir>
I get syntax error at the colon in »let f () = let (x, y, z) : int * int * int = (1, 2, 3) in x« using ocaml 3.11.2 D:
zolk3ri has joined #ocaml
<theblatte>
where did you even find OCaml 3.11.2? ;)
<reynir>
at work :(
<reynir>
It's what's shipped with the latest release of Solaris
<theblatte>
hah :)
ZirconiumY has joined #ocaml
ZirconiumY is now known as ZirconiumX
letoh has quit [Ping timeout: 240 seconds]
<discord3>
<Christophe> reynir: try moving the parentheses : let f () = let (x, y, z : int * int * int) = (1, 2, 3) in x
<reynir>
Yes, that works! :)
<reynir>
Hopefully I won't have to touch that code again :D
frefity has quit [Ping timeout: 248 seconds]
mfp has joined #ocaml
frefity has joined #ocaml
catern has quit [Quit: catern]
kakadu has joined #ocaml
letoh has joined #ocaml
TarVanimelde has quit [Quit: TarVanimelde]
kakadu has quit [Remote host closed the connection]
kakadu has joined #ocaml
monstasat has joined #ocaml
<monstasat>
Hi! I am using cohttp to establish a server on my backend app. My api assumes using both websockets and http. I want to find a way to define if a request is a websocket or a plain http. I assumed that I can do that by checking 'scheme' part of Uri (which can be returned by Cohttp.Request.uri), but it is always absent. Of course I can change names of my ws api paths, but it is quite redundant
<monstasat>
Here is an example of uri returned by cohttp: //127.0.0.1:8080/api/board/4/device/state
<monstasat>
as can be seen, scheme is absent
<monstasat>
despite this is a websocket request
shinnya has joined #ocaml
Fare has quit [Ping timeout: 240 seconds]
Rosslaew has joined #ocaml
neatonk has joined #ocaml
<discord3>
<Christophe> ELLIOTTCABLE, you could use the Either monad to achieve that but that would mean changing the way you write your functions. The Either monad returns Left x or Right y and shortcuts on Left. Usually it's used for error passing but you could use it to pass the actual result of your function once it's attained. You could do: let f x = if x mod 2 = 0 then Left "It's even" else Right x let g x = if x mod 2 = 1
<discord3>
then Left "It's odd" else Right x let h x = Left "What the hell dude ?" Right 1337 >>= f >>= g >>= h (* gives Left "odd" *)
<discord3>
<Christophe> That way you'd have Left result if one function succeeded and your original value if none succeeded
<discord3>
<Christophe> Wait I see that tit did not go formatted as intended, let me resend the code
<discord3>
<Christophe> let f x = if x mod 2 = 0 then Left "It's even" else Right x
<discord3>
<Christophe> let g x = if x mod 2 = 1 then Left "It's odd" else Right x
<discord3>
<Christophe> let h x = Left "What the hell dude ?"
<discord3>
<Christophe> Right 1337 >>= f >>= g >>= h (* gives Left "odd" *)
jao has joined #ocaml
Haudegen has quit [Remote host closed the connection]
mbuf has quit [Remote host closed the connection]
mbuf has joined #ocaml
spew has joined #ocaml
cow-orker has quit [Remote host closed the connection]
neatonk has quit [Ping timeout: 256 seconds]
neatonk has joined #ocaml
neatonk has quit [Ping timeout: 276 seconds]
silver has joined #ocaml
Haudegen has joined #ocaml
jaar has quit [Ping timeout: 256 seconds]
_andre has joined #ocaml
Rosslaew has quit [Remote host closed the connection]
Rosslaew has joined #ocaml
Fare has joined #ocaml
mbuf has quit [Quit: Leaving]
frefity has quit [Ping timeout: 260 seconds]
frefity has joined #ocaml
frefity has quit [Client Quit]
jbrown has joined #ocaml
jaar has joined #ocaml
Fare has quit [Ping timeout: 260 seconds]
ziyourenxiang has joined #ocaml
Rosslaew has quit [Ping timeout: 240 seconds]
Bronsa has joined #ocaml
Fare has joined #ocaml
aciniglio has joined #ocaml
spew has quit [Read error: Connection reset by peer]
mbuf has joined #ocaml
jbrown has quit [Quit: Leaving]
jbrown has joined #ocaml
spew has joined #ocaml
neatonk has joined #ocaml
<Fare>
how do I redirect output to a string in ocaml?
<discord3>
<loxs> Printf.sprintf
<reynir>
what sort of output
<Fare>
discord3, won't work if I'm generating strings in sub functions.
<octachron>
Fare, if you control the function producing the output you can use Format with a buffer formatter
<octachron>
otherwise, if you really need redirecting, you can use the Unix module to redirect your channel to a pipe
<discord3>
<Perry> Fare, "discord3" is a gateway to the discord channel, not a person.
pierpal has quit [Quit: Poof]
pierpal has joined #ocaml
pierpal has quit [Ping timeout: 248 seconds]
pierpal has joined #ocaml
monstasat has quit [Remote host closed the connection]
<ELLIOTTCABLE>
but … no IRC client is going to complete on the, idk, first word in a message
<ELLIOTTCABLE>
who's genius idea was that -_-
<ELLIOTTCABLE>
ugh sorry not relevant ignore me.
<ELLIOTTCABLE>
Christophe: thank you! I'll look at this
ozzymcduff has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
<ELLIOTTCABLE>
looks like Either pretty much just replaces Option?
pierpal has quit [Ping timeout: 260 seconds]
pierpal has joined #ocaml
webshinra has quit [Remote host closed the connection]
jbrown has quit [Quit: Leaving]
jbrown has joined #ocaml
mbuf has quit [Quit: Leaving]
jbrown has quit [Quit: Leaving]
soupladler has quit [Ping timeout: 256 seconds]
Fare has quit [Ping timeout: 256 seconds]
pierpal has quit [Quit: Poof]
pierpal has joined #ocaml
jbrown has joined #ocaml
<discord3>
<Christophe> It's a different monad, with slightly similar semantics :)
sh0t has joined #ocaml
<Armael>
w
<Armael>
argh.
<discord3>
<Christophe> It is implemented (minus the operator) in the standard library as "result" type, Ok and Error constructors (you can then use Containers' CCResult for the monad)
<discord3>
<Christophe> Or you can use Core_kernel's Either, that uses First and Second constructors, for less opinionated names :)
<discord3>
<Perry> Is there a standard set of monad operators or a preferred set of monad libraries in the OCaml ecosystem?
gtrak has joined #ocaml
tianon has quit [Ping timeout: 240 seconds]
tianon has joined #ocaml
<ZirconiumX>
There are a bunch of monad operators that I've found, Perry
<ZirconiumX>
WRT "monad libraries", I don't know enough about the language, other than Lwt/Async are monad based.
<companion_cube>
there is no standard `either` type, but `result` is definitely the standard type for errors
<ZirconiumX>
Far as I can tell, option's for one type and result is for two
<companion_cube>
result is for Ok/Error, is all
<discord3>
<Perry> The documentation of "Result" in the Pervasives manual consists of the type signature. 😃
<discord3>
<Perry> That said, this is one of the few times when I think that's enough.
shinnya has quit [Ping timeout: 256 seconds]
<discord3>
<Perry> Normally the joke with Haskell or OCaml is people saying "Why do you need documentation, you have the type signature!" but for Result I think that's actually true.
Fare has joined #ocaml
mbuf has joined #ocaml
ygrek has joined #ocaml
oni-on-ion has joined #ocaml
oni-on-ion has left #ocaml [#ocaml]
catern has joined #ocaml
catern has quit [Excess Flood]
catern has joined #ocaml
catern has quit [Excess Flood]
catern has joined #ocaml
catern has quit [Excess Flood]
catern has joined #ocaml
catern has quit [Excess Flood]
unyu has joined #ocaml
catern has joined #ocaml
catern has quit [Excess Flood]
webshinra has joined #ocaml
catern has joined #ocaml
catern has quit [Excess Flood]
<discord3>
<Christophe> Why is there no (to my knowledge) monadic operations in the standard library for options and results?
<discord3>
<Perry> It's worse than that. I think there are no standard functions over options or results, period.
<discord3>
<Christophe> it feels sad that the types are there but we need 3rd party libraries
<discord3>
<Bluddy> Results are fairly new, and until 4.07, the core team didn't want to add new modules at the top level due to the possibility of creating conflicts with user libraries.
<discord3>
<Bluddy> 4.07 moved the stdlib to the Stdlib 'namespace'
<discord3>
<Bluddy> So feel free to submit this stuff now.
<discord3>
<Perry> What's the status on 4.07 being released btw?
<discord3>
<Bluddy> I don't know. It seems to be taking forever.
<discord3>
<Bluddy> Every time there's a desire to release quickly, and it doesn't quite work out.
<discord3>
<Perry> BTW, I'm really looking forward to something like odoc generating the Pervasives documentation. As it stands right now, finding anything in it is slow and unwieldy.
Haudegen has quit [Remote host closed the connection]
pierpal has quit [Quit: Poof]
pierpal has joined #ocaml
<companion_cube>
Christophe: it's the opposite, the standard type was added so that 3rd party libs could agree
<Fare>
For debugging... do you define all your printers by hand, or is there a way to get ocaml to print your values in a painless way?
<Fare>
I admit that printf debugging without a generic printf is, well, painful.
<discord3>
<Perry> [@@deriving show] shows up in my code all the time. 😃
<Fare>
Perry: how do you get deriving show to work across module boundaries? Some of the things I'm showing are defined in module parameters, and deriving looks like it hates it.
<Fare>
and/or maybe I need to have all those parameters follow some special interface?
<companion_cube>
you need to `[@@deriving show]` in the .mli too
<Fare>
I find Haskell typeclasses much more pleasant than explicitly building modules upon modules
<companion_cube>
if it's in a functor's parameters you need to require these to have a `pp` function too
<discord3>
<Perry> Fare: Yah well, when you have time, maybe you can work on modular implicits. 😉
<companion_cube>
that's rough
<companion_cube>
few people are able to contribute to this meaningfully :-/
<companion_cube>
(typeclasses have their own issues, too)
<Fare>
companion_cube: what type signature should the pp even have?
<discord3>
<Perry> companion_cube: thus my wink.
<companion_cube>
oh, didn't see it through the bridge
<discord3>
<Perry> Fare: play with @deriving show, it's what you want.
<companion_cube>
we're on a bridge!!
<discord3>
<Perry> companion_cube: it removed the emoji!!!???
<Fare>
It showed me the emoji as unicode on hexchat.
<Fare>
Now I need to re-wrap all my primitive types including integers and strings, etc., in modules that define and export pp_ functions for which I have to guess the type.
<discord3>
<Perry> you don't have to wrap them in modules.
<discord3>
<Perry> I don't.
<discord3>
<Perry> You only need @deriving show annotations on the more complicated stuff that you choose to print out during debugging.
<companion_cube>
hmm maybe I don't have the right font then
<discord3>
<Perry> Fare, why are you slumming with the strongly typed people anyway? You're a Lisp fanatic.
drewr has quit [Ping timeout: 260 seconds]
<companion_cube>
know your enemy? :p
mbuf has quit [Quit: Leaving]
Haudegen has joined #ocaml
FreeBirdLjj has joined #ocaml
thizanne_ has joined #ocaml
thizanne_ has quit [Client Quit]
<Fare>
I'm renewing my Lisp fanaticism through a trip in static land.
<dmbaturin_>
Fare: The Lisp fanatics' progress from this type system to that which is to come? ;)
<companion_cube>
the easier it becomes to write a ppx, the weaker arguments from lisp are, I think ;-)
<Fare>
so, is there at least a with-output-to-string in ocaml ?
<companion_cube>
Format.asprintf
<ZirconiumX>
He probably means more like rebinding stdin/stdout
<companion_cube>
(or unix magic, I guess — dynamic binding is weird)
<ZirconiumX>
Ideally all code would use string output. rather than printing
<companion_cube>
err, nope :/
<companion_cube>
(ideally all code would use Format instead of strings, but well, that's another problem)
ozzymcduff has joined #ocaml
<Fare>
GAH! I forgot to call the continuation, so was returning a partial result!
FreeBirdLjj has quit [Remote host closed the connection]
<Fare>
Error: Unbound value meme
<Fare>
Hint: Did you mean mem?
Bronsa has quit [Ping timeout: 264 seconds]
FreeBirdLjj has joined #ocaml
Haudegen has quit [Remote host closed the connection]
jnavila has joined #ocaml
Fare has quit [Ping timeout: 240 seconds]
jnavila has quit [Ping timeout: 240 seconds]
jaar has quit [Ping timeout: 245 seconds]
pierpal has quit [Quit: Poof]
pierpal has joined #ocaml
Bronsa has joined #ocaml
pierpal has quit [Quit: Poof]
pierpal has joined #ocaml
Bronsa has quit [Ping timeout: 268 seconds]
al-damiri has joined #ocaml
ozzymcduff has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
FreeBirdLjj has quit [Remote host closed the connection]
jnavila has joined #ocaml
ozzymcduff has joined #ocaml
<discord3>
<mars0i> There is a with_output_to style function in Core.Unix fwiw. Maybe elswehere in Core, too.
Fare has joined #ocaml
kakadu has quit [Quit: Konversation terminated!]
jao has quit [Ping timeout: 260 seconds]
pierpal has quit [Quit: Poof]
pierpal has joined #ocaml
pierpal has quit [Quit: Poof]
pierpal has joined #ocaml
aciniglio has quit [Read error: Connection reset by peer]
jao has joined #ocaml
<ELLIOTTCABLE>
Ugh. I am just having the hardest time with this.
<ELLIOTTCABLE>
So I have no formal background in any of this — kinda figuring it out as I go — so forgive me if I badly screw up some terminology or sound like an idiot;
<ELLIOTTCABLE>
but.
<ELLIOTTCABLE>
I'm trying to parse Scheme (R5RS.) in OCaml. Well, actually, I'm trying to *compile* Scheme, but I'm currently blocked on trying to get a dang plan for parsing (which, while a learning experience of its own, is not really what I got into this project for … 🤣
<ELLIOTTCABLE>
I started out learning a bunch about Menhir, wanting to just let a mature project do the work for me
<ELLIOTTCABLE>
I got a good ways (well, at least, from my perspective, heh) into writing a Menhir grammar for the formal syntax in R5RS
<ELLIOTTCABLE>
before managing to finally notice that it's … not actually a context-free grammar (yes, that shoulda been obvious. I don't write much Lisp.)
<ELLIOTTCABLE>
I
<ELLIOTTCABLE>
've had a few other suggestions for alternatives, but I keep running into dealbreakers:
<ELLIOTTCABLE>
- Sexplib was another time-sink — wrote a significant chunk of a janky recursive-descent parser by hand, letting Sexplib do the "lexing", before realizing that Sexplib throws away quotes etc — `"this here"` is just an Atom with a space in it, not something I can thereafter detect and create a `string` from,
<ELLIOTTCABLE>
- mParse has no documentation, other than basically ‘this should be obvious, 'cuz you've all used Parsec, rite?’ I don't know Haskell
<ELLIOTTCABLE>
(not to mention the impossibility of Unicode support gahhhh)
<ELLIOTTCABLE>
tl;dr does anybody have any suggestions for parsing Scheme, other than writing a full lexer and parser, from scratch, by myself? I'd really love to draw on somebody else's expertise / efforts, so I can get on to building a damn compiler for the first time! 😞
<ZirconiumX>
I'd focus on an even smaller Lisp first
<ELLIOTTCABLE>
oh, forgot: bap-primus-lisp, which uses Sexplib; but turns out it has no primitive types, and so never ran into the strings problem.
<ZirconiumX>
But I'm a newbie, so
<ELLIOTTCABLE>
ZirconiumX: that's okay! so am I. I'll take any advice at this point. 🤣
<ZirconiumX>
I think writing the parser/lexer would actually be a good learning experience, myself
<ZirconiumX>
Though I'd be a heretic and use a Go-style lexer/parser
<ZirconiumX>
That might not mean much to you, though
catern has joined #ocaml
<ZirconiumX>
Essentially the parser and lexer become coroutines
<ZirconiumX>
Instead of trying to lex it all and then parse it all
ohama has joined #ocaml
<ZirconiumX>
Essentially the core of a mini lisp is a recursive descent parser
<ZirconiumX>
When you find a left paren, you recurse
<ZirconiumX>
And then you can represent the AST as a (G?)ADT
<ZirconiumX>
ELLIOTTCABLE: start with something small like that
<companion_cube>
I think the only parser combinator in serious use these days is angstrom
<companion_cube>
but it's maybe a bit too oriented towards high-perf
ozzymcduff has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
<discord3>
<Perry> R5RS is actually context free, IIRC.
<discord3>
<Perry> In fact, I've written R5RS parsers and I'm pretty damn sure it's context free.
<discord3>
<Perry> It's just a little weird at the lexical level.
<discord3>
<Perry> ocamllex + Menhir will be fine for the job.
<discord3>
<Perry> You will have to be careful about coding the lexer, though, as the description in R5RS of the lexical level is not very clear or simple.
<discord3>
<Perry> I think it is built for DSLs that are almost ocamlish.
<discord3>
<Perry> (Genlex)
<companion_cube>
just use ocamllex
<companion_cube>
(or ulex or sedlex if you want unicode)
<discord3>
<Perry> sedlex. ulex isn't going anywhere, sedlex might. I might actually get enough energy to start implementing enough features to make it roughly equivalent to ocamllex at some point.
<discord3>
<Perry> "in my copious spare time" which isn't very copious. 😃
<discord3>
<Perry> or Drup or someone else might.
<discord3>
<mseri> 😄
pierpal has quit [Quit: Poof]
pierpal has joined #ocaml
<discord3>
<Perry> Anyway, ELLIOTTCABLE, feel free to hit me up with questions about how to parse R5RS in OCaml. Hell, if you're willing to do a pretty clean job of parsing it and to put the parser up on github, I'll probably be willing to answer quite a few questions. I'm easy to find on the discord side of the bridge.
<ZirconiumX>
Is there a link to the Discord channel?
dxtr has quit [Ping timeout: 240 seconds]
Fare has quit [Ping timeout: 276 seconds]
jnavila has quit [Remote host closed the connection]
kakadu has joined #ocaml
kakadu has quit [Remote host closed the connection]
kakadu has joined #ocaml
Fare has joined #ocaml
sgnb has joined #ocaml
steenuil has quit [Remote host closed the connection]