flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml MOOC http://1149.fr/ocaml-mooc | OCaml 4.03.0 announced http://ocaml.org/releases/4.03.html | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
yunxing_ has joined #ocaml
Algebr` has quit [Ping timeout: 250 seconds]
yunxing_ has quit [Quit: Leaving...]
nojb__ has joined #ocaml
seangrove has joined #ocaml
nojb_ has quit [Ping timeout: 246 seconds]
fedruantine has joined #ocaml
seangrove has quit [Remote host closed the connection]
seangrove has joined #ocaml
nojb_ has joined #ocaml
<seangrove> I have a hashtbl I've made with (string, custom_type) key/values, and I'd like to generate json from it. custom_type has a [@@deriving yojson] annotation. Is there an automatic was to do this?
nojb__ has quit [Ping timeout: 244 seconds]
nojb__ has joined #ocaml
<tormen> Hmm. Is using output_string on the out_channel returned by ( Unix.out_channel_of_descr (Unix.openfile "foo" [Unix.O_APPEND] 0o640) ) thread-safe ? (like "all or nothing is written" and/or "2 calls to output_string cannot MIX -- they will be executed one after the other)
nojb_ has quit [Ping timeout: 244 seconds]
<tormen> I am wondering hence for the module UnixThread it is written that module Unix is thread-safe, but the function "output_string" is from the Pervasives module and NOT from the Unix module ...
<rgrinberg> seangrove: [@@deriving yojson] doesn't work on your hash table type?
<rgrinberg> if it doesn't, then a simple work around is to do [@@deriving yojson] on the equivalent assoc type and then convert that to a hash table
<seangrove> rgrinberg: `type channel_store = Tbl of (string, channel) Hashtbl.t [@@deriving yojson]` errs with `Error: Unbound value Hashtbl.to_yojson`
<rgrinberg> seangrove: thought so. So not all builtin types are supported yet.
<rgrinberg> I'd make a bug report for this. Although i'm sure whitequark is aware.
<seangrove> rgrinberg: What's the equivalent assoc type?
<rgrinberg> (string * channel) list
<rgrinberg> of course you can also just write a proper converter manually
<seangrove> rgrinberg: Was hoping to be able to avoid the intermediate allocation (just out of design, not doing anything critical right now)
<rgrinberg> seangrove: ok then write a converter manually
<seangrove> rgrinberg: Well, maybe I'll just fold over the hashmap and create the intermediate representation :)
<seangrove> Not sure what writing a manual converter with yojson might entail
<seangrove> rgrinberg: Is there a generic way to convert (a * b) list to json?
copy` has quit [Quit: Connection closed for inactivity]
<rgrinberg> seangrove: well, you need to know concrete types to actually write json
<rgrinberg> brb in 30 minutes
rgrinberg has quit [Ping timeout: 260 seconds]
<seangrove> How can I define a way to get Uri.t to serialize as a string in JSON that works everywhere?
<seangrove> type whatever = Uri.t [@@deriving yojson] obviously doesn't work, complaining about Uri.to_yojson doesn't exist
nojb_ has joined #ocaml
nojb__ has quit [Ping timeout: 244 seconds]
nojb__ has joined #ocaml
nojb_ has quit [Ping timeout: 246 seconds]
nojb_ has joined #ocaml
nojb__ has quit [Ping timeout: 246 seconds]
Algebr` has joined #ocaml
nojb__ has joined #ocaml
nojb_ has quit [Ping timeout: 246 seconds]
rgrinberg has joined #ocaml
<rgrinberg> seangrove: did you figure it out?
fedruantine has quit [Max SendQ exceeded]
FreeBirdLjj has joined #ocaml
<Enjolras> seangrove: if Uri.t is abstract, you need to derive on t at the point of defnition of t where it is not abstract
<Enjolras> and add to_yojson and from_yojson to the signature of Uri
<Enjolras> this aliasing can only work if the type is not abstract iirc
FreeBirdLjj has quit [Ping timeout: 244 seconds]
<Drup> Or you create from/to_yojson manually yourself, since it's just going to be a string.
ncthom91 has joined #ocaml
nojb_ has joined #ocaml
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
nojb__ has quit [Ping timeout: 246 seconds]
<seangrove> Ok, makes sense.
scarygelatin has joined #ocaml
<seangrove> Drup: [%html {|<div id="content">some content</div>|}] gives me an error: Uninterpreted extension 'html'
<seangrove> Hrm, let me update my oasis file, sorry
<seangrove> No, same thing
ncthom91 has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
sh0t has joined #ocaml
ncthom91 has joined #ocaml
<Drup> you loaded tyxml.ppx ?
<seangrove> tyxml-ppx -.0
<seangrove> -.-
Algebr` has quit [Ping timeout: 250 seconds]
nicholasf has joined #ocaml
Sorella has joined #ocaml
Algebr` has joined #ocaml
Algebr` has quit [Ping timeout: 250 seconds]
<seangrove> I have src/main.ml, I created a file src/sinsi_view.ml, how can I reference a function in src/sinsi_view.ml from main.ml?
<seangrove> Referencing `Sinsi_view.render_home_page` inside of main.ml says that "Unbound module: Sinsi_view"
nicholasf has quit [Remote host closed the connection]
<seangrove> Ok, just had to run make and then save in merlin again, picked it up
ncthom91 has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
Algebr` has joined #ocaml
<seangrove> I see, `Merlin failed with error: "Error: Error while running external preprocessor Command line: ppx_tyxml '/var/folders/dl/3vkt0hs5045_cvfcyzmjyr480000gn/T/camlppx012bf7' '/var/folders/dl/3vkt0hs5045_cvfcyzmjyr480000gn/T/camlppx13883d' 1>/dev/null 2>/dev/null`
<seangrove> No idea why, but at least that explains why merlin dies with it
Algebr` has quit [Ping timeout: 250 seconds]
sh0t has quit [Remote host closed the connection]
<Drup> hum, that's surprising, I tested with merlin and it was working okay
<seangrove> Will try it on a friend's computer
<seangrove> Drup: Do you have an example of creating a form with tyxml? We're struggling quite a bit here
<Drup> hum, just like with normal html ?
<seangrove> Drup: Nevermind, the ppx extension works on my friend's computer, and we were able to create a form via the ppx. Noooooo idea about how to do it with just the normal function interface though, we spent ~45 minutes trying to figure it out.
<seangrove> Would be nice to see more examples of elements in https://github.com/ocsigen/tyxml/blob/master/examples/basic_website/site_html.ml
<seangrove> (I know you're busy, just mentioning it, not saying you should fix it)
<Drup> Can you show your example ?
scarygelatin has quit [Quit: Leaving]
<seangrove> let%html feed_form = "<form><input type='text' placeholder='Add RSS feed' /></form>"
TarVanimelde has joined #ocaml
<seangrove> Never figured out how to get the non-ppx approach going
<Drup> form [ input ~a:[ a_input_type `Text ; a_placeholder "Add RSS feed" ] () ]
<Drup> What issues were you having ?
<Drup> It would be helpful for me to know what you attempted
<Drup> Note that with -dsource, you can see what is the equivalent ocaml code
<Drup> You can try it in utop for example, here is the output: https://bpaste.net/show/99d188e0f944
<Drup> more nicely formated: https://bpaste.net/show/896c15ed943a
<Drup> (it's a bit overly verbose, because it's very generic, but you should get the idea)
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
<rgrinberg> Drup: how come re's marks are in a set for a particular group?
<rgrinberg> Is there no well defined order?
<Drup> what would it mean to have an order ?
<rgrinberg> No idea. The order in which they are added?
<rgrinberg> Anyway, i guess there's no well defined order
<Drup> rgrinberg: what would the order give you ?
GeoffSK has joined #ocaml
<GeoffSK> how do i get access to the threads module from utop?
yunxing_ has joined #ocaml
yunxing_ has quit [Client Quit]
clog has quit [Ping timeout: 250 seconds]
clog has joined #ocaml
pierpa has quit [Ping timeout: 244 seconds]
p_nathan has joined #ocaml
vfoley has quit [Ping timeout: 264 seconds]
sdothum has quit [Quit: ZNC - 1.6.0 - http://znc.in]
nicholasf has joined #ocaml
yunxing_ has joined #ocaml
yunxing_ has quit [Client Quit]
tmtwd has joined #ocaml
<GeoffSK> How do i get the list of valid values for Graphics.set_font ? (Ubuntu)
FreeBirdLjj has quit [Ping timeout: 264 seconds]
p_nathan has quit [Ping timeout: 250 seconds]
FreeBirdLjj has joined #ocaml
nojb__ has joined #ocaml
nicholasf has quit [Remote host closed the connection]
nojb_ has quit [Ping timeout: 246 seconds]
d0nn1e has quit [Ping timeout: 244 seconds]
d0nn1e has joined #ocaml
A1977494 has joined #ocaml
erai has quit [Ping timeout: 260 seconds]
slash^ has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
nicholasf has joined #ocaml
MercurialAlchemi has joined #ocaml
<adrien> GeoffSK: the same as the ones shown by X
<adrien> GeoffSK: but you will never get something pretty with Graphics
<GeoffSK> adrien: Thanks. I found a link to X logical font description. But so far i haven't managed to create a valid format.
<GeoffSK> adrien: Bit at least i know where to look.
<adrien> GeoffSK: try xfontsel
<adrien> *iirc* that helps
<GeoffSK> adrien: That look useful. I am giving it a go. (sure is ugly)
<GeoffSK> adrien: Perfect thanks.
atbagautdinov has joined #ocaml
rgrinberg has quit [Ping timeout: 276 seconds]
nicholasf has quit [Ping timeout: 244 seconds]
nicholasf has joined #ocaml
seangrove has quit [Ping timeout: 276 seconds]
nicholasf has quit [Remote host closed the connection]
tani has joined #ocaml
tane has joined #ocaml
nicholasf has joined #ocaml
tani has quit [Quit: Verlassend]
Algebr` has joined #ocaml
nicholasf has quit [Ping timeout: 250 seconds]
Simn has joined #ocaml
tmtwd has quit [Ping timeout: 240 seconds]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
Sorella has quit [Quit: Connection closed for inactivity]
seangrove has joined #ocaml
seangrove has quit [Ping timeout: 272 seconds]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
nicholasf has joined #ocaml
fluter has quit [Ping timeout: 250 seconds]
Algebr` has quit [Ping timeout: 250 seconds]
fluter has joined #ocaml
TarVanimelde has quit [Quit: Senpai noticed me, but he did not care.]
shinnya has joined #ocaml
seangrove has joined #ocaml
GeoffSK has quit [Quit: Thanks, i am leaving]
m4chine has joined #ocaml
<m4chine> any OCaml people around?
seangrove has quit [Ping timeout: 250 seconds]
<m4chine> I am no expert in functional, just learning, and I am curious about one thing
<m4chine> if we use nested let ... in ... doesnt it make it equivalent to sequential programming?
<m4chine> I mean, can the programm still be purely functional if we use let ... in ... to enforce order between operations ?
<lyxia> if you use only pure functions there's no meaning to the order of operations
<def`> And if you don't... it is not purely functional.
<def`> But it is not bad to not be purely functional, your program should gather input and report an awser at some point :)
A1977494 has quit [Quit: Leaving.]
<m4chine> hmm using functions order of operations can be defined by calling functions in given order, like instead of executing A, B, C sequentially, A() can call B() which calls C()
<m4chine> in such case if let ... in ... is function itself it has sequential behavior
<m4chine> which is why I asked myself if it still is purely functional or not
<_y> even in a purely functional style you need to evaluate things at some point, so you have an evaluation order
<_y> the point of being purely functional is not about not computing stuff one after the other, it is about not performing side effects
<m4chine> I see, I made sure my functions do not cause side effects and also do not depend on anything else then what has been given in arguments
<m4chine> (I am switching carrieers to functional, applied for job and made them little demo but had some theoretical doubts, thanks for clarifying)
m4chine has quit [Read error: Connection reset by peer]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
seangrove has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
leyyin has joined #ocaml
larhat has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
StrykerKKD has joined #ocaml
FreeBirdLjj has joined #ocaml
hiddenlotus has joined #ocaml
malc_ has joined #ocaml
hiddenlotus has quit [Remote host closed the connection]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
darkf has quit [Ping timeout: 250 seconds]
kolko has joined #ocaml
m4chine has joined #ocaml
m4chine has quit [Ping timeout: 244 seconds]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
A1977494 has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
seangrove has quit [Ping timeout: 260 seconds]
seangrove has joined #ocaml
A1977494 has quit [Quit: Leaving.]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
seangrove has quit [Ping timeout: 252 seconds]
sdothum has joined #ocaml
AlexRussia has joined #ocaml
<pyon> When I define a class type, the same identifier can also be used as an object type, right?
AlexRussia has quit [Ping timeout: 260 seconds]
<Drup> pyon: yes
<pyon> Ah, that's very convenient!
<pyon> Especially since the syntax for object types isn't so convenient. :-|
<def`> I am curious to know what you mean by that?!
seangrove has joined #ocaml
seangrove has quit [Ping timeout: 252 seconds]
m4chine has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
m4chine has quit [Ping timeout: 264 seconds]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 244 seconds]
m4chine has joined #ocaml
m4chine has quit [Ping timeout: 258 seconds]
AlexRussia has joined #ocaml
m4chine has joined #ocaml
stomp has quit [Ping timeout: 244 seconds]
stomp has joined #ocaml
danieli has quit [Ping timeout: 246 seconds]
danieli has joined #ocaml
seangrove has joined #ocaml
seangrove has quit [Ping timeout: 246 seconds]
Simn has quit [Ping timeout: 264 seconds]
sh0t has joined #ocaml
Sorella has joined #ocaml
seangrove has joined #ocaml
rgrinberg has joined #ocaml
rgrinberg has quit [Client Quit]
rgrinberg has joined #ocaml
AlexRussia has quit [Ping timeout: 250 seconds]
p_nathan has joined #ocaml
AlexRussia has joined #ocaml
vfoley has joined #ocaml
atbagautdinov has quit [Remote host closed the connection]
sh0t has quit [Ping timeout: 250 seconds]
sh0t has joined #ocaml
kolko has quit [Ping timeout: 260 seconds]
<hannes> def`: when I C-c C-x using merlin, it does not always go to the next error location (but sometimes another C-c C-x is needed, looks like the first only runs the checker)... is that intentional / has been observed by others?
leyyin has left #ocaml ["So Long, and Thanks for All the Fish"]
seangrove has quit [Ping timeout: 252 seconds]
m4chine has quit [Quit: Lost terminal]
seangrove has joined #ocaml
rgrinberg has quit [Ping timeout: 250 seconds]
lusory has joined #ocaml
nicholasf has quit [Remote host closed the connection]
nicholasf has joined #ocaml
nicholasf has quit [Remote host closed the connection]
<companion_cube> be sure you Lwt.join all the relevant threads in lwt_main.run
<companion_cube> awww
AlexRussia has quit [Ping timeout: 250 seconds]
nicholasf has joined #ocaml
yunxing_ has joined #ocaml
seangrove has quit [Ping timeout: 252 seconds]
yunxing__ has joined #ocaml
yunxing_ has quit [Ping timeout: 250 seconds]
fedruantine has joined #ocaml
TheLemonMan has joined #ocaml
nicholasf has quit [Ping timeout: 252 seconds]
nicholasf has joined #ocaml
rgrinberg has joined #ocaml
nichola__ has joined #ocaml
tmtwd has joined #ocaml
kolko has joined #ocaml
Simn has joined #ocaml
nicholasf has quit [Ping timeout: 264 seconds]
seangrove has joined #ocaml
yunxing_ has joined #ocaml
yunxing__ has quit [Read error: Connection reset by peer]
seangrove has quit [Ping timeout: 252 seconds]
Sorella has quit [Quit: Connection closed for inactivity]
nichola__ has quit [Remote host closed the connection]
nicholasf has joined #ocaml
tormen has quit [Ping timeout: 272 seconds]
<rgrinberg> Drup: I'm adding a pp to Re.Group but I'm not sure what should I output. Should I just dump the raw record or should I go for something more civilized like the individuals + their positions only.
ygrek_ has joined #ocaml
ansiwen has quit [Quit: No Ping reply in 180 seconds.]
ansiwen has joined #ocaml
tormen has joined #ocaml
<Drup> I'm not sure
<companion_cube> who would the printer be for?
troydm has joined #ocaml
<rgrinberg> companion_cube: right now I just need something to debug effectively
<rgrinberg> Drup: ok then I will just do whatever's convenient for me now and we can change it later if necessary.
<rgrinberg> We don't offer backwards compat. on printer output anyway
<companion_cube> substring + position, I'd say
pierpa has joined #ocaml
<rgrinberg> companion_cube: OK, that is what's useful to me anyway. Should I special caseGroup.get g 0 with its own label or something?
<rgrinberg> Also, the what about the group index?
bobry has joined #ocaml
<companion_cube> I'd go for an array-like presentation anyway
<companion_cube> ["abcd", "ab", "d"] for "(ab)c(d)" matching some string
<rgrinberg> companion_cube: makes sense. there's only at most 9 groups anyway
<rgrinberg> so you can easily eyeball it
<companion_cube> maybe [0:"abcd", 1:"ab", 2:"d"] for quick indexing
<rgrinberg> Can I use Array.init in 4.00 compatible code?
tane has quit [Quit: Leaving]
<companion_cube> I think so
<companion_cube> it's been there for ever
<profan> companion_cube: thanks for the containers lib btw, it's pretty neat
<companion_cube> oh, thanks
tmtwd has quit [Ping timeout: 240 seconds]
<MercurialAlchemi> containers is the awesome
<rgrinberg> \o/
<MercurialAlchemi> (though I think I like gen better, because it's so small)
iZsh_ has quit [Quit: ZNC - http://znc.in]
iZsh has joined #ocaml
<companion_cube> heh, they're made to interact anyway :)
<MercurialAlchemi> they're also pretty much no-dep libs
<companion_cube> (except base-string, result, etc., yeah)
nicholasf has quit [Remote host closed the connection]
<zozozo> well, compatibility packages do not really count I think
slash^ has quit [Read error: Connection reset by peer]
AlexRussia has joined #ocaml
benwbooth has quit [Ping timeout: 252 seconds]
modlfo has joined #ocaml
yunxing_ has quit [Remote host closed the connection]
<rgrinberg> Drup: companion_cube check this out:
<rgrinberg> # Group.all (exec (Re.compile (alt [group @@ char '{'; group @@ char '"'])) "{");;
yunxing_ has joined #ocaml
<rgrinberg> (you will need open Re as well)
<rgrinberg> This gives: bytes array = [|"{"; "{"; ""|]
<rgrinberg> What gives?
<rgrinberg> Where does that empty group come from
<companion_cube> did you mean to close with "}" ?
<Drup> well, it's the other group which never matches anything, hence it's empty
<Drup> that's the normal behavior for groups
Simn has quit [Ping timeout: 264 seconds]
<rgrinberg> Oh. I thought if the group doesn't match then it's not included.
kolko has quit [Quit: ZNC - http://znc.in]
<Drup> all the groups are always included
yunxing_ has quit [Ping timeout: 250 seconds]
<rgrinberg> ok thanks for clarfiying.
Sorella has joined #ocaml
AlexRussia has quit [Ping timeout: 250 seconds]
Simn has joined #ocaml
Kakadu has joined #ocaml
Algebr` has joined #ocaml
unbalancedparen has joined #ocaml
<MercurialAlchemi> does an UnexpectedProcessState raise any bell?
<MercurialAlchemi> (an exception)
<companion_cube> not to me
<MercurialAlchemi> ah, never mind
<MercurialAlchemi> it's one of mine
<companion_cube> :D
AlexRussia has joined #ocaml
<Algebr`> if you do a caml_alloc_custom of a c++ object, sizeof(That_object) ought to be correct right?
<mrvn> it's a start
<Algebr`> mrvn: share some of your insights?
<adrien> sizeof works on the type of its parameter...
<Algebr`> mrvn: looking at your qt5 bindings
MercurialAlchemi has quit [Ping timeout: 264 seconds]
<mrvn> Algebr`: you still have to call the constructor and destructor at the end
<Algebr`> ~Foo won't be called for me?
<mrvn> how should it? The object never gets freed, only the ocaml block
<mrvn> As far as the compiler knows you have just a random block of memory.
<Algebr`> I see, well I call it in finalize
<mrvn> are you calling placement new too?
darkf has joined #ocaml
<Algebr`> oops, no, where would I do it.
<mrvn> after the alloc
<Algebr`> short example somewhere?
darkf_ has joined #ocaml
<Algebr`> ah, connection_stubs
<mrvn> new(Data_custom_val(v))That_object()
darkf has quit [Client Quit]
darkf_ is now known as darkf
nicholasf has joined #ocaml
<Algebr`> hmm, c++ might be too much of a hassle
<mrvn> other people just put a pointer to That_object into the custom block
<rgrinberg> How do I enable a particular warning number with ocamlbuild?
<companion_cube> -warn -w+42
<companion_cube> or warn(+42) in the _tags file
fleaswallow has joined #ocaml
<rgrinberg> And if I'd like to make them fatal?
AlexRussia has quit [Ping timeout: 244 seconds]
fleaswallow has quit [Quit: Leaving]
fleaswallow has joined #ocaml
<companion_cube> hmmm just do as on the command line, I guess
<companion_cube> warn(@42)
<Algebr`> damnit, no way to pass strings somehow unboxed
<Algebr`> In the manual's interfacing with C section about noalloc: there this: ...However this is not needed if we know that the C function doesn’t allocate and doesn’t raise exceptions
<Algebr`> Does that mean OCaml based allocations or any allocations, including those of C heap
adelbertc has joined #ocaml
tmtwd has joined #ocaml
malc_ has quit [Quit: ERC (IRC client for Emacs 25.0.50.2)]
benwbooth has joined #ocaml
rgrinberg has quit [Ping timeout: 276 seconds]
AlexRussia has joined #ocaml
ygrek_ has quit [Ping timeout: 244 seconds]
modlfo has quit [Quit: Leaving]
d0nn1e has quit [Ping timeout: 260 seconds]
d0nn1e has joined #ocaml
tmtwd has quit [Ping timeout: 276 seconds]
Algebr` has quit [Ping timeout: 250 seconds]
Simn has quit [Quit: Leaving]
TheLemonMan has quit [Remote host closed the connection]
AlexRussia has quit [Ping timeout: 258 seconds]
rgrinberg has joined #ocaml
Algebr` has joined #ocaml
<struk|desk> When one registers a callback via #include <caml/callback.h> api, what are the concurrency semantics? Is the thread essentially the thread directly from the native layer? How is the ocaml GC synchronized under these circumstances? Can I safely mutate ocaml data structures in the callback thread, or do I need to adopt some strategy to do so safely? (eg mutexs, concurrent data structures, async or lwt, queues, etc.)
<mrvn> struk|desk: you have to hold the runtime lock to callback
<struk|desk> mrvn: "you" == ocaml run time ensures this?
<mrvn> no, you the programmer
<Algebr`> proper way to choose the c compiler in oasis? Thought NativeOpt: -cc clang would work but not
<mrvn> ocaml can't because you would be accessing the closure and argument variables without lock just to call callback() and then it's already too late.
<mrvn> NativeOpt: -cc g++
<mrvn> ByteOpt: -cc g++
<mrvn> on ARM it's a lot simpler to write code that doesn't use a stack at all.
<mrvn> ups, ewin
<Algebr`> mrvn: yea, doing that
<Algebr`> but it still isn't inserting those args.
<Algebr`> grr, I don't want it to use ocamlc at all, just ocamlopt. Doing CompiledObject:best or native still makes oasis use ocamc
<Algebr`> ocamlc
<mrvn> it always does for mli files
<mrvn> cmi
<Algebr`> but I don't have any mlis
<mrvn> then it generates the cmi files from the ml files
<mrvn> which is probably what you are seeing
<Algebr`> oasis isn't passing anything from ByteOpt, even trying junk
<Algebr`> are oasis variables overrideable
<struk|desk> mrvn: ok, thanks
<struk|desk> mrvn: so even if I used lwt or async to wrap the callback to their respective monad types, I still have to acquire the runtime lock?
vfoley has quit [Ping timeout: 276 seconds]
StrykerKKD has quit [Remote host closed the connection]
struk|desk has quit [Remote host closed the connection]
<mrvn> stomp: only one ocaml thread at a time
struk|desk has joined #ocaml
Kakadu has quit [Remote host closed the connection]
<struk|desk> mrvn: assuming stomp was supposed to be me...didn't follow your last statement, about only 1 thread at a time. can you clarify?
<Algebr`> I think he means to say that only 1 ocaml thread is doing work at any given time
<struk|desk> yeah I know that.I was asking if there is a benefit to using async or lwt here, in that I can let it's scheduler with the concurrency issues introduced by the native callback, without explicitly acquiring a runtime lock in my code.
<struk|desk> *scheduler deal with
<mrvn> using async or lwt has nothing to do with running multiple threads
<struk|desk> is that a no, then? are you also essentially claiming the scheduler's of lwt/async don't manage the runtime lock?
Algebr` has quit [Ping timeout: 250 seconds]
<mrvn> I'm saying to use async or lwt if you find it usefull., it won't change anything on your callback at all.
<struk|desk> ok so it's probably not terribly useful..hmm
seangrove has joined #ocaml
madroach has quit [Ping timeout: 244 seconds]
madroach has joined #ocaml
dwwoelfel has joined #ocaml
unbalancedparen has quit [Ping timeout: 240 seconds]
Algebr` has joined #ocaml
unbalancedparen has joined #ocaml
Algebr` has quit [Remote host closed the connection]
Algebr` has joined #ocaml
<Algebr`> def`: what is the merlin_extend usage? is that like a hook to merlin
unbalancedparen has quit [Ping timeout: 264 seconds]
<Algebr`> Really frustrated with oasis not letting me pick clang over gcc as a c compiler
<Algebr`> did -cc clang in both NativeOpt and ByteOpt, still no dice.
<Algebr`> changed gcc to change in the setup.data, still now
<Algebr`> no
unbalancedparen has joined #ocaml