<d_bot>
<hhugo> Seems related to injectivity annotations
mxns has quit [Ping timeout: 260 seconds]
mjsor has joined #ocaml
zebrag has quit [Ping timeout: 272 seconds]
<d_bot>
<hhugo> It's not a new error apparently
zebrag has joined #ocaml
yomimono has joined #ocaml
mxns has joined #ocaml
mxns has quit [Ping timeout: 264 seconds]
<d_bot>
<Kate> I don't think I've seen that one anywhere
amiloradovsky has quit [Ping timeout: 264 seconds]
Hrundi_V_Bakshi has quit [Ping timeout: 240 seconds]
amiloradovsky has joined #ocaml
mxns has joined #ocaml
borne has quit [Ping timeout: 260 seconds]
mxns has quit [Ping timeout: 260 seconds]
Haudegen has quit [Ping timeout: 264 seconds]
amiloradovsky1 has joined #ocaml
amiloradovsky has quit [Remote host closed the connection]
amiloradovsky1 is now known as amiloradovsky
tryte_ has joined #ocaml
tryte has quit [Ping timeout: 240 seconds]
reynir has quit [Remote host closed the connection]
reynir has joined #ocaml
amiloradovsky has quit [Remote host closed the connection]
amiloradovsky has joined #ocaml
nicoo has quit [Ping timeout: 240 seconds]
amiloradovsky1 has joined #ocaml
amiloradovsky has quit [Ping timeout: 260 seconds]
amiloradovsky1 is now known as amiloradovsky
nicoo has joined #ocaml
amiloradovsky has quit [Ping timeout: 260 seconds]
mxns has joined #ocaml
mxns has quit [Ping timeout: 264 seconds]
mfp has quit [Ping timeout: 260 seconds]
amiloradovsky has joined #ocaml
amiloradovsky has quit [Ping timeout: 260 seconds]
ggole has joined #ocaml
mmohammadi9812 has quit [Quit: Quit]
narimiran has joined #ocaml
waleee-cl has quit [Quit: Connection closed for inactivity]
_whitelogger has joined #ocaml
mxns has joined #ocaml
mxns has quit [Ping timeout: 264 seconds]
raver has joined #ocaml
borne has joined #ocaml
mjsor has quit [Quit: Konversation terminated!]
borne has quit [Ping timeout: 260 seconds]
borne has joined #ocaml
hnOsmium0001 has quit [Quit: Connection closed for inactivity]
<d_bot>
<craigfe> That error is the one that gets given for non-injective GADT definitions:
<d_bot>
<craigfe> ```ocaml
<d_bot>
<craigfe> type 'a s
<d_bot>
<craigfe> type _ t = T : 'a -> 'a s t
<d_bot>
<craigfe> ```
<d_bot>
<craigfe> "In this definition, a type variable cannot be deduced from the type parameters."
<d_bot>
<craigfe> (The type-checker is worried that `'a` will disappear under expansion of `s`, and so won't have a good type to assign when pattern matching on `T`)
<d_bot>
<craigfe> So it seems plausible that one could also reach that error via injectivity annotations; couldn't find an example of it right now though
mxns has joined #ocaml
Haudegen has joined #ocaml
mxns has quit [Ping timeout: 258 seconds]
Serpent7776 has joined #ocaml
mal`` has quit [Quit: Leaving]
mal`` has joined #ocaml
mxns has joined #ocaml
mxns has quit [Ping timeout: 256 seconds]
olle has joined #ocaml
raver has quit [Remote host closed the connection]
delysin has quit [Quit: WeeChat 2.9]
bartholin has joined #ocaml
mfp has joined #ocaml
nullcone has quit [Quit: Connection closed for inactivity]
tane has joined #ocaml
bartholin has quit [Quit: Leaving]
bartholin has joined #ocaml
mxns has joined #ocaml
mxns has quit [Ping timeout: 264 seconds]
raver has joined #ocaml
neiluj has joined #ocaml
neiluj has quit [Changing host]
neiluj has joined #ocaml
nicoo has quit [Ping timeout: 240 seconds]
mxns has joined #ocaml
nicoo has joined #ocaml
Haudegen has quit [Read error: Connection reset by peer]
FreeBirdLjj has joined #ocaml
Haudegen has joined #ocaml
neiluj has quit [Ping timeout: 256 seconds]
raver has quit [Remote host closed the connection]
<d_bot>
<Cyclomatic Complexity> I imagine `Modify` and `Field` are macros defined elsewhere. But instead of grepping everywhere, is there a document explaining the structure of those files?
<mrvn>
I ment more like: bytecomp/translcore.ml
<mrvn>
"%array_unsafe_get", Parrayrefu Pgenarray;
<mrvn>
By the way: Why does the bytecode use caml_array_unsafe_get_float but not caml_array_unsafe_get_addr?
<mrvn>
s/bytecode/bytecomp/
raver has joined #ocaml
gareppa has quit [Remote host closed the connection]
mxns has quit [Ping timeout: 272 seconds]
<d_bot>
<Cyclomatic Complexity> (i have personally no idea, i am very new to all of this)
jnavila has joined #ocaml
<mrvn>
In case you haven't figured it out yet but the externals that start with % are compiler primitives where the compiler can generate inline code instead of having a C call. Or call a specific sub function if it can infer the type. Like float array.
mxns has joined #ocaml
decentpenguin has quit [Ping timeout: 264 seconds]
narimiran has quit [Ping timeout: 240 seconds]
decentpenguin has joined #ocaml
Hrundi_V_Bakshi has quit [Quit: No Ping reply in 180 seconds.]
Hrundi_V_Bakshi has joined #ocaml
jnavila has quit [Quit: Konversation terminated!]
mrvn has quit [Ping timeout: 260 seconds]
mrvn has joined #ocaml
Hrundi_V_Bakshi has quit [Quit: No Ping reply in 180 seconds.]
Hrundi_V_Bakshi has joined #ocaml
fishyfriend_ has joined #ocaml
orbifx has joined #ocaml
<orbifx>
hello all
<orbifx>
I want a module type, which has a function taking the same type as a parameter:
<orbifx>
end
<orbifx>
val f : (module M) -> .. -> ..
<orbifx>
module type M = sig
<orbifx>
But the module isn't bound at that point, and writing as `module rec M ..` didn't work. Any recommendations?
tane has joined #ocaml
<zozozo>
maybe try adding an explicit S signature in M, and then have f take as argument a module of type S, and then try and create the signature M with module S = M ? (though I don't think that will work)
<orbifx>
So turn M to a functor.. and just pass the same parameter? Can give it a shot after I try another idea I had zozozo. Why do you think it won't work?
<zozozo>
well, I think in all cases, the point where you try and "tie the loop" and make things recursive will probably fail
<zozozo>
out of interest, what'd be your use case for this ?
<orbifx>
making a parser that takes subparsers as parameters
<orbifx>
seems having the module parameter in the signature as 'a is good enough for the compiler :)
<zozozo>
probably simpler to make a simple type for it I think: something like: type ('in, 'out) parser = P of ( ('in, 'out) parser -> 'in -> 'out )
<zozozo>
anyway, if you ahve a working solution, that's good, ^^
yomimono has joined #ocaml
<orbifx>
('b -> 'c -> (module M)) -> 'a
<orbifx>
hmm, this type ('in, 'out) reminds me of TyXML trees. It's not a solution yet.. I just got past that compilation error by replacing `module M` in the function signature with a type variable. But I think this causes a logic error further on:
<orbifx>
The type variable 'a occurs inside ('b -> 'c -> (module M)) -> 'a
<orbifx>
Error: This expression has type 'a but an expression was expected of type
<orbifx>
hmm that was something else.
<zozozo>
indeed, it seems to me like you actually want a recursive type, which is not allowed regularly, you'd need to either add an "indirection" using an ADT (like the one I wrote earlier with ('in, 'out) parser), or use the -rectypes option of the compiler (but this is discouraged as it may lead to weirds things)
<orbifx>
is there a short explanation for why recursive types are not allowed?
<d_bot>
<Drup> by default ? It's very very easy to make types that don't make sense
<steenuil>
shouldn't you be using parser combinators if you want a parser that takes subparsers as parameters?
<steenuil>
like just have a type ('in, 'out) = 'in -> ('out * 'in, error) result and then define the usual bind, choice, many, fix etc
<orbifx>
steenuil, zozozo: I think the in-out approach is based on in, out types been variants correct?
<zozozo>
orbifx: depends, really, `in can be simply strings, or some kind of token stream potentially, 'out would typically be your AST
<steenuil>
yeah it doesn't have to be variants, 'in is just whatever you feed to your parser and 'out is the result
<orbifx>
sure, though I don't produce an AST, but I get it. Has anyone written an explanation-review on this approach?
<orbifx>
trying to think the pros and cons of this approach.
<zozozo>
never used it personally, I've always found menhir to be great
<zozozo>
but as suggested above, parser generatros such as angstrom have taken a similar approach and I have heard good things about it
<companion_cube>
you could also make parsers based on `lexbuf -> 'a`
<companion_cube>
if you use ocamllex below
<orbifx>
I wish to write this in "pure" ML, rather than use any generator
<zozozo>
orbifx: by "pure" you mean without side-effects ?
<companion_cube>
without codegen it seems
<steenuil>
if you don't want to generate code parser combinators are probably the best way to go about it
tane has quit [Quit: Leaving]
<companion_cube>
well I'd say to write a `Lexer` module, which gives you at least: `cur: unit -> token` and `next:unit -> unit`
<orbifx>
sorry, bad choice of word.. without codegen as companion_cube, written by hand using plain OCaml
<companion_cube>
and then you can do `lexer -> 'a`
<companion_cube>
as an 'a parser
<companion_cube>
it's a valid route imho
<companion_cube>
if you want a flexible parser
<companion_cube>
(as in, it's not necessarily worse than parser combinators)
<zozozo>
right, and I just saw that I mad a horrible typo above: I meant parser combinators like angstrom, which as far as I know doesn't involve codegen ?
<steenuil>
you can use that Lexer module as input to a parser combinator too :)
<steenuil>
I was writing a blog post just about this but haven't finished it yet...
<zozozo>
anyway, seing the number of typos I'm making, it's time to sleep, ^^
<orbifx>
companion_cube: I _think_, my parsing approach is similar to what you suggested. I have a generic parse function which takes a module with the current valid syntax and applies it.
<orbifx>
I need to see a simple type 'in, 'out example, cause I'm also getting to my sleep time
nullcone has joined #ocaml
<orbifx>
companion_cube: have you got an article recommendations on this topic?