gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.1 http://bit.ly/nNVIVH
NihilistDandy has joined #ocaml
Tobu has quit [Ping timeout: 272 seconds]
NihilistDandy has quit [Ping timeout: 264 seconds]
jmcarthur has quit [Ping timeout: 246 seconds]
Tobu has joined #ocaml
iago has quit [Quit: Leaving]
dsheets has quit [Quit: Leaving.]
pchopin has quit [Ping timeout: 272 seconds]
pchopin has joined #ocaml
<xenocons> http://marijnhaverbeke.nl/hob/saga/ looks interesting
maurer has left #ocaml []
JuzorBNC is now known as Juzor
datkin has quit [Ping timeout: 260 seconds]
Tobu has quit [Ping timeout: 260 seconds]
Juzor is now known as JuzorBNC
jimmyrcom has quit [Remote host closed the connection]
Tobu has joined #ocaml
emmanuelux has quit [Ping timeout: 245 seconds]
pchopin has quit [Remote host closed the connection]
Tobu has quit [Ping timeout: 272 seconds]
dsheets has joined #ocaml
Tobu has joined #ocaml
andreypopp has joined #ocaml
Tobu has quit [Ping timeout: 272 seconds]
sgnb has joined #ocaml
Tobu has joined #ocaml
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
andreypopp has quit [Quit: Quit]
cago has joined #ocaml
ftrvxmtrx has joined #ocaml
eikke has joined #ocaml
Snark has joined #ocaml
ankit9 has joined #ocaml
djcoin has joined #ocaml
silver has joined #ocaml
silver has quit [Remote host closed the connection]
silver has joined #ocaml
mika1 has joined #ocaml
julien is now known as julien_t
<eikke> I have an issue with higher-order functors, so if anyone would like to help me out
<eikke> doesnt compile (line 72)
<eikke> it doesn't "know" D1.m should equal S1(IO).m which is equal to S2(IO).m and (finally) equal to D2.m
skchrko has joined #ocaml
andreypopp has joined #ocaml
probst has joined #ocaml
probst has quit [Client Quit]
probst has joined #ocaml
tufisi has joined #ocaml
Kakadu has joined #ocaml
Cyanure has joined #ocaml
thomasga has joined #ocaml
benozol has joined #ocaml
Submarine has quit [Remote host closed the connection]
avsm has joined #ocaml
destrius has joined #ocaml
<mfp> eikke: you have to sprinkle some with type x = y
<mfp> eikke: S1:functor(ST1:STORE) -> FRONT with type t = ST1.t
<mfp> ditto for S2
<mfp> oh, the pb is with the monad
<eikke> yes
fantasticsid has joined #ocaml
<eikke> I've been trying quite some things the last 2 days, yet cant get it to work
<eikke> so maybe I'm missing something obvious, or it's not possible and I'd need to use some other approach
* mfp reads again
<eikke> the reason I'm trying this is: there's some library we got which should work both on top of normal IO calls as well as Lwt or something else, and we want several 'serialization' types
<eikke> Fake and Simple are the serialization implementations (FRONT)
<eikke> Store1 is an IO backend (for sync IO that's be +- the identity monad, for Lwt the obvious bind and return)
<eikke> and Rewrite should be able to rewrite from one serialization format into another
<mfp> in your example, are S1 and S2 supposed to be using the same monad?
<eikke> so Rewrite should work on F1(S) and F2(S) where the same S (and as such same 'a m, bind and return) are used
<mfp> k
<eikke> ST1 and ST2 are always the same (which is why I pass IO)
<eikke> ideally I could pass 2 values to a function defined in Rewrite, of type SD1(A) and SD2(A), but I guess that won't be possiuble at all
<eikke> I know things *can* work if the STORE type is twice the same, but I can't figure out how to encode this in the type system etc
<mfp> hmm am I missing something? S1:functor(ST1:STORE) -> FRONT with type 'a m = 'a ST1.m + S2:functor(ST2:STORE) -> FRONT with type 'a m = 'a ST2.m
<mfp> seems to work fine
<mfp> (well, the very last line doesn't type as there are some missing fields in the example)
<mfp> ok, this compiles:
Tobu has quit [Ping timeout: 272 seconds]
<mfp> oops gotta login to github, 1m
thomasga has quit [Ping timeout: 245 seconds]
ftrvxmtrx has quit [Quit: Leaving]
<eikke> mfp: this kinda rocks
<eikke> thanks a million, really
<mfp> eikke: btw., if you're functorizing over the concurrency monad, you can just call the module Lwt, provide 'a t, bind, return, fail and you can use lwt's syntax extension
<mfp> if you include backtrace_bind, backtrace_catch, backtrace_try_bind and backtrace_finalize (see lwt.mli for the signatures) you can even use raise_lwt
<eikke> thats the idea :)
<eikke> to 'abstract' exception handling as well
<eikke> although inside our pure core algorithms (well, pure... they use the serder backends) we dont want to use exceptions
<destrius> hi guys... i'm writing a map function for a complex tree-like structure, but the type of my map function gets returned as ('a -> 'a) -> 'a tree -> 'a tree, instead of ('a -> 'b) ... is there a good way to get the typechecker to tell me where i went wrong causing 'a = 'b?
<mfp> destrius: you can add an annotation like let map : (type a) (type b) -> (a -> b) -> a tree -> b tree = fun f t ->
<destrius> mfp: i annotated the types, specifying that the map function is ('a -> 'b) etc., but it still ends up giving me ('a -> 'a)
<mfp> I believe the type checker will complain if your code forces a = b an is thus less general
<destrius> the complicating factor is that it consists of a few mutually recursive functions
<mfp> destrius: yes, annotating that way will yield 'a = 'b, but (type a) (type b) .... is different
<destrius> ah as in specify a concrete type?
<mfp> and it's the way to get polymorphic recursion if you need it
<mfp> an "explicit polymorphic type"
ocp has joined #ocaml
<eikke> destrius: if you specify "'a -> 'b" the type checker is perfectly allowed to refine this to "'a -> 'a" since you never specified 'a and 'b should be different types
<destrius> ah, ok
<destrius> thanks, i'll try that!
<eikke> when using (type a) (type b) (a -> b) you specify they should possibly be different types
<mfp> actually it's an "explicit generic type", I was confusing it with the way to define polymorphic recursion, which is let rec foo : 'a1 ... 'an. ... = fun ...
ocp has quit [Remote host closed the connection]
ftrvxmtrx has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
ftrvxmtrx has joined #ocaml
mart has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
ftrvxmtrx has joined #ocaml
ulfdoz_ has joined #ocaml
ulfdoz has quit [Ping timeout: 252 seconds]
ulfdoz_ is now known as ulfdoz
destrius has quit [Quit: Leaving.]
datkin has joined #ocaml
ikaros has joined #ocaml
ikaros has quit [Quit: Ex-Chat]
emmanuelux has joined #ocaml
ftrvxmtrx has quit [Quit: Leaving]
iago has joined #ocaml
fantasticsid has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
_andre has joined #ocaml
Tianon has quit [Ping timeout: 260 seconds]
Tianon has joined #ocaml
Tianon has quit [Changing host]
Tianon has joined #ocaml
matthewt has quit [Ping timeout: 276 seconds]
rby has quit [Ping timeout: 245 seconds]
rby has joined #ocaml
skchrko has quit [Ping timeout: 246 seconds]
hto_ has quit [Read error: Connection reset by peer]
hto has joined #ocaml
skchrko has joined #ocaml
emmanuelux has quit [Read error: Connection reset by peer]
<hcarty> diml: Is it possible to check the state of a Lwt_mvar.t (empty/full) without blocking?
<hcarty> diml: Or do I need to use Lwt_stream or some other inter-thread communication technique in order to avoid blocking?
<diml> hcarty: no, the exported functions does not allow that
<diml> i can add a function to check if a mvar is empty if you need it
<diml> also note that you can always check if a thread is blocked with Lwt.state
smondet has joined #ocaml
agarwal1975 has joined #ocaml
agarwal1975 has quit [Client Quit]
ankit9 has quit [Quit: Leaving]
agarwal1975 has joined #ocaml
agarwal has joined #ocaml
agarwal has quit [Remote host closed the connection]
<hcarty> diml: Lwt.state may allow me to do what I need.
<hcarty> I have one thread which is listening on a zeromq socket for tasks to perform. When a task arrives it is put in an mvar to be picked up by another thread.
<hcarty> The other thread has its own list of task threads which it monitors. I need this thread to be able to check for a value in the mvar and continue to monitor the existing list of tasks.
<hcarty> s/tasks/task threads/
<diml> hcarty: how do you monitor your threads ? with Lwt.choose ?
<hcarty> diml: I'm trying to figure that part out too :-) I am planning to use nchoose_split so that I can separate the completed threads from the ongoing threads.
<hcarty> The number of threads (tasks) is not constant.
<diml> hcarty: maybe you can just put the Lwt_mvar.take in the choose too
<hcarty> diml: And wrap each thread in a variant? type result_t = Thread of thread_result_t | Task of task_result_t
<diml> hcarty: yes
<hcarty> diml: I think that will work well. Thank you for taking the time to answer my questions.
smondet has quit [Remote host closed the connection]
smondet has joined #ocaml
<Lor> Hm, is there a by-address (==-compatible) hash function in the standard library?
<thelema> Lor: this is a bad idea, as values can be relocated by GC
<Lor> Right, I guess I want something like StableNames in haskell.
<Lor> objects in ocaml actually do have a stable hash value for this very purpose.
<Lor> Anyway, in this case I'm interested in custom blocks, and to my understanding those cannot be moved by the gc.
Cyanure has quit [Remote host closed the connection]
mika1 has left #ocaml []
cago has quit [Quit: Leaving.]
Kakadu has quit [Quit: Page closed]
benozol has quit [Quit: Konversation terminated!]
<diml> Lor: they can be moved
<diml> for example int32 and int64 are custom blocks and they can be moved
<Lor> Ah, right. I confused them with pointers to outside the caml heap.
eikke has quit [Ping timeout: 260 seconds]
JuzorBNC is now known as deelazy
deelazy is now known as JuzorBNC
JuzorBNC is now known as Juzor
emmanuelux has joined #ocaml
ftrvxmtrx has joined #ocaml
djcoin has quit [Quit: WeeChat 0.3.2]
andreypopp has quit [Quit: Computer has gone to sleep.]
Tobu has joined #ocaml
Tobu has quit [Changing host]
Tobu has joined #ocaml
avsm has quit [Quit: Leaving.]
eikke has joined #ocaml
err404 has joined #ocaml
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
eikke has quit [Ping timeout: 252 seconds]
Zedrikov has joined #ocaml
silver has quit [Remote host closed the connection]
<hcarty> diml: Is it safe to use a ref for communication between threads? I have a few points where a checkable mvar would work, but the check fits most logically inline with other processing.
pippijn_ is now known as pippijn
<hcarty> diml: So without a Lwt_mvar.is_full or similar function I can't use an mvar and avoid blocking.
<hcarty> Or... I may be thinking about this in an un-Lwt-ish way. I could pass the mvar-checking thread along until it returns a value.
<pippijn> lwt is not going to preempt your threads
<pippijn> so it won't interrupt a memory (ref) write or read
<hcarty> pippijn: Thank you. That's what I expected/hoped.
Juzor is now known as JuzorBNC
noamsml_ is now known as noamsml
wieczyk has joined #ocaml
<wieczyk> Hi, could someone give me good paper/points about higher order polymorphism in programming languages? I am preparing seminar on my university about this. We have already lectures for system F, we are basing on Pierce's book.
<wieczyk> But for Fomega Pierce is only giving small intuitions and a lot of meta theory. I would like to tell also about some usage of Fomega, or some subset of Fomega, or sth like this.
Zedrikov is now known as crevee
<Lor> wieczyk, I'd suggest looking into haskell rather than ocaml
andreypopp has joined #ocaml
<Lor> haskell has direct type constructor polymorphism, in ocaml you have to use modules, so the relationship with Fomega is less obvious
<wieczyk> Hm, could you give me some points for this?
<wieczyk> Maybe some paper, I want only show motivation for Fomega before I tell about meta theory.
<Lor> Monads are the classic example in Haskell, but they are a bit complicated.
<Lor> Functors are simpler, but I can't think of a credible practical use case that would use functors alone.
avsm has joined #ocaml
andreypopp has quit [Quit: Computer has gone to sleep.]
andreypopp has joined #ocaml
jderque has joined #ocaml
_andre has quit [Quit: leaving]
avsm has quit [Quit: Leaving.]
albacker has joined #ocaml
albacker has quit [Changing host]
albacker has joined #ocaml
Snark has quit [Quit: Quitte]
avsm has joined #ocaml
agarwal1975 has quit [Quit: agarwal1975]
crevee has quit [Quit: Bye all, see you next time!]
andreypopp has quit [Quit: Computer has gone to sleep.]
andreypopp has joined #ocaml
djcoin has joined #ocaml
ASau` has joined #ocaml
Submarine has quit [Remote host closed the connection]
ASau has quit [Ping timeout: 244 seconds]
zcero has joined #ocaml
zcero has quit [Client Quit]
Tobu has quit [Ping timeout: 260 seconds]
jderque has quit [Quit: leaving]
tufisi has quit [Ping timeout: 246 seconds]
Tobu has joined #ocaml
andreypopp has quit [Quit: Computer has gone to sleep.]
skchrko has quit [Remote host closed the connection]
srcerer has quit [Ping timeout: 245 seconds]
err404 has quit [Remote host closed the connection]
srcerer has joined #ocaml
albacker has quit [Ping timeout: 276 seconds]
djcoin has quit [Quit: WeeChat 0.3.2]
Tobu has quit [Ping timeout: 260 seconds]
smondet has quit [Remote host closed the connection]
Tobu has joined #ocaml
<pippijn> it seems that ocaml likes to use exceptions for non-exceptional cases
<_habnabit> like what
avsm has quit [Quit: Leaving.]
<pippijn> or am I supposed to Hashtbl.mem before I Hashtbl.find?
<_habnabit> it's pretty easy to catch Not_found
<_habnabit> also I'd say that's definitely an exceptional case. what else could it return, without making it an 'a option?
<pippijn> it's not exceptional that a "find" routine does not find anything
<pippijn> that's pretty common
<_habnabit> so what should the return type be?
<hcarty> pippijn: If you use Batteries then you can have lots of find-and-friends return 'a option types instead of raising exceptions.
<pippijn> I'm not saying what things should be like
<pippijn> maybe 'a option
<hcarty> I think Core does the same thing out of the box, at the cost of any stdlib compatibility layer.
<_habnabit> pippijn, in the case of there being no value, you can't just invent a value of that type
<pippijn> I'm just saying that ocaml uses exceptions a lot for non-exceptional cases
<hcarty> pippijn: But 'a option makes the arguably usual case (find found something) more difficult to handle.
<_habnabit> pippijn, so find can't be 'a t -> key -> 'a _and_ not raise an exception generally; it's an important question
<_habnabit> that seems exceptional to me
<pippijn> hcarty: Option.map/Option.may
<hcarty> pippijn: 'exceptional' is subjective
<_habnabit> what do _you_ think is exceptional?
<hcarty> pippijn: But that propagates everywhere downstream
mjonsson has joined #ocaml
<hcarty> pippijn: Also, stdlib doesn't have an Option module. And it probably shouldn't, given the core team's focus.
<pippijn> hcarty: what's their focus?
<hcarty> pippijn: The compiler
<pippijn> good
<hcarty> Comprehensive libraries are up to the community to develop - which is a large part of why Batteries came to exist.
<pippijn> does the compiler depend on anything but stdlib?
<hcarty> No
<Lor> The way ocaml is implemented, using exceptions makes the "key present" case (which is usually more common) cheaper than if the found value were always wrapped in Some.
<pippijn> Lor: makes sense
<Lor> Also, for instance, End_of_file is rarely an "exceptional" situation, yet it is more convenient to signal it with an extension than by wrapping the return values of all read functions in an option.
<Lor> Arguably "exception" is too suggestive a name for the language feature, given its uses.
JuzorBNC is now known as Juzor
<pippijn> I just found BatOption depends on camomile
<pippijn> great..
<pippijn> I hope batteries 2 will come out soon so that's fixed
Juzor is now known as JuzorBNC
<hcarty> pippijn: All (most?) of Batteries 1.x does, due to the IO support
<pippijn> ah
<pippijn> it makes batteries completely unusable for js_of_ocaml
<hcarty> A lack of Camomile dependence in Batteriex 2 will be very welcome :-)
<pippijn> I've implemented what I needed in Ex* instead of Bat*
<Lor> It's unfortunate, though, that ocaml doesn't have the "exceptional syntax" syntax for handling exceptions.
<pippijn> so when it's fixed, I can replace Ex with Bat and delete some code
<pippijn> Lor: what's that?
<hcarty> pippijn: Can you test Batteries git against js_of_ocaml? If it doesn't work then that would be a good thing to know before release.
<Lor> Yes.
<pippijn> hcarty: yes, but not today
<pippijn> 22h flight makes me want to do nothing
<Lor> You can simulate it with e.g. "match (BatStd.wrap f x) with Ok a -> foo | Bad exn -> bar"
Tobu has quit [Ping timeout: 260 seconds]
JuzorBNC is now known as Juzor
<pippijn> Lor: I like this article
<pippijn> I read to page 7, I'll read the rest tomorrow
<pippijn> good night
<xenocons> nice
<xenocons> didn't know about andrew kennedy ty for link
<xenocons> sml.net !!!