companion_cube changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml 4.11 release notes: https://caml.inria.fr/pub/distrib/ocaml-4.11/notes/Changes | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
_ks has joined #ocaml
mertyildiran has joined #ocaml
<mertyildiran> Hi, is it possible to call a function in OCaml from C? If so how can I do it?
cantstanya has quit [Ping timeout: 240 seconds]
cantstanya has joined #ocaml
_ks has quit [Quit: WeeChat 2.3]
cantstanya has quit [Remote host closed the connection]
cantstanya has joined #ocaml
<mertyildiran> Is the answer to my question CamlIDL? I think I need to generate C FFI for my OCaml module.
Haudegen has quit [Ping timeout: 260 seconds]
kleisli_ has joined #ocaml
waleee-cl has quit [Quit: Connection closed for inactivity]
mfp has quit [Ping timeout: 264 seconds]
ldbeth has joined #ocaml
ldbeth has quit [Remote host closed the connection]
ldbeth has joined #ocaml
ldbeth has quit [Ping timeout: 246 seconds]
zolk3ri has quit [Remote host closed the connection]
ldbeth has joined #ocaml
ldbeth has quit [Ping timeout: 272 seconds]
<mertyildiran> I've found a good example to call an OCaml function from C in here https://github.com/johnwhitington/ocaml-main-program-in-c Thanks anyway!
ldbeth has joined #ocaml
ldbeth has quit [Ping timeout: 240 seconds]
<inkbottle> I had to change `Fix : ('a -> 'a) lam -> 'a lam` to `Fix : (('a -> 'b) -> 'a -> 'b) lam -> ('a -> 'b) lam`
<inkbottle> And I had to replace `Fix f -> (eval f) (eval (Fix f))` by `Fix f -> fun a -> (eval f) (eval (Fix f)) a`
<inkbottle> And it just worked.
ldbeth has joined #ocaml
ldbeth has quit [Ping timeout: 260 seconds]
ldbeth has joined #ocaml
ldbeth has quit [Ping timeout: 272 seconds]
ldbeth has joined #ocaml
ldbeth has quit [Ping timeout: 240 seconds]
silver has quit [Read error: Connection reset by peer]
ldbeth has joined #ocaml
mertyildiran has quit [Quit: WeeChat 2.8]
ldbeth has quit [Ping timeout: 256 seconds]
ldbeth has joined #ocaml
ldbeth has quit [Ping timeout: 258 seconds]
bartholin has quit [Ping timeout: 272 seconds]
_whitelogger has joined #ocaml
reynir has quit [Ping timeout: 240 seconds]
reynir has joined #ocaml
Tuplanolla has joined #ocaml
ggole has joined #ocaml
waleee-cl has joined #ocaml
kleisli_ has quit [Ping timeout: 260 seconds]
decentpenguin has quit [Read error: Connection reset by peer]
decentpenguin has joined #ocaml
<d_bot> <Et7f3> For new #compiler channel why not #tip-and-tricks or #friendly-compiler
osa1 has joined #ocaml
_whitelogger has joined #ocaml
kleisli_ has joined #ocaml
waleee-cl has quit [Quit: Connection closed for inactivity]
Haudegen has joined #ocaml
sonologico has quit [Remote host closed the connection]
jbrown has joined #ocaml
mfp has joined #ocaml
osa1 has quit [Quit: osa1]
osa1 has joined #ocaml
kleisli_ has quit [Quit: Leaving]
outerpassage has joined #ocaml
<d_bot> <ostera> speaking of GADTs, I've been doing some type-foo this morning, trying to get a heterogeneous list working, and I'm having some trouble understanding an error that popped up in a `find` function:
<d_bot> <ostera>
<d_bot> <ostera> ```ocaml
<d_bot> <ostera> let rec find : type k v. k -> ((k * v) * 'r) het_kv_list -> v option =
<d_bot> <ostera> fun key het_kv_list ->
<d_bot> <ostera> match het_kv_list with
<d_bot> <ostera> | Cons ((key2, v), _) when key = key2 -> Some v
<d_bot> <ostera> | Cons (_, rest) -> find key rest
<d_bot> <ostera> | _ -> None
<d_bot> <ostera> ```
<d_bot> <ostera>
<d_bot> <ostera> the type of het_kv_list is
<d_bot> <ostera>
<d_bot> <ostera> ```ocaml
<d_bot> <ostera> type 'a het_kv_list =
<d_bot> <ostera> | Empty : (unit * unit) het_kv_list
<d_bot> <ostera> | Cons: ('k * 'v) * 'r het_kv_list -> (('k * 'v) * 'r) het_kv_list
<d_bot> <ostera> ```
<d_bot> <ostera>
<d_bot> <ostera> so its just a good ol' type-level list, except that I'm forcing key-value pairs onto its type structure. I cna tell its working since I have an `add` function that does the right thing and gives me back the right type as I add stuff.
<d_bot> <ostera>
<d_bot> <ostera> Anyway, the error I'm getting on this `find` function is on the `find key rest` expression, specifically over the `rest` name:
<d_bot> <ostera>
<d_bot> <ostera> ```ocaml
<d_bot> <ostera> Error: This expression has type 'r het_list but an expression was exected of type ((k * 'a) * 'r) het_list
<d_bot> <ostera> The type variable 'r occurs inside (k * 'a) * 'r
<d_bot> <ostera> ```
<d_bot> <ostera>
<d_bot> <ostera> I understand that I have to existentially quantify `k` and `v` since otherwise the types would escape their scope, but I'm not sure how to tell the compiler that `'r` here is safe to recur on.
<d_bot> <ostera> In particular, I'm not sure I understand what this implies:
<d_bot> <ostera>
<d_bot> <ostera> ```ocaml
<d_bot> <ostera> The type variable 'r occurs inside (k * 'a) * 'r
<d_bot> <ostera> ```
<d_bot> <craigfe> @ostera: I may be wrong, but it looks like the type of your `find` function requires that the type of the search key matches that of the first key in the association list. The type-checker is telling you that it's unable to recursively apply that property on the rest of the list in the inductive case
<d_bot> <craigfe> I think it's probably wrong to have a type equality there
<d_bot> <craigfe> (unless perhaps you want the keys to be homogeneous and only the _values_ to be heterogeneous, in which case you'll need to strengthen your type to require that)
<d_bot> <ostera> yes, i can see that -- when I do have `('k2 * 'v2)` instead, I do get the error that there was an expression of type `'k2` that should've been of type `k`
<d_bot> <craigfe> Indeed: polymorphic equality is magic but it's not _that_ magic šŸ™‚
<d_bot> <craigfe> It still unifies the types of its arguments
<d_bot> <ostera> right. maybe my approach is off then
<d_bot> <ostera> what I'm looking to do is associate a specific polymorphic variant tag with a type
<d_bot> <ostera> so that I can retrive the type with the tag later on
<d_bot> <craigfe> I expect that polymorphic variant tags are not structured enough to achieve what you want
<d_bot> <ostera> i could add some structure around them, i guess the question is whether I'll be able to do this `key = key2` (or use some equivalent construct) to prove that this is in fact the key you're looking for
<d_bot> <craigfe> You could use something like `gmap` (which requires a GADT specifying the key-value relation), or a list indexed by more structured objects. Oleg's `hlist` library does this with highly-typed peano integers
<d_bot> <ostera> > which requires a GADT specifying the key-value relation
<d_bot> <ostera> I unfortunately won't know the key-value relation upfront, only at the point of cons'ing to the list
<d_bot> <ostera> checking oleg's hlist
<d_bot> <craigfe> I think the problem with the `key = key2` idea is that it's trying to recover type information from an operation that cannot do that. You could use type equality witnesses for something like that, but I expect the better approach is to have the indexing value imply the correctness of the find
<d_bot> <craigfe> e.g. a `find` operation on such an hlist shouldn't return an `option`, as far as I can see
<d_bot> <ostera> hm. so if you haven't registered something then it wont type-check to find it
<d_bot> <craigfe> indeed.
<d_bot> <craigfe> If you want to "recover" type information after it has been lost, that's possible too, but it's a different approach
<d_bot> <ostera> suppose that my cons function returns the extended collection and also a key to find the element again
<d_bot> <ggole> Sounds a bit like you want a list of `univ`, but with a type equality rather than just a value
<d_bot> <craigfe> > suppose that my cons function returns the extended collection and also a key to find the element again
<d_bot> <craigfe> @ostera This would probably be simple, because indexing the head of the list will always be done with `Zero` (or some analogue)
<d_bot> <craigfe> I tend to agree with @ggole that you seem to be looking for dynamic types instead
<d_bot> <ostera> @craigfe I guess a nat type would work there
<d_bot> <ostera> @ggole what do you mean by `univ` here? šŸ¤”
<d_bot> <craigfe> ```ocaml
<d_bot> <craigfe> type univ = Pack : 'a typerep * 'a -> univ
<d_bot> <craigfe> ```
<d_bot> <craigfe> (presumably)
<d_bot> <ggole> It allows you to store and recover typed data in a heterogenous container
<d_bot> <craigfe> (and by extension the `Univ_map` module in the same library)
<d_bot> <ggole> Yeah, that's the one. Open variants make it pretty easy to implement.
<d_bot> <ostera> I see their map has a Packed.t type that hides one variable, but surfaces the other, and the key does the opposite
<d_bot> <ostera>
<d_bot> <ostera> ```ocaml
<d_bot> <ostera> type ('s, 'a) data
<d_bot> <ostera> type 's packed = T = : 'a key * ('s, 'a) data -> 's
<d_bot> <ostera> ```
osa1 has quit [Quit: osa1]
osa1 has joined #ocaml
<d_bot> <ostera> ```ocaml
<d_bot> <ostera> let find (type b) t (key : b Key.t) =
<d_bot> <ostera> match Map.find t (uid_of_key key) with
<d_bot> <ostera> | None -> None
<d_bot> <ostera> | Some (Packed.T (key', value)) ->
<d_bot> <ostera> (* cannot raise -- see [invariant] *)
<d_bot> <ostera> let Type_equal.T =
<d_bot> <ostera> Type_equal.Id.same_witness_exn (Key.to_type_id key) (Key.to_type_id key')
<d_bot> <ostera> in
<d_bot> <ostera> Some (value : (_, b) Data.t)
<d_bot> <ostera> ;;
<d_bot> <ostera> ```
<d_bot> <ostera> if I get this, `type b` quantifies the type of the key, but its the `Type_equal` module that's doing the work of checking that the two keys are _actually_ of the same type
<d_bot> <craigfe> Right
<d_bot> <ostera> which is what I naively attempted to do by fixing `'k` to `k`, and relying on `key = key2` as a guard
<d_bot> <ggole> Yeah, `=` has the wrong type to establish that two keys have the same type
<d_bot> <ostera> if I did have an equality function that forced two things to be of the same type, would this be enough? šŸ¤”
<d_bot> <craigfe> The notion of a `Refl` GADT is effectively the type-level equivalent of `=`, so you were not far off šŸ™‚
<d_bot> <ggole> Yeah, an equality function that returns the type witness you need is the way to go
<d_bot> <ggole> eg, the type of an equality function allowing you to know that `a key` and `b key` are the same would be something lik e`'a key` -> `'b key` -> `('a, 'b) type_equality option`
<d_bot> <ostera> that's assuming I own the structure of `key` and can put something inside of it to compare the two of them
<d_bot> <ggole> There needs to be enough information, yeah
<d_bot> <ggole> Enough *type* information, specifically
<d_bot> <ostera> ```ocaml
<d_bot> <ostera> type 'a key = 'a
<d_bot> <ostera> let key: 'a -> 'a key = fun x -> x
<d_bot> <ostera> ```
<d_bot> <ostera>
<d_bot> <ostera> off the top of my head, this shouldn't be enough
<d_bot> <craigfe> The idea is to create the type witness at a point when the type is known to you, and you can later _use_ the type witness to rediscover the type
<d_bot> <ostera> yeah, exactly, so this function `key` would be necessary for you to cons somethiing onto the list
<d_bot> <ostera> and you can use this key to find stuff back
<d_bot> <ggole> This GADT stuff isn't necessary for `univ` though
<d_bot> <ggole> Because `univ` 'tags' are typed
<d_bot> <craigfe> > ```ocaml
<d_bot> <craigfe> > type 'a key = 'a
<d_bot> <craigfe> > let key: 'a -> 'a key = fun x -> x
<d_bot> <craigfe> > ```
<d_bot> <craigfe> >
<d_bot> <craigfe> > off the top of my head, this shouldn't be enough
<d_bot> <craigfe> @ostera This doesn't forget the type information, so it's not actively hurting you, but it's also not creating a type witness that can be used later. Usually you'd have `'a -> key` (where `key` contains both a witness of `'a` and an `'a`, so is equivalent to `univ`)
<d_bot> <ggole> You do need it in order to have maps with type indexed keys, eg, if you want to associate `'a key` to `'a value` in a map
<d_bot> <ostera> @ggole what would the type_equality type look like?
<d_bot> <ostera> I guess this list is a sort of type indedex map šŸ¤”
<d_bot> <ggole> `type ('a, 'b) type_equality = Refl : ('a, 'a) type_equality`
<d_bot> <ggole> The `Refl` name is traditional
<d_bot> <craigfe> (and therefore law)
<d_bot> <ostera> I assume it comes from "Reflexive" ?
<d_bot> <ggole> Yep
<d_bot> <ostera> okay so here's what I got so far https://sketch.sh/s/mpHB7NfvCnjl7Uw4T1AsVq/
<d_bot> <ostera> I should refactor `find` to use the `eq` instead
<d_bot> <ggole> Hmm, the type of the registry containing the types of the elements seems to be a problem
<d_bot> <craigfe> You'll need a mechanism for assigning type identifiers as well as just the type equality values
<d_bot> <ggole> I think you can do this just with open types
<d_bot> <octachron> the type key is useless. Similarly, `eq` is wrong
<d_bot> <ggole> If I understand what you are going for
<d_bot> <octachron> If you want to prove identity, you need to go through open variant.
<d_bot> <ostera> @ggole yeah i think that could also work -- I'm trying to make sure that all the registered keys are typed-checked
<d_bot> <ostera> so that you know for a fact that a name is registered before you can do something with the associated value
vicfred has quit [Remote host closed the connection]
<d_bot> <ostera> (in this case I'm intending to use the process type as the value, so that registering a process by name, and finding it by name, yields a witness of the type of messages it can receive)
vicfred has joined #ocaml
<d_bot> <ostera> maybe the mistake was to use polymorphic variant tags as names? šŸ¤”
<d_bot> <ggole> ```ocaml
<d_bot> <ggole> type elt = ..
<d_bot> <ggole> type registry = elt list
<d_bot> <ggole>
<d_bot> <ggole> type proc_3_message_type = | Add of int
<d_bot> <ggole>
<d_bot> <ggole> type elt +=
<d_bot> <ggole> | WorkerPool of int
<d_bot> <ggole> | SocketPool of string
<d_bot> <ggole> | OtherPool of proc_3_message_type
<d_bot> <ggole>
<d_bot> <ggole> let registry = [
<d_bot> <ggole> WorkerPool 1;
<d_bot> <ggole> SocketPool "hello";
<d_bot> <ggole> OtherPool (Add 2);
<d_bot> <ggole> ]
<d_bot> <ggole>
<d_bot> <ggole> let rec find f = function
<d_bot> <ggole> | [] -> None
<d_bot> <ggole> | x::xs ->
<d_bot> <ggole> match f x with
<d_bot> <ggole> | Some _ as result -> result
<d_bot> <ggole> | None -> find f xs
<d_bot> <ggole>
<d_bot> <ggole> let socket_pool_name =
<d_bot> <ggole> find
<d_bot> <ggole> (function
<d_bot> <ggole> | SocketPool name -> Some name
<d_bot> <ggole> | _ -> None)
<d_bot> <ggole> registry
<d_bot> <ggole> ```
<Armael> note that you're spamming irc like hell
<d_bot> <ggole> This is a bit rough, but it should get the idea across
<d_bot> <ggole> Sigh
<d_bot> <ggole> I guess I'll use a paste site?
<d_bot> <ostera> (sounds like something the bot could do?)
osa1 has quit [Ping timeout: 240 seconds]
<d_bot> <ostera> @ggole yeah the reason I didn't go down this path was the added ceremony -- if you want to register a name you have to start by extending the type, but maybe that's good enough for now.
<d_bot> <ggole> With local modules you can hide the type extension work under a function and just return an accessor
<d_bot> <ggole> Although I'm not sure that's much of an improvement
<d_bot> <craigfe> @ostera Here's an example of using local modules to hide type extension work: https://github.com/mirage/irmin/blob/master/src/irmin/type/witness.ml#L27
<d_bot> <craigfe> (In this case, also implementing a nice signature for type identifiers and equality witnesses that would work for your case, but seems to be overkill as @ggole says)
<d_bot> <ostera> i think one of the reasons I went with the hlist was that I really just need to get a hold of a witness of the type associated with a particular name
<d_bot> <ostera> i've got a send function that looks like:
<d_bot> <ostera>
<d_bot> <ostera> ```ocaml
<d_bot> <ostera> val send : 'm -> 'm proc -> unit
<d_bot> <ostera> ```
<d_bot> <ostera>
<d_bot> <ostera> where `'m proc` is actually abstract
<d_bot> <ostera>
<d_bot> <ostera> and I was hoping to use a `key` type to retrieve that specific `'m proc` type, so that I could use `send`
<d_bot> <ostera> so calling
<d_bot> <ostera>
<d_bot> <ostera> ```ocaml
<d_bot> <ostera> Registry.register `my_name self
<d_bot> <ostera> ```
<d_bot> <ostera>
<d_bot> <ostera> where `self : <some type> proc`
<d_bot> <ostera>
<d_bot> <ostera> would let me do
<d_bot> <ostera>
<d_bot> <ostera> ```ocaml
<d_bot> <ostera> let proc = Register.find `my_name in
<d_bot> <ostera> send message proc
<d_bot> <ostera> ```
<d_bot> <ostera> but given that the registry should be global and mutable (ugh), I think I'm pushing this too far :/
<d_bot> <ostera> (or just approaching it from the wrong angle)
<d_bot> <octachron> It sounds like a hmap would work well enough?
<d_bot> <octachron> Or the janestreet one. Or orec.
<d_bot> <ostera> i'll have a look at orec too
<d_bot> <octachron> Note that orec is a cutesy interface to make hmaps look like open records.
<d_bot> <ostera> noted
<d_bot> <ostera> @ggole @craigfe thanks for bouncing this with me btw šŸ™Œ
<d_bot> <ggole> np!
<d_bot> <ostera> hmap is currently outside my understanding in the usage of modules šŸ¤¦
<d_bot> <ostera> @octachron when you say that the types key and eq were useless, what did you mean?
<d_bot> <octachron> They are basically equivalent to @ggole 's code with a more regular interface, using first class modules to pack extension constructors with a known name as the main ingredient.
<d_bot> <octachron> So `type any = Any: 'any -> any` which is the same type as your type key up to renaming cannot be used to do anything (magically polymorphic functions excepted).
<d_bot> <octachron> Because if I have a value of type `Any x` , I only know that there is some unknown type ` 'any` such that `x: 'any`, and nothing more.
<d_bot> <ostera> hm, if I get this right, i should also include then type information about _the value_ that the key points to?
<d_bot> <ostera> (but not necessarily as a visible parameter of the type? šŸ¤”)
<d_bot> <octachron> No, you need some information about the type `'any`.
<d_bot> <octachron> A simple, valid example of existential types would be `type showable = Pack: 'a * ('a -> string) -> showable`
<d_bot> <octachron> Here, if I get a value of type `Pack (x, show)`, I know that `show x` is well-typed.
<d_bot> <ostera> right, and that'd work for any type 'a as long as we provide the corresponding `'a -> string` that we can use to "know" what `'a` is?
<d_bot> <ostera> (maybe "know" is the wrong verb there)
<d_bot> <ostera> e.g, if I give you
<d_bot> <ostera>
<d_bot> <ostera> ```ocaml
<d_bot> <ostera> val get_value : type a. (a -> string) -> showable -> a
<d_bot> <ostera> ```
<d_bot> <ostera> would you be able to use `(a -> string)` to know the type of `a` and return that? šŸ¤”
<d_bot> <octachron> No, that cannot work.
<d_bot> <octachron> You cannot make the inner type `a` escape.
<d_bot> <ostera> but you could implement
<d_bot> <ostera>
<d_bot> <ostera> ```ocaml
<d_bot> <ostera> val str : showable -> string
<d_bot> <ostera> ```
<d_bot> <octachron> And since, there is no way to prove the identity of functions, you cannot learns anything about the inner type from the `a -> string` function.
<d_bot> <octachron> Yes, `str` is implementable.
<d_bot> <ostera> okay so within the scope of a constructor, you'd ideally pack all the information you need so that you can reconstruct some value later
<d_bot> <octachron> Sort of?
<d_bot> <ostera> how is this more useful than without `'value`? šŸ¤”
<d_bot> <ostera>
<d_bot> <ostera> ```ocaml
<d_bot> <ostera> type key = Key: 'name * 'value -> key
<d_bot> <ostera> ```
<d_bot> <ostera> (my guess is that it isnt)
<d_bot> <octachron> This is still useless? Now, you know that you have two values of which you know nothing.
<d_bot> <ostera> good! okay, so I understand why it's useless.
<d_bot> <ostera> this should be useful, right?
<d_bot> <ostera>
<d_bot> <ostera> ```ocaml
<d_bot> <ostera> type 's t = T : 'a * ('s * 'a) -> 's t
<d_bot> <ostera> ```
<d_bot> <octachron> Not really? You have two elements of an unknown types along with a element of a known type.
<d_bot> <octachron> Any program that is using `'s t` (without magical polymorphic functions) can be rewritten to use `type 'a id = T of 'a`.
<d_bot> <ostera> alright, i'm clearly out of my depth here. Any good introduction to GADTs that could clear out the rules by which type information can be recovered?
<d_bot> <octachron> Existential types are here to erase information. You cannot recover it. However, you can sometimes GADTs abilities to add equation to types to rediscover some equalities.
<d_bot> <ostera> so its a question of what information can I throw away, and what information will I keep to figure out what I threw away
jbrown has quit [Ping timeout: 272 seconds]
<d_bot> <ostera> anyway, i'll take a break now -- much to learn, thanks @octachron šŸ™Œ
<d_bot> <octachron> Trying to write with a small typed dsl is often a good way to play with those questions.
ziman has joined #ocaml
outerpassage has quit [Ping timeout: 260 seconds]
<ziman> Hello! I have X.ml containing 'let n : int = 3', and Y.ml containing 'let _ = Printf.printf "%d\n" X.n'. I compile X and Y using ocamlopt, and then link them together. So far so good. When I change the value of 'n', recompile X.ml but not Y.ml, and attempt to link them together, I get "Files Y.cmx and X.cmx make inconsistent assumptions over implementation X". I have two questions: 1) where can I
<ziman> read more about what exactly those assumptions are? I have not been able to google that up yet. 2) i'd expect that as long as I don't change the interface of X, I can update its implementation and link the program together again. Does it not work that way?
troydm has joined #ocaml
<ziman> (manually making an X.mli and compiling it into a .cmi file does not seem to help, either)
jnavila has joined #ocaml
<d_bot> <Et7f3> When you compile file all .cmo contain checksum of the cmi
<d_bot> <Et7f3> When you have only a .ml file a .mli is inferred to produce a .cmi
outerpassage has joined #ocaml
<ziman> so i tried to write a .mli file manually but even if i don't touch the .mli file and compile just the .ml into .cmx, i seem to get the same problem. Also, the error message is strange; I'd expect "Files Y.cmx and X.cmx make inconsistent assumptions over interface X" if the .cmi file were the problem but I get "Files Y.cmx and X.cmx make inconsistent assumptions over implementation X".
<ziman> looks like -opaque solves this
Anarchos has joined #ocaml
<ziman> but it's also good news that without -opaque, i can get cross-module optimisation, which is great
outerpassage has quit [Quit: Leaving]
aterius has joined #ocaml
osa1 has joined #ocaml
osa1 has quit [Quit: osa1]
osa1 has joined #ocaml
sonologico has joined #ocaml
Anarchos has quit [Quit: Vision[0.10.3]: i've been blurred!]
jflewkfjlwjefklf has joined #ocaml
jflewkfjlwjefklf has quit [Remote host closed the connection]
zebrag has joined #ocaml
inkbottle has quit [Ping timeout: 256 seconds]
ajfelfjlsdkfjejf has joined #ocaml
jbrown has joined #ocaml
<brettgilio> anybody aware of an ocaml implementation of precis rfc8264-6
_ks has joined #ocaml
ajfelfjlsdkfjejf has quit [Quit: Leaving]
reynir has quit [Ping timeout: 256 seconds]
reynir has joined #ocaml
narimiran has joined #ocaml
borne has joined #ocaml
tane has joined #ocaml
worc3131 has joined #ocaml
andreas303 has quit [Remote host closed the connection]
andreas303 has joined #ocaml
<brettgilio> Didnt find one, decided i'll implement it
narimiran has quit [Ping timeout: 258 seconds]
jnavila has quit [Quit: Konversation terminated!]
<d_bot> <dinosaure> @ostera if you want something like: `send : 'a t -> 'a -> unit` and `recv : 'a t -> 'a`, you probably should look `colombe` which delivers such function from a description of a _protocol_: https://github.com/mirage/colombe/blob/master/src/state.ml
<d_bot> <ostera> Thank, ill have a look šŸ™‚ i do have those functions in place already, judging by the signature s
<d_bot> <ostera> What Iā€™m working out still is the registry that for a given type ā€˜a (ie, a polymorphic variant tag) gives me back some ā€˜b t that I can use in send
<d_bot> <dinosaure> about session-type, indexed monad can help you to describe a full protocol like session-types, however readability is more important for me
<d_bot> <dinosaure> extensible variant such as `type 'a t = ..` and `type 'a t += T : 'a t` can help you but such design is too permissive for me
<d_bot> <ostera> how so?
<d_bot> <ostera> i mean, in what context is it too permissive for you?
<d_bot> <ostera> thanks for the example btw! is this encoding the valid message sequencing of the protocol in the signatures of send/recv?
<d_bot> <dinosaure> I mean, from the point of view of the user, he is able to extend the variant and break some of your assumptions. For example, you can think that for any new exception (which is a extensible variant), we _should_ have a pretty-printer (or a way to serialize/deserialize it, encode/decode it), however the user can extend such variant without such functions
<d_bot> <dinosaure> about the example, it's just way to describe the SMTP with valid (and expected) types (with GADT)
<d_bot> <ostera> this is very relevant to me, thanks for sharing
<d_bot> <ostera> i can imagine a process defining the protocol in you have to communicate with it in a similar way
osa1 has quit [Quit: osa1]
<d_bot> <ostera> but I'd probably end up making an API _on top_ of the more primitive `send : 'a t -> 'a -> unit` to still allow for less structure, yet well typed, message passing
<d_bot> <dinosaure> good šŸ™‚
waleee-cl has joined #ocaml
ziman has left #ocaml ["WeeChat 2.9"]
ggole has quit [Quit: Leaving]
borne has quit [Ping timeout: 260 seconds]
borne has joined #ocaml
<d_bot> <ostera> @dinosaure after some pondering, this is what I came up for the extensible variants -- its not super sophisticated, but seems to give me the guarantees i need:
<d_bot> <ostera>
<d_bot> <ostera> 1. can only retrieve names that were actually registered
<d_bot> <ostera> 2. each registered name is unique and typed
<d_bot> <ostera> 3. retrieving a name gives you back the `'a t` that you'd expect
<d_bot> <ostera>
<d_bot> <ostera> it does have the drawbacks of extensible variants you mention, in particular a potential source of bugs is someone defining their own `find_in_registry` function that knows about some other variant constructor than their own.
<d_bot> <ostera>
<d_bot> <ostera> Another drawback is that its a little boilerplatey, and without some ppx to rewrite the extension constructor, I'm not sure how to make this work with a nice functor include šŸ¤· -- would have to keep digging.
<d_bot> <ostera>
<d_bot> <ostera> Anyway, here's the source if you're interested: https://sketch.sh/s/l3uZ5gkMLa7KKCSjWHu8b2/
<d_bot> <dinosaure> You probably should use `type 'a t = private ..` to enforce the user to use `register`
<d_bot> <dinosaure> I dis something about that on the new version of `conduit`: https://github.com/mirage/ocaml-conduit/blob/056e94b57e6fc2a08b587e949a7c38d2f1b79e6a/src/core/e0.ml#L84
<d_bot> <dinosaure> But I need to Alep now, sorry :(
<d_bot> <ostera> no worries, its getting late over here too
<d_bot> <ostera> thanks @dinosaure šŸ™Œ
<d_bot> <ostera> i'll have a look at that tomorrow
Tuplanolla has quit [Quit: Leaving.]
tane has quit [Quit: Leaving]
<d_bot> <stab> hmmm... i suspect this program graph is constructed poorly considering there are no SCCs where all nodes in the SCC are dominated by a member of that SCC
<d_bot> <stab> which translates to this program having no traditional loops which seems unlikely lol
sagax has quit [Ping timeout: 272 seconds]
Haudegen has quit [Ping timeout: 246 seconds]
<d_bot> <stab> lovely i think ive found a bug in ocamlgraph
<d_bot> <stab> given a node "a" calling `dom "a" "a"` returns false. fairly sure based on the defintion of dominators a node always dominates itself
<d_bot> <stab> eh im guessing it's an issue in my code with equality maybe
<d_bot> <stab> because they do do the check
mertyildiran has joined #ocaml
<d_bot> <stab> nah pretty sure it's an issue with the implementation of dominatorsreading it through again