<tbli>
i'm a little confused as to the meaning of the type signature `let (>>=) (p : 'a parser) (q : 'a -> 'b parser) : 'b parser =`
cantstanya has quit [Ping timeout: 240 seconds]
cantstanya has joined #ocaml
smazga has joined #ocaml
tbli has quit [Remote host closed the connection]
zebrag has quit [Quit: Konversation terminated!]
zebrag has joined #ocaml
smazga has quit [Ping timeout: 260 seconds]
smazga has joined #ocaml
smazga has quit [Ping timeout: 246 seconds]
<d_bot>
<beheddard> It takes a value in the parser monad, and a function which takes a parameter not wrapped in parser and returns a value in parser. So you can think of it as doing the unwrapping of 'a from parser and giving it to the function q
tbli has joined #ocaml
smazga has joined #ocaml
<tbli>
yeah, i'm kind of struggling to understand the concept of being wrapped in a parser
<tbli>
so i read the solution to that one and am trying to implement `map (f : 'a -> 'b) (p : 'a parser) : 'b parser`
<tbli>
so i presume you would want to start with something like `fun f -> p f`, but i'm not sure how to continue from there
<tbli>
f' i guess, since f is overloaded :)
<d_bot>
<beheddard> Wrapped isn't the best word I guess in this case, but whatever your parser is, when you create it has some kind of configuration or state I presume, which is polymorphic
<d_bot>
<beheddard> ( 'a )
<d_bot>
<beheddard> So bind would take functions that create parsers with some input
<tbli>
and they defined `type cursor = token Seq.t`
<d_bot>
<beheddard> map simply takes functions that "map" a value into another and gives you a parser with that state/config
<tbli>
yeah, so i don't really understand why you would want to map a parser?
<tbli>
or what the purpose of doing that would be?
<tbli>
like right now i have a model that each parser has some thing that it's trying to parse
<tbli>
so maybe you have a parser to parse the string "123"
<d_bot>
<beheddard> Ive never worked with them really sorry π I'm just speaking generally, but you might want to take the function that the parser currently uses, compose it with another function, then return a new parser with the composed function
<tbli>
so question, does `p >>= (fun x -> return x)` return p?
smazga has quit [Ping timeout: 256 seconds]
<d_bot>
<beheddard> the result is whatever `return x` evaluates to, so it should be the same as p
<d_bot>
<beheddard> Assuming that `return` is defined as usual for a monad
<tbli>
and how should (<<) and (>>) work?
<tbli>
is `let (>>) p q = q` valid?
<tbli>
it type checks but seems wrong
<d_bot>
<beheddard> I'm not familiar with the usual functions that those infixes would represent in the context of a parser
<d_bot>
<beheddard> usually `>>` means "compose" to me
smazga has joined #ocaml
<d_bot>
<beheddard> like `let ( >> ) f g x = g (f x)`
<d_bot>
<beheddard> might be something different expected in the exercises that you are going through, I havem
smazga has quit [Ping timeout: 264 seconds]
smazga has joined #ocaml
smazga has quit [Ping timeout: 265 seconds]
zebrag has quit [Quit: Konversation terminated!]
zebrag has joined #ocaml
smazga has joined #ocaml
smazga has quit [Ping timeout: 240 seconds]
<sleepydog>
i think (>>) here is defined as ( *> ) in angstrom, e.g. "run parser x and y, then discard the results of x and choose the results of y"
<sleepydog>
so you can do things in angstrom like `char '(' *> word <* char ')' >>= fun inner_value -> ...` and so on
smazga has joined #ocaml
<sleepydog>
as far as why you would want the map operation, it's just a convenience that lets you use normal functions more easily.
<sleepydog>
compare : `take_while1 is_digit >>= fun num -> return int_of_string num` to `take_while1 is_digit >>| int_of_string` (where (>>|) is the map operation)
smazga has quit [Ping timeout: 264 seconds]
mxns has joined #ocaml
mxns has quit [Ping timeout: 272 seconds]
tbli has quit [Ping timeout: 245 seconds]
zebrag has quit [Quit: Konversation terminated!]
zebrag has joined #ocaml
mxns has joined #ocaml
smazga has joined #ocaml
smazga has quit [Ping timeout: 264 seconds]
mxns has quit [Ping timeout: 272 seconds]
smazga has joined #ocaml
mbuf has joined #ocaml
smazga has quit [Ping timeout: 246 seconds]
smazga has joined #ocaml
smazga has quit [Ping timeout: 256 seconds]
zebrag has quit [Read error: Connection reset by peer]
zebrag has joined #ocaml
oni-on-ion has quit [Quit: Quit]
sleepydog has quit [Ping timeout: 240 seconds]
smazga has joined #ocaml
waleee-cl has quit [Quit: Connection closed for inactivity]
Serpent7776 has joined #ocaml
smazga has quit [Ping timeout: 264 seconds]
narimiran has joined #ocaml
dborisog has joined #ocaml
shawnw has joined #ocaml
andreas303 has quit [Quit: andreas303]
andreas303 has joined #ocaml
smazga has joined #ocaml
smazga has quit [Ping timeout: 264 seconds]
jlr has joined #ocaml
raver has joined #ocaml
zebrag has quit [Quit: Konversation terminated!]
bjorkint0sh has quit [Remote host closed the connection]
zebrag has joined #ocaml
bjorkint0sh has joined #ocaml
Haudegen has joined #ocaml
mbuf has quit [Ping timeout: 260 seconds]
bartholin has joined #ocaml
indicato` has quit [Remote host closed the connection]
pyx has joined #ocaml
pyx has quit [Client Quit]
Seylerius has quit [Quit: Idle for 30+ days]
Haudegen has quit [Quit: Bin weg.]
Haudegen has joined #ocaml
glass is now known as theglass
mbuf has joined #ocaml
hnOsmium0001 has quit [Quit: Connection closed for inactivity]
Mehdi[m] has left #ocaml ["User left"]
zebrag has quit [Quit: Konversation terminated!]
zebrag has joined #ocaml
steenuil has joined #ocaml
_whitelogger has joined #ocaml
mfp has joined #ocaml
mro_name has joined #ocaml
Tuplanolla has joined #ocaml
smazga has joined #ocaml
olle_ has joined #ocaml
zebrag has quit [Read error: Connection reset by peer]
zebrag has joined #ocaml
smazga has quit [Ping timeout: 240 seconds]
zebrag has quit [Read error: Connection reset by peer]
zebrag has joined #ocaml
nicoo has quit [Ping timeout: 240 seconds]
cantstanya has quit [Ping timeout: 240 seconds]
mro_name has quit [Quit: Leaving...]
cantstanya has joined #ocaml
nicoo has joined #ocaml
mbuf has quit [Ping timeout: 264 seconds]
andreas303 has quit [Remote host closed the connection]
nullcone has quit [Quit: Connection closed for inactivity]
zebrag has quit [Quit: Konversation terminated!]
zebrag has joined #ocaml
ArthurStrong has joined #ocaml
kitties is now known as ki||ies
ki||ies is now known as kitties
andreas303 has joined #ocaml
smazga has joined #ocaml
smazga has quit [Ping timeout: 264 seconds]
zebrag has quit [Quit: Konversation terminated!]
zebrag has joined #ocaml
zebrag has quit [Quit: Konversation terminated!]
zebrag has joined #ocaml
shawnw has quit [Ping timeout: 246 seconds]
waleee-cl has joined #ocaml
zebrag has quit [Quit: Konversation terminated!]
zebrag has joined #ocaml
smazga has joined #ocaml
smazga has quit [Ping timeout: 260 seconds]
olle_ has quit [Ping timeout: 272 seconds]
mxns has joined #ocaml
sleepydog has joined #ocaml
hnOsmium0001 has joined #ocaml
smazga has joined #ocaml
hannes has quit [Quit: leaving]
hannes has joined #ocaml
raver has quit [Quit: Gateway shutdown]
zebrag has quit [Remote host closed the connection]
zebrag has joined #ocaml
aiowej has joined #ocaml
<aiowej>
I'm using Dune and utop for the first time. My project has a library called "parser.ml". I'm getting weird errors, about `parser.cmi` and `utop.exe` making inconsistent assumptions regarding this module. This happened when it was named "parse.ml" as well. Are those two words forbinned/reserved? Seems strange since I don't personally know anyone using OCaml and not implementing languages in it :D
<d_bot>
<stab> are you running dune utop?
<d_bot>
<stab> i believe in utop you would be able to access the module as Parse cause capitalization but id need more info to try to help
tane has joined #ocaml
<octachron>
dune utop uses utop-full which links the compiler-libs, so your Parser module is probably conflicting with OCaml's one.
<aiowej>
yes - `dune utop . -- -emacs` to be precise.
<theblatte>
does the toplevel itself build successfully? utop will warn about conflicting modules but for me that doesn't prevent it from running
<theblatte>
I have "(link_flags (-linkall -warn-error -31))" in the corresponding dune stanza
<theblatte>
not sure if that's still needed
<aiowej>
It does lol! But it was more than 25 lines up, so I didn't notice (as the human eye is not able to perceive more than 80*25 chars anyways)
<aiowej>
Thanks, I'll just name it something other than Parser
<d_bot>
<stab> also lol my server still doesnt work i hate everything... I confirmed that it is a server issue because the rust implementation of the server works fine
<companion_cube>
could it be a buffering issue?
<theblatte>
names and buffering issues, the two biggest problems in OCaml
<d_bot>
<stab> maybe? it's super weird the async read line call just immediately returns with EOF
<d_bot>
<stab> but like there is a line there
<d_bot>
<stab> or coming anyways
<d_bot>
<stab> maybe it's like nonblock or something and insta returning?
<d_bot>
<stab> that would be weird behavior tho
<d_bot>
<stab> it is possible i dont understand anything that im doing with this async library.. i thought i did lol
zebrag has quit [Quit: Konversation terminated!]
zebrag has joined #ocaml
Jesin has quit [Quit: Leaving]
Jesin has joined #ocaml
<sleepydog>
if the fd were non-blocking i would expect a result other than `Eof
<sleepydog>
ah wait, you are calling unpack_reader_result twice, do you know which one receives the `Eof ?
zebrag has quit [Quit: Konversation terminated!]
zebrag has joined #ocaml
zebrag has quit [Remote host closed the connection]
<Fardale>
hannes: are the test in awa library under the isc license?
<dinosaure>
someone knows a free dataset of email addresses?
olle_ has joined #ocaml
<d_bot>
<Drup> well, any leaked dataset of hashed passwords π
<dinosaure>
not sure that it's legal :p
<Fardale>
hannes: great! thank you
<d_bot>
<Drup> well, it's a dataset.
mxns has quit [Ping timeout: 264 seconds]
mxns has joined #ocaml
olle_ has quit [Ping timeout: 246 seconds]
amr has joined #ocaml
amr has quit [Quit: WeeChat 2.5]
amr has joined #ocaml
<d_bot>
<Anurag> dinosaure: I think there are some publicly available email datasets that should be fine to use. I found one such public dataset at https://loc.gov/item/2018487913/?loclr=blogsig
<d_bot>
<stab> Any ideas on how to deal with nested monads? Basically im trying to write an async function that returns a read result of Ok|EOF so it's basically going to be returning a nested monad of type Read_result Defered.t
aiowej has quit [Read error: Connection reset by peer]
mxns has joined #ocaml
<d_bot>
<stab> The trick is i bind into the first read to utilize the undeferred value which will be either Ok or EOF so then ill have to bind it again. The problem is the deferred value is now inside the Ok|EOF monad context which isnt right...
<d_bot>
<stab> basically need to invert the monad
<d_bot>
<stab> i guess what im asking for is monad transformers i suppose?
<d_bot>
<stab> not too sure
mxns has quit [Ping timeout: 264 seconds]
mxns has joined #ocaml
jnavila has joined #ocaml
mxns has quit [Client Quit]
mxns has joined #ocaml
<d_bot>
<craigfe> @stab: I'm not 100% sure I follow your example but: (a) I expect nested binds not to change the layering order, (b) one cannot invert the ordering of arbitrary monads, (c) one _can_ pull a monadic action out of a container, which is sufficient for your use-case
<d_bot>
<craigfe> e.g. `'a Deferred.t Read_result.t -> 'a Read_result.t Deferred.t` is implementable just with pattern matching, but the reverse is not
<d_bot>
<stab> what im unhappy about here is the duplication of the logic where if the read failed i return Eof otherwise proceed with further reads, but i couldnt figure out how to get things to line up otherwise
<d_bot>
<stab> Like i feel like i should be able to leverage the read result monad to avoid that code duplication but im not sure how
mxns has joined #ocaml
<d_bot>
<stab> Because once i bind into the Read_result the deferred values will be inside a read result context instead of being able to lift them to the outside
<d_bot>
<craigfe> I see
<d_bot>
<stab> But yeah it seems like im doing what you are recommending which is like pattern matching to invert the monad
raver has joined #ocaml
<d_bot>
<craigfe> It does indeed look like there's a utility function waiting to be pulled out of there
<d_bot>
<craigfe> I'm trying to decide whether it's sufficient for you to literally just define the composition of the monads and use that:
<d_bot>
<craigfe>
<d_bot>
<craigfe> ```ocaml
<d_bot>
<craigfe> type 'a t = 'a Read_result.t Deferred.t
<d_bot>
<craigfe> val ( >>= ) : 'a t -> ('a -> 'b t) -> 'b t
<d_bot>
<craigfe> val return : 'a -> 'a t
<d_bot>
<craigfe> ```
<d_bot>
<craigfe> Looks like it would work to me: you have two cases where you're binding on the Deferred only to immediately bind / map on the Read_result
<d_bot>
<stab> oh yeah that makes a lot of sense
<d_bot>
<craigfe> The inner case is a bind + map, for which people sometimes define a specific helper function
<d_bot>
<craigfe> which I think is effectively the set of utility functions you want
<d_bot>
<stab> will definitely take a look. Thanks i dont think i ever would have thought of composing them into a monad but that makes a lot of sense lol
jlr has quit [Ping timeout: 272 seconds]
narimiran has quit [Ping timeout: 260 seconds]
<d_bot>
<beheddard> I've done similar, map Lwt, while binding the result inside
<d_bot>
<beheddard> Just made an infix for it and it became pretty painless
<d_bot>
<roddy> I would be inclined to convert your `Read_result.t`s into `Result.t`s immediately and then use `Deferred.Result.t` or `Deferred.Or_error.t` (the async equivalents of `Lwt_result`). Right now the second time you match on Read_result you're using Eof to indicate a failure that isn't necessarily an Eof. It would be nicer to have an error signalling what has actually gone wrong (i.e. Eof from the first read or Eof from the second or nu
<d_bot>
<stab> @roddy hmm i see what you are saying the context for this function tho is that it is being used in read all on a pipe to transform the pipe which only uses EOF to end the pipe...
<d_bot>
<stab> I guess to be technically correct what i would do is operate over a Deffered.Result.t to have the explicit errors then perhaps convert them back to an EOF at the end if i want to just end the pipe on any of the defined error
hoel has left #ocaml [#ocaml]
amr has joined #ocaml
Serpent7776 has quit [Quit: leaving]
amr has quit [Remote host closed the connection]
amr has joined #ocaml
jnavila has quit [Quit: Konversation terminated!]
olle_ has joined #ocaml
raver has quit [Ping timeout: 256 seconds]
raver has joined #ocaml
amr has quit [Remote host closed the connection]
amr has joined #ocaml
tane has quit [Quit: Leaving]
raver has quit [Quit: Gateway shutdown]
webshinra has quit [Remote host closed the connection]