adrien 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.02.3 announced http://ocaml.org/releases/4.02.html | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
Kakadu has quit [Remote host closed the connection]
rpg has quit [Quit: rpg]
foolishmonkey has quit [Quit: Leaving]
ril is now known as ril[away]
madroach has quit [Ping timeout: 248 seconds]
yegods has joined #ocaml
madroach has joined #ocaml
yegods has quit [Ping timeout: 272 seconds]
ril[away] is now known as ril
_berke_ has joined #ocaml
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
<infinity0> is there a common pattern to build a (string -> module) mapping?
<infinity0> i was going to do something like module X = (etc);; let all = ("X",X)::all;; etc but wondered if there is a better way
<Algebr2> like taking a string and giving back a module? Have all the simplier solutions not been good enough?
sillyotter has joined #ocaml
aantron has quit [Remote host closed the connection]
darkf_ has joined #ocaml
sillyotter has quit [Client Quit]
darkf has quit [Ping timeout: 250 seconds]
sillyotter has joined #ocaml
darkf_ is now known as darkf
ygrek has quit [Remote host closed the connection]
sillyotter has quit [Quit: leaving]
ygrek has joined #ocaml
aantron has joined #ocaml
seangrove has joined #ocaml
dksong has joined #ocaml
dksong has quit [Ping timeout: 260 seconds]
Emmanuel` has joined #ocaml
Emmanuel` has quit [Client Quit]
Emmanuel` has joined #ocaml
<Emmanuel`> hello
<aantron> hi :)
shinnya has quit [Ping timeout: 272 seconds]
<seangrove> I'm trying to parse e.g.: `{{name}} likes {{color}}` - I think I want everything outside of {{}} and {%%} to be ignored and just parsed as a single long string, but I'm not sure how to express that in the parser.mly
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
<aantron> seangrove: what is your tokenizer doing?
<aantron> it sounds like you should be able to do most or all of this with a regular expression
FreeBirdLjj has joined #ocaml
<seangrove> aantron: A tokenizer would be part of the parser.mly rather than the lexer.mll, right?
<aantron> it is also known as the lexer, so lexer.mll
<seangrove> aantron: Sorry for the questions, I certainly feel very dumb in this area!
<seangrove> But that makes sense, I'll poke at it for a bit
<aantron> np, all who know this learned at some point
<aantron> ok :)
crass_ has quit [Ping timeout: 250 seconds]
malc_ has joined #ocaml
ril has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<infinity0> Algebr2: i dunno what would be "simpler", to let the user select a different behaviour from the command-line
<infinity0> the selection does have to be on the module-level not the function-level / config-value-level
<SomeDamnBody> how do I load things from the opam folder from within utop?
<Drup> like any other libraries, #require
<SomeDamnBody> like, say I have some library built and I'd like to load it in the utop. It has some prerequisite satisfied as a library
<SomeDamnBody> oh ok
<SomeDamnBody> I was using #load
<Drup> Except if you are not using ocamlfind, but you deserve the pain, and you should use ocamlfind :3
<aantron> infinity0: a "map" (e.g. associative list, as you have) from strings to module values is simple enough. though, do you need modules? if they don't carry any types, you may be able to get away with records
lolisa has joined #ocaml
<infinity0> they do carry types unfortunately but thanks i'll remember that option for other stuff in the future
<infinity0> i have a bunch of modules built from each other and the type occurs at the very bottom of the dependency graph, so i'm guessing it'll be hard to turn any of these modules into records
<Emmanuel`> is there anything I should know about package? I installed ounit using opam, yet if I corebuild -package ounit (or any variation thereof) it claims it can't find the package
<aantron> Emannuel`: try -package oUnit
jeffmo has joined #ocaml
<Emmanuel`> ... yeah it works
jeffmo has quit [Client Quit]
<aantron> the opam package name and the ocamlfind package names are two different things, but have the same value for most packages. but ounit decided (by accident?) to set different names
<Emmanuel`> and I couldn't find anything relevant about compiling with oUnit
<Emmanuel`> (and the examples on the website are dead)
<Emmanuel`> thanks!
<aantron> what do you mean relevant? this should tell you how to use ounit http://ounit.forge.ocamlcore.org/api-ounit/index.html
<aantron> as for compiling, you just did so by supplying -package oUnit
<Emmanuel`> yes, I meant I searched how to get it to compile, with no success
<aantron> ah.
<Emmanuel`> (using oUnit was ok, I looked at the video, it's pretty straightforward)
darkf_ has joined #ocaml
<Emmanuel`> I guess my question was /was there a way for me to figure it out without asking here/
<aantron> you could do "ocamlfind list"
darkf has quit [Ping timeout: 260 seconds]
<Emmanuel`> yes!
<Emmanuel`> nice
darkf_ is now known as darkf
<aantron> that will tell you the ocamlfind names of all the packages installed, according to ocamlfind. ocamlfind is what you care about when using -package or #require
<aantron> each opam package contains some number of ocamlfind packages, some of which are subpackages of each other
<Emmanuel`> this is great, precisely what I needed. Thanks a ton
<aantron> enjoy :)
dksong has joined #ocaml
dksong has quit [Ping timeout: 240 seconds]
<seangrove> So I'm having trouble with the logic of how to parse everything outside of {{}} and {%%} as a string - https://gist.github.com/sgrove/ea6f7f305c7547b6231f
<seangrove> Ah, might have an idea, one moment
<aantron> as an initial suggestion, i would say you only a few rules (i forgot how and what to escape, so this is approximate): {{([^}])|}[^}]*}}, and an analogous rule for {%%}, everything else you match with .*
<aantron> and i forgot if there is special handling for newlines, i.e. if they are included in .
<aantron> i think if you are parsing everything as strings, you could use module Str
<seangrove> aantron: Stuff inside of {{ }} won't be parsed as strings
<aantron> thats right, i meant the other text
<Drup> And regardless, don't use Str.
<seangrove> Ok, just making sure
<aantron> Drup, its bad, but it has the advantage of being in the standard library
<Drup> re is standalone pure ocaml portable to basically everywhere, there is no reason not to use it
<Drup> seangrove: why is read_text not in read ?
<SomeDamnBody> Drup, I found the issue with the interface problem. When I did make clean earlier, a conflict with the Makefile caused the _build folder not to be dropped. So then opam pin picked it up again
<Drup> SomeDamnBody: ah, I see, and combined with path pinning ...
<Drup> So it all works now ?
<seangrove> aantron: Bah, I'm just fouling things up. Could use a more concrete pointer re: the rules if you don't mind.
<aantron> seangrove: do you have some experience with regular expressions?
<seangrove> aantron: Yeah, Regular expressions are certainly fine. How they work with menhir is another story :)
<aantron> given only what you said about trying to match {{...}} and {%...%}, i dont think you need menhir at all
<aantron> you can use ocamllex only for that, or re only
<aantron> as long as you arent dealing with things like nested {{ }}
<aantron> and as long as the surrounding grammar cant escape them in some complex way
<SomeDamnBody> So I can see with ocamlobjinfo that a module is being exported. And I have that sub library that contains the module I need specified as a dependency in my module
<seangrove> aantron: Heh, ok, so a more full example: `Today is {{ site.date | toDayOfWeek }}, {% if post.is_private %} you must log in to read this {% endif %}
<SomeDamnBody> so it appears that that library is exporting what I need
<aantron> is there any way for {{ to appear in the surrounding text, and not be counted as the beginning of a replacement location?
<seangrove> aantron: Trying to build a library for http://liquidmarkup.org/
<SomeDamnBody> But then when I go to compile my code, which uses that module exported by the library which I have as a dependency, it gives me unbound module
<Drup> seangrove: don't bother, use a parser, it's going to be both simpler and easier to maintain
<aantron> is there any way for }} to appear inside a replacement expression, and not terminate it?
<Drup> Using regex is cute, but it's not faster, and it's a pile of spagetti waiting to happen
<aantron> Drup: ocamllex uses regex, the only question is the complexity of your productions
<seangrove> aantron: I see what you mean now - I'd like to learn Menhir anyway down the road :)
<Drup> aantron: sure, to tokenize, not to parse
<aantron> if they are a simple straight line of alternating opaque strings and replacement locations, then menhir is a bit of overkill
Emmanuel` has quit [Quit: Konversation terminated!]
<Drup> SomeDamnBody: can't answer without full details
Emmanuel` has joined #ocaml
badon has quit [Disconnected by services]
badon_ has joined #ocaml
<aantron> of course if you need any kind of nontrivial analysis of either the surrounding text or the replacement expressions, then you should use menhir
<seangrove> I should probably think about the type the lexer should return
badon_ is now known as badon
<aantron> you might also benefit from separating the text and expressions, treating both as opaque, in a first pass, and then in a second pass parsing the expressions using ocamllex+menhir or whatever you are using
<aantron> but whether thats possible depends on whether {{ and }} can be escaped and how
<seangrove> aantron: I see - easily strip out all the non-{{}} stuff, and then process everything inside and splice it back in?
<Drup> aantron: I'm not sure why you would do that
<Drup> you are making all this much more complicated than it should be x)
<aantron> Drup: if you have a parser for the expressions lying around :)
<Drup> But he doesn't, he's writing it
<Drup> seangrove: your token type is right
<Drup> keep it
Emmanuel` has quit [Client Quit]
Emmanuel` has joined #ocaml
<Drup> your tokenizer is not right, you should have only one rule for read + read_text, and one read_string
<Drup> your string handling is okay
<Drup> your parser is not very useful for now, since you can read only one value, which I'm not sure it's very useful, but I guess you'll extend it later
Emmanuel` has quit [Client Quit]
<infinity0> aantron: so, thinking about what you said about records...
<seangrove> Drup: So all three rules should be combined into one?
<infinity0> could you or anyone else enlighten me on the advantage of (a) "module XXX = struct type t [..function defs in terms of t..] end" over (b) "type 'a xxx = { [..] };; let (xxx_instance:t xxx) = [..function defs in terms of t..];;"
<Drup> seangrove: just the first wo, for now
<infinity0> e.g. why are modules even necessary, why don't we just do everything in terms of polymorphic record types (and instantiate the types when needed)
<Drup> seangrove: you should real ocamllex's manual in more details, you could simplify your things
<Drup> (In particular, you can write strings like "{{" directly ...)
Emmanuel` has joined #ocaml
<aantron> infinity0: i believe modules give you the advantage of abstract types
<aantron> in (a) the type could be known to the implementation, thus the functions could deconstruct values of type t
<aantron> whereas in (b) the functions cannot deconstruct values of "type" 'a
<aantron> ultimately though both products and modules are (roughly) product types with some quantifiers on them, so a lot of their use cases will be similar
<Drup> type system wise, modules are much more powerful, though
<seangrove> Drup: But if I combine read + read_text, read_text is expecting an accumulation buffer to read all of the text, so I would have to change the signature of read, right?
<Drup> (You basically get HKT with modules)
<aantron> both records*
<Drup> (And some form of dependent functions)
<Drup> seangrove: you have to rewrite read_text differently
lolisa has quit [Quit: KVIrc 4.9.1 Aria http://www.kvirc.net/]
lolisa has joined #ocaml
<Drup> Something like "source_text { TEXT (Lexing.lexeme lexbuf) }" for example
<seangrove> Drup: Will that create a TEXT entry for every char then?
<Drup> well no, look at your regexp for source_text
<seangrove> Ahhh, ok, that makes sense.
<Emmanuel`> is there anything special to do to declare function signature with default argument in the .mli file?
<Emmanuel`> I have something that compiles, yet when I use my function (omissing the optional argument) I get a partial application instead of the results
<Drup> Emmanuel: ?foo:string
<aantron> Emmanuel`: is the optional argument last in the signature?
<Emmanuel`> it's first
<Emmanuel`> both in the .ml and the .mli
<Drup> what's the complete type ?
<aantron> can you show the signature and the call?
<Emmanuel`> sure
Emmanuel` has quit [Quit: Konversation terminated!]
<infinity0> hm... i thought you'd be able to deconstruct t on the RHS of (xxx_instance:t xxx) = {}
Emmanuel` has joined #ocaml
<Emmanuel`> let then' ?(on_failure=raise_on_failure) ~(promise: 'a t) ~(on_success: ('a -> 'b)) : 'b t = (* .ml *)
<Emmanuel`> wait, let me repost my connection is horrible
<Emmanuel`> val then' : ?on_failure:(exn -> 'b) -> promise:('a t) -> on_success: ('a -> 'b) -> 'b t (* .mli *)
<Emmanuel`> let then' ?(on_failure=raise_on_failure) ~(promise: 'a t) ~(on_success: ('a -> 'b)) : 'b t = (* .ml *)
<Emmanuel`> function call :
<Emmanuel`> let _ = Promise.then' ~on_success:(fun () -> "Hello") ~promise: promise in ...
<Drup> oh, promises :p
<Drup> You need at least one non-labeled argument
<Emmanuel`> (it's a toy project, trying to get familiar with OCaml by re-implementing a structure I was familiar with in JS)
<Emmanuel`> (it's proving to be quite the headache hahaha)
<Drup> It's not the easiest to implement correctly, yes
<aantron> you need at least one non-labeled argument after your optional argument*
<Drup> +thing
<Drup> ^ what aantron said
<Emmanuel`> yup
<Emmanuel`> I think it's working, I have another error message :)
<infinity0> i guess if you had "sig type 'a t [..] end" then there is no way you can have the equivalent functionality with a record - because you can instantiate a module whilst keeping 'a abstract, but with a record value you need to instantiate all the type parameters
<infinity0> but i can't think of a case where you can't replace "sig type t [..] end" with a record, since to instantiate a module with that signature you also have to instantiate type t
<aantron> infinity0: signatures would correspond to record types in this discussion. ocaml record types cannot be wrapped in existential quantifiers ("abstract types"), so they simply do not support what signatures support
<aantron> in order to "instantiate" a signature, you must provide a type and values. but to instantiate a record, you provide the values
<aantron> a record type*
<aantron> s/a type/types/
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
<aantron> i think part of the issue is that under type erasure, the extra "features" of signatures over record types are "lost", when you consider both "operationally." the point in that case is that signatures help you to decompose your program better than record types do, in some situations
<def`> +1
<def`> operationnally, ~everything ends up being an array of values
Emmanuel` has quit [Client Quit]
Emmanuel` has joined #ocaml
<aantron> to make another nebulous statement, signatures give you more type-level programming than record types do, e.g. getting the compiler to yell at you in situations you couldnt achieve with record types
<aantron> one concrete example of such type-level programming is using abstract types. the fact that ultimately each usage of abstract types can be translated away, is a piece of the argument that compilation with type erasure will go through. it doesnt meant that we dont want to use abstract types to improve our ability to reason about programs
struk|desk is now known as struk|desk|away
bobthenameless has joined #ocaml
ygrek has quit [Ping timeout: 265 seconds]
igoroliveira has quit [Quit: Connection closed for inactivity]
yegods has joined #ocaml
<seangrove> Is there a function to tell if an assoc list has a key?
<seangrove> Bah, mem_assoc
yegods has quit [Ping timeout: 264 seconds]
johnelse has quit [Ping timeout: 260 seconds]
struk|desk|away is now known as struk|desk
johnelse has joined #ocaml
johnelse is now known as Guest89484
darkf has quit [Ping timeout: 250 seconds]
darkf has joined #ocaml
darkf_ has joined #ocaml
darkf has quit [Ping timeout: 260 seconds]
Fleurety has quit [Remote host closed the connection]
Fleurety_ has joined #ocaml
darkf_ has quit [Ping timeout: 260 seconds]
Fleurety_ has quit [Excess Flood]
darkf has joined #ocaml
malc_ has quit [Ping timeout: 252 seconds]
Fleurety has joined #ocaml
struk|desk is now known as struk|desk|away
Fleurety has quit [Max SendQ exceeded]
<seangrove> Ok, so I have a liquid subdirectory with a few files - how do I refer to the files (or modules) in that subdir from the main project in the parent dir?
kushal has joined #ocaml
Fleurety has joined #ocaml
_2can has quit [Ping timeout: 256 seconds]
_2can has joined #ocaml
seangrove has quit [Ping timeout: 272 seconds]
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
_berke_ has quit [Quit: bed o'clock]
<Emmanuel`> weeeeeee, I have a test suite that works on asynchronous/deferred functions
<Emmanuel`> only took me all day \o/
Simn has joined #ocaml
yegods has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
yegods has quit [Ping timeout: 265 seconds]
MercurialAlchemi has joined #ocaml
openplatypus has joined #ocaml
seangrove has joined #ocaml
<seangrove> What am I missing here? https://gist.github.com/sgrove/404540fe89771d4b4369
<seangrove> Clearly menhir is installed, but mirage configure doesn't seem to puick it up
MercurialAlchemi has quit [Ping timeout: 276 seconds]
<seangrove> I probably just had it listed in under libraries instead of packages
<Algebr2> odd cause it says: [NOTE] Package menhir is already installed (current version is 20151112).
pierpa has quit [Ping timeout: 276 seconds]
freehck has joined #ocaml
MercurialAlchemi has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
Emmanuel` has quit [Client Quit]
Emmanuel` has joined #ocaml
badon has quit [Ping timeout: 240 seconds]
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
SomeDamnBody has quit [Ping timeout: 248 seconds]
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
dksong has joined #ocaml
seangrove has quit [Ping timeout: 240 seconds]
Haudegen has quit [Ping timeout: 276 seconds]
musha68k has quit [Ping timeout: 256 seconds]
MasseR has quit [Ping timeout: 276 seconds]
dksong has quit [Ping timeout: 240 seconds]
musha68k has joined #ocaml
tvaalen has quit [Remote host closed the connection]
tvaalen has joined #ocaml
struk|desk has joined #ocaml
jpdeplaix has joined #ocaml
struk|desk|away has quit [Read error: Connection reset by peer]
silver has joined #ocaml
haelix has joined #ocaml
badon has joined #ocaml
copy` has quit [Quit: Connection closed for inactivity]
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
larhat has joined #ocaml
infinity0 has quit [Ping timeout: 264 seconds]
Haudegen has joined #ocaml
infinity0 has joined #ocaml
malc_ has joined #ocaml
MasseR has joined #ocaml
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
larhat has quit [Quit: Leaving.]
rand__ has joined #ocaml
warp has joined #ocaml
kushal has quit [Ping timeout: 264 seconds]
dariol has joined #ocaml
infinity0 has quit [Remote host closed the connection]
larhat has joined #ocaml
infinity0 has joined #ocaml
sepp2k has joined #ocaml
rand__ has quit [Quit: leaving]
rand__ has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
ygrek has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
elfring has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
lolisa has quit [Read error: Connection reset by peer]
lolisa has joined #ocaml
yegods has joined #ocaml
lolisa has quit [Client Quit]
dksong has joined #ocaml
yegods has quit [Remote host closed the connection]
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
warp has quit [Quit: I'll.. be back... https://i.imgur.com/KYU8vSO.gif]
dksong has quit [Ping timeout: 250 seconds]
warp has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
slicefd has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
ygrek has quit [Ping timeout: 276 seconds]
yegods has joined #ocaml
jwatzman|work has joined #ocaml
octachron has joined #ocaml
seangrove has joined #ocaml
kushal has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
seangrove has quit [Ping timeout: 260 seconds]
pgiarrusso has quit [Quit: pgiarrusso]
_andre has joined #ocaml
yegods has quit [Remote host closed the connection]
swistak35 has joined #ocaml
<companion_cube> hi
darkf has quit [Quit: Leaving]
dhil has joined #ocaml
dksong has joined #ocaml
yegods has joined #ocaml
Janni_ has joined #ocaml
dksong has quit [Ping timeout: 272 seconds]
openplatypus has quit [Remote host closed the connection]
<Janni> Salut! As a Haskell programmer I'm wondering... when writing top-level functions in OCaml, (how) can I provide a signature, if I want to?
<flux> janni, usually, this is done in the signature file, ie. foo.mli vs foo.ml
<flux> janni, but you can also use these two ways: let a : int -> int = fun a -> a + 42
<flux> or let a (x : int) = x + 1
<Janni> Oh right. Thanks. I looked at a lot of code, and I haven't seen that syntax anywhere...
<companion_cube> let f : a -> b -> c = fun x y -> .... indeed
<companion_cube> I write this when types are not inferrable
<Janni> (which is what I need to do it for exactly)
Kakadu has joined #ocaml
yegods has quit [Remote host closed the connection]
dhil has quit [Ping timeout: 250 seconds]
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
octachron has quit [Ping timeout: 248 seconds]
yegods has joined #ocaml
pgiarrusso has joined #ocaml
yegods has quit [Remote host closed the connection]
clog has quit [Ping timeout: 260 seconds]
yegods has joined #ocaml
yegods has quit [Remote host closed the connection]
pgiarrusso has quit [Quit: pgiarrusso]
rand__ has quit [Ping timeout: 276 seconds]
dksong has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
dksong has quit [Ping timeout: 250 seconds]
pgiarrusso has joined #ocaml
pgiarrusso has quit [Client Quit]
orbifx has joined #ocaml
badon_ has joined #ocaml
badon has quit [Disconnected by services]
badon_ is now known as badon
JacobEdelman_ has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
pgiarrusso has joined #ocaml
seangrove has joined #ocaml
clog has joined #ocaml
rand__ has joined #ocaml
pgiarrusso has quit [Quit: pgiarrusso]
octachron has joined #ocaml
seangrove has quit [Ping timeout: 264 seconds]
pgiarrusso has joined #ocaml
pgiarrusso has quit [Client Quit]
<Drup> @late seangrove: menhir is not an ocamlfind package, it's only an executable. I advise you to create your own library for liquid thingy parsing (which uses menhir, and which is not related to mirage whatsoever) and to later use said library with mirage
<flux> mrvn, did you ever get ocaml-rpi properly up and running, I recall you had some issues with it?
pgiarrusso has joined #ocaml
<infinity0> aantron: thanks, yeah i get the general reasons on why more powerful abstractions are good, though i like to explore in what concrete situations i can actually avoid modules
<infinity0> it's good to understand when you don't actually need the power and can get away with a simpler construction
<infinity0> the record approach seems to work with my code so far, there's a few syntactical trade-offs with modules... the lack of internal type aliasing makes things more verbose, but i don't need to add "with type" type constraints when building new records from old ones, it's already implicit in the parameterised type
<infinity0> this is just a programming exercise for me anyway, to learn the language better
pgiarrusso has quit [Quit: pgiarrusso]
openplatypus has joined #ocaml
pgiarrusso has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
pgiarrusso has quit [Client Quit]
Emmanuel` has joined #ocaml
antkong has joined #ocaml
antkong has quit [Client Quit]
AlexRussia has quit [Ping timeout: 248 seconds]
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
mietek has quit [Ping timeout: 240 seconds]
mietek has joined #ocaml
Haudegen has quit [Ping timeout: 250 seconds]
MercurialAlchemi has quit [Quit: leaving]
ggole has joined #ocaml
MercurialAlchemi has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
Haudegen has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
dhil has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
lmaury has joined #ocaml
openplatypus has quit [Remote host closed the connection]
Emmanuel` has joined #ocaml
orbifx has quit [Quit: WeeChat 1.3]
t4nk597 has joined #ocaml
FreeBird_ has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 250 seconds]
Emmanuel` has quit [Quit: Konversation terminated!]
<t4nk597> i switched from llvm3.6 to llvm3.9, but I get now "Not a value Char6 character". Does anybody here use llvm3.8 or newer?
Emmanuel` has joined #ocaml
orbifx has joined #ocaml
Emmanuel` has quit [Client Quit]
Emmanuel` has joined #ocaml
<orbifx> Is there an issue with having multiple expaction handling expressions sequentially?
<orbifx> try ... with ...; try ... with ... ;;
<orbifx> ?
seangrove has joined #ocaml
<flux> well, no, except the scope might be surprising
<flux> an indenting editor will indicate how.. :)
thegameg has joined #ocaml
<flux> try 42 with A -> 42 ; try 55 with B -> 55 is the same as try 42 with A -> (42 ; try 55 with B -> 55)
<flux> to limit the scope of the try .. with .. you can use begin try .. with .. end; (or parens in place of begin/end if you so wish)
<ggole> If in doubt, explicit parens!
dariol has left #ocaml ["Ex-Chat"]
<mrvn> or: try ... with A -> ... | B -> ...
<ggole> That has quite different semantics, though
<ggole> (Which might still be those that are desired, I admit.)
seangrove has quit [Ping timeout: 252 seconds]
<mrvn> apropo exceptions. Python has "try/except/except/final". Any plans on having that in ocaml too?
<mrvn> "try/except/else/final" I mean
Emmanuel` has quit [Quit: Konversation terminated!]
<flux> I doubt it.
<orbifx> flux thanks for the scoping
Emmanuel` has joined #ocaml
<orbifx> mrvn: I'm considering merging them yeah, but wanted to know about the semantics
<flux> in particular 'final' would be a bit awkward in a functional environment
<mrvn> indeed
<ggole> The standard workaround is to write a function try_finally
<mrvn> both else and final would have to be a closure
<flux> maybe a decent syntax extension could do that
<flux> mrvn, but perhaps the new optimizer reduces the cost
<orbifx> flux how did you know about the precedence fo the operators there? bitten before?
<mrvn> wouldn't try_finally sualy be inlined?
<mrvn> orbifx: -> binds most. just ask your auto indent
<flux> orbifx, I don't recall, but it's not really that surprising, given how pattern matching scopes as well.
<flux> or how let a = 42; 44 is the same as let a = (42; 44)
<orbifx> ok
<orbifx> mrvn: auto indent.. pfft :P
domsj has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
<orbifx> Kakadu: here?
Emmanuel` has joined #ocaml
<reynir> What's the meaning of 'else' in try/except/else/final ?
<flux> we should also get python's for else!
<orbifx> :P
<orbifx> heresy.. where is the dogma bot?
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
<elfring> orbifx: Do you fiddle still with any background processes by OCaml interfaces?
<flux> ok, so the 'else' is executed in python if there is no exception raised
<orbifx> that's what I call eager exception expectations
<orbifx> yeah elfring
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
<elfring> orbifx: How many processes are waiting in the background for your OCaml application?
lokien has joined #ocaml
<orbifx> none.. that application starts and forks to two applications
Erylisia has joined #ocaml
domsj has left #ocaml ["ERC (IRC client for Emacs 24.5.2)"]
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
<elfring> orbifx: How much do you control these applications (in the background)?
MercurialAlchemi has quit [Ping timeout: 260 seconds]
<Janni> Am I correct if i say that in OCaml the world "module" in used in two unrelated meanings? If I look at https://ocsigen.org/lwt/2.5.1/api/Lwt for instance I read "module Lwt : sig..end" while in the sources of the packages there is no such declaration. So, do Ocamllers sometimes say "module" when they actually simply mean "file" or "compilation unit"?
Emmanuel` has quit [Client Quit]
Emmanuel` has joined #ocaml
<flux> janni, when you have a file.ml, it becomes a module
BitPuffin has joined #ocaml
<Janni> Oh, OK. Thanks.
<flux> janni, it is mostly as if you had written module File = struct (* contents of file.ml *) end in your ocaml toplevel
<orbifx> I guess the answer is explicit and implicit modules?!
MercurialAlchemi has joined #ocaml
<orbifx> elfring: what do you mean by control?
<flux> let's not call them implicit modules, implicit modules are a new and shiny future feature :)
<flux> janni, actually the pair file.mli and file.ml become module File : sig (* contents of file.mli *) end = struct (* contents of file.ml *) end
<Janni> Ah yes, that makes it very clear!
<infinity0> is it possible to have first-class functors?
<elfring> orbifx: Have you got any specific names for your example applications? (Would you like to continue this discsussion less abstract?)
<flux> infinity0, hmm, like this?
<mrvn> infinity0: I don't think so. They are a compile time thing. You can use first class modules instead.
<flux> module type A = sig type a end module type B = functor(A : A) -> sig end module type C = functor(B : B) -> functor(A : A) -> sig type b = B(A).b end
BitPuffin has quit [Disconnected by services]
<flux> oh, sorry I misunderstood that being related to higher-orderdness
<elfring> orbifx: Which function does start the background execution for the mentioned applications?
itPuffinB has joined #ocaml
<Drup> mrvn: functors are not compile time
<infinity0> flux, mrvn: oh i meant let x = (module Functor : FunctorType), it seems to work over here
itPuffinB is now known as BitPuffin
<infinity0> i just had the sig/struct the wrong way round at first
<Drup> infinity0: as you discovered, it works just fine :)
<mrvn> Hmm, must be new since we have first class modules. Doesn't that make functors slower?
<Drup> mrvn: It's not new
<ggole> Functors have never been compile-time in OCaml
<Drup> ggole: but they soon will be !
<pippijn> Drup: really?
<flux> infinity0, yep, seems to work as expected
<ggole> And many of the SML implementations do it the same way
<ggole> (Not all.)
<flux> it will work by accident, with the new optimizer?
<Drup> it will work by design with the new optimizer
Emmanuel` has quit [Quit: Konversation terminated!]
<mrvn> ggole: They used to generate you a new module from another module and you couldn't pass modules as parameters otherwise.
Emmanuel` has joined #ocaml
<flux> will there be no cases where it won't get optimized?
<flux> or will it depend on some heuristics..
<orbifx> elfring: I've lost the point of the discussion, what is the point?
<Drup> flux: when it's not static
<ggole> mrvn: that doesn't mean they were "compile time"
<mrvn> flux: if the modules are know it should optimize.
<Drup> (or when the resulting code is too big)
<ggole> And what is that?
<mrvn> ggole: I stand corrected. I thought they were and would get optimized better than passing a record of closures around.
<malc_> first order non curried functor specialization patch
<mrvn> malc_: why isn't that in git?
<elfring> orbifx: Have you got any specific names like (Alice or Bob) for your example applications? (Would you like to continue this discsussion less abstract?)
igoroliveira has joined #ocaml
<malc_> mrvn: it predates git ;)
<malc_> 3.04 was its target
<malc_> you can search ML archives for the announcement and lack of interest
<ggole> Ooh, way back in the day
<Drup> flux: but basically, it's just that the new optimizer is good at inlining, and functors are constant functions over constant arguments, so they are easy to inline.
<Drup> (at least, they are often like that, when first class modules are involved, it's all different, obviously)
<orbifx> elfring: no I haven't baptised them yet.. they are nameless processes :P
<orbifx> elfring: I'm not sure what I'm helping if you with, is this just a casual random chat?
<Drup> malc_: It's a bit sad, but considering the amount of dev on OCaml at the time, I'm not that surprised :(
<Kakadu> orbifx: I'm there
copy` has joined #ocaml
<flux> drup, I wonder might it be able to then optimize some cases of first class usage then as well?
<flux> also, how about objects.. :)
<elfring> orbifx: Do you distinguish your background processes by their purpose? Which kind of work should they perform?
<orbifx> Kakadu: there is a small typo when you get the time; http://kakadu.github.io/lablqt/tutorial2.html#building
<mrvn> Drup: will that finally optimize closure arguments?
JacobEdelman_ has quit [Quit: Connection closed for inactivity]
<orbifx> Kakadu: the last instruction there has class2_c.o twice: `class2_c.o class2_c.oz`
<ggole> Yeah, that was one of the design goals iirc
<orbifx> elfring: yes I do. Meanwhile you haven't answered my question.
<Drup> flux: maybe ? functions and functors are basically the same
<mrvn> Would also be nice to have non-inlining optimization of colsure arguments. E.g. when "foo int_compare" is used 50 times in the code it should build a partially optimized version of foo and reuse that instead of inlining it 50 times (unless it's realy small).
<malc_> Drup: a bit sad, yeah
<elfring> orbifx: I assume that "a casual random chat" can evolve into a constructive discussion, can't it?
jbrown has quit [Ping timeout: 272 seconds]
<mrvn> Drup: other than syntax aren't they exactly the same?
M-Illandan has quit [Remote host closed the connection]
<Drup> mrvn: well, typing is quite different :)
<ggole> Of course not, the typing is different
jbrown has joined #ocaml
* Drup pokes ggole
<ggole> You win this time -_-
<mrvn> In what way? the type aliases?
<orbifx> elfring: if it has a goal. Must define what is the goal to deem it constructive.
<ggole> Subsumption, stuff like with constraints, etc
<edwin> inlining sounds interesting, can it also entirely throw away the functor if all its instances are inlined in the final application?
<Drup> edwin: iirc, not yet
<ggole> And the HKT-like parts
Denommus has joined #ocaml
<mrvn> edwin: who cares? disk space is cheap and only used pages get swapped in. :)
<edwin> well my .opam is 14G, but yeah plenty more to fill :)
<mrvn> edwin: and how much of that are final binaries?
<malc_> mrvn: people who can not add extra storage?
<malc_> me?
<ggole> It's quite possible for dead code to sit in the cache close to live code, which does have a modest cost
<elfring> orbifx: I looked into this chat channel once more while you indicated a bit of interest for parallel programming. Would you like to extend your software development "experiments" in this area?
<ggole> (There's probably a million other things to worry about first, though.)
<mrvn> Compared to firefox wasting 2-6GB ram all I find that little overhead negible.
<mrvn> -all
<flux> I have a python-based clock on my screen.. it sometimes grow to 2 gigabytes.. sometimes I choose to kill it, sometimes not :)
<orbifx> elfring: I'm not doing experiments for fun alone unfortunately, I need to deliver a project. So I can't get into very abstract discussion.
Emmanuel` has quit [Quit: Konversation terminated!]
<mrvn> flux: python seems to have a lot of overhead for objects and bad GC
Emmanuel` has joined #ocaml
<orbifx> but if you have some specific questions to a specific end, I'll gladly answer them.
<flux> I would rather blame the cairo bindings
<ggole> The benefits of reducing code size aren't really a matter of RAM usage.
<mrvn> flux: they probably leak memory
<flux> the clock used to work at 2 fps, I patched it to 30 fps and now the problem arises :)
<flux> the python code is simple, so I think that must be it.
<ggole> More about taking space in the caches, iTLB, etc
<Janni> Isn't there a ready-to-use OCaml equivalent of Hoogle, i.e. a search engine for the (standard) libraries where one can search the API documentations by signature?
<Drup> Janni: not as good, unfortunatly
<mrvn> Janni: like all functions int->int->int?
<malc_> Neil Mitchell is probably laughing his ass of rightnow.. another instance of ocamlers drooling over hskl tooling
<malc_> sigh
<malc_> *off
<ggole> Why wouldn't they? ocaml tooling isn't all that great
<ggole> Although it's a *lot* better than it used to be.
<mrvn> there is ocaml tooling?
<Janni> flux: Thanks. Let's see how good it is...
<Drup> malc_: on the other hand, we don't have Opam Hell :3
<malc_> Drup: just you wait ;)
<Drup> (and merlin is much better than anything in haskell land)
<Drup> so, it's so-so
<elfring> orbifx: I would also prefer to turn some useful design abstractions into practical software tools. How do you think about to tell in which project(s) the mentioned processes should help?
<Drup> some things are better in haskell land (hoogle and cabal build, mostly), some things are much worse
<malc_> Drup: they have shake
<malc_> [i.e. nirvana]
<Drup> yes, the build systems are decent :p
<orbifx> elfring: The project is for controlling a vehicle. We have a joystick for the input (process A) and one for the gui (process B).
M-Illandan has joined #ocaml
rpg has joined #ocaml
<gargawel> Drup: Cabal hell issues got a lot better recently in Haskell world thanks to Stack / Stackage, and ghc-mod / ghc-modi have a similar feature set than Merlin
<edwin> mrvn: ~2.8 GB of actual ELF executables
<malc_> du -b -s -h .cabal
<malc_> 754M.cabal
<malc_> sigh
<malc_> pandock and shake
<mrvn> orbifx: and you want them to run in ocaml?
<malc_> bloody gigabyte
MercurialAlchemi has quit [Ping timeout: 272 seconds]
<elfring> orbifx: How do you distinguish input data that are provided by the graphical user interface?
<malc_> -k
<Drup> malc_: tbf, I doubt edwin as *one* compiler.
<Drup> has*
<edwin> oops I have an android switch too (3.4G) so subtract that
<orbifx> mrvn: I'm running them in ocaml. Using fork.
<edwin> but yeah about 14 compiler switches for various experiments
pierpa has joined #ocaml
<orbifx> elfring: distinguish in what way?
<Drup> gargawel: is ghc-mod usable now ? It was catastrophic 2y ago.
<lokien> how to update a list of tuples? [("1","somestr");("3","anotherstr")] - how do I swap "somestr" for something else?
<lokien> I'm using core
<mrvn> lokien: you dont, you make a new list
<lokien> mrvn: how to make a new list with swapped value?
<mrvn> lokien: You want to update the item with tag "1" to a new value?
<elfring> orbifx: Do you use the graphical user interface only for the display of output data?
<lokien> mrvn: yeah
jeffmo has joined #ocaml
<Drup> malc_: are you still ocaml things now or only haskell ?
<Kakadu> orbifx: fixed, thanks.
<malc_> Drup: not sure how to parse that
<orbifx> Kakadu: np
<mrvn> lokien: simple/stupid: let rec replace tag value = function [] -> [] | (t, v)::xs when t = tag -> (tag, value)::xs | x::xs -> x::(replace tag value xs)
<lokien> mrvn: thanks
<orbifx> elfring: to beging with it will be only for display of data yeah. Eventually it will be bidirectional to allow for some visual control.
<mrvn> lokien: better with List.fold_left if the order doesn't matter. Faster with Hashtbl
<Drup> malc_: add "doing" :D
<malc_> Drup: ocaml is all i doing, the only haskell thing i did is shake buildsystem for ocaml stuff :)
<lokien> mrvn: only 9 tags, speed doesn't matter
<malc_> add "am"
<malc_> s;is;was
<mrvn> lokien: also look at List.assoc and friends.
<Drup> Oh ? Did you distributed this ocaml-shake plugin ?
<lokien> mrvn: I'm looking at it, but I can't tell what a function does just by its type :(
<malc_> just something that makes me less miserable when building my stuff
<mrvn> lokien: the docs have explanations
<elfring> orbifx: Is your process configuration already working so far?
seangrove has joined #ocaml
<Drup> malc_: still, that's cool
<orbifx> elfring: no it isn't, sockets are accepting connections
<orbifx> scratch that, I think I just fixed it
<elfring> orbifx: Which implementation detail did you fix?
<lokien> mrvn: also, that recurrent solution throws an error >:C
<lokien> mrvn: oh, nvm, typo
seangrove has quit [Ping timeout: 240 seconds]
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
<orbifx> sockets need to initialised after fork, or they are duplicated (ofcouse)
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
<elfring> orbifx: Can your processes also perform data exchange by ordinary channels like "stdin" and "stdout"?
FreeBird_ has quit [Ping timeout: 272 seconds]
<orbifx> Kakadu: how can run_with_QmlAppEngine handle sockets? Where does it fit in it's event loop?
yegods has joined #ocaml
Emmanuel` has quit [Client Quit]
<Kakadu> it doesn't fit at all
<Kakadu> can you create another ocaml thread with this event loop?
<orbifx> ow ok, so it's not blocking? It's cooperative?
<elfring> orbifx: Do you start your background processes before the graphical user interface (or an other event handler) will become active?
Erylisia has quit [Ping timeout: 250 seconds]
<gargawel> Drup: yes, it's pretty usable (and actively supported)
<Kakadu> I was thinking that if we release internal lock it will become cooperative
<orbifx> elfring: they both start from one and then fork
<orbifx> Kakadu: so is it released?
Emmanuel` has joined #ocaml
<elfring> orbifx: I find this last feedback hard to understand. How often does this forking happen (and where)?
rand__ has quit [Quit: leaving]
Erylisia has joined #ocaml
<orbifx> once, during startup of the parent.
lokien has quit [Remote host closed the connection]
tane has joined #ocaml
<elfring> orbifx: Does the "parent" start only one background process so far?
lokien_ has joined #ocaml
seangrove has joined #ocaml
<Kakadu> orbifx: kind of released
<Kakadu> but the problem is that ocaml threads work but Lwt ones doesn't
<orbifx> Kakadu: that's ok, I don't use Lwt for now.
<orbifx> elfring: yes
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
malc_ has quit [Quit: leaving]
<elfring> orbifx: Can the involved two processes perform data exchange by ordinary channels like "stdin" and "stdout"?
shinnya has joined #ocaml
<orbifx> Kakadu: any guidance on how it should work with Ocaml threads?
<orbifx> elfring: they could in theory yes
<orbifx> stdin|out are streams too
<elfring> orbifx: Would data exchange by standard streams make sense in your use case?
<Kakadu> orbifx: I'm going to put example involving thread to the repo
<orbifx> Kakadu: thanks, when will you have time for that?
<Kakadu> today
<orbifx> thanks man, send an email or a message
<elfring> Kakadu: Where would your OCaml thread usage example be published?
NingaLeaf has joined #ocaml
<Kakadu> elfring: What do you expect from it?
M-Illandan has quit [Remote host closed the connection]
aantron has quit [Remote host closed the connection]
hcarty has joined #ocaml
AlexRussia has joined #ocaml
jwatzman|work has quit [Quit: jwatzman|work]
<elfring> Kakadu: I am just curious if I can read a bit more about your recent software developments. Do you try to improve the situation around a topic like "http://stackoverflow.com/questions/16562394/what-libraries-should-i-use-for-better-ocaml-threading"?
JacobEdelman_ has joined #ocaml
<Kakadu> Oh, I don't know much about multithreading. orbifx just needs some of this stuff and I don't want to lose my only possible user of lablqt.
<Kakadu> elfring: ^^
<orbifx> Kakadu: hehe, no one else reported?
<Kakadu> QtQuick differes too much from ocamlers' expectations
MercurialAlchemi has joined #ocaml
<Kakadu> Okay, I almost done the demo
<elfring> Kakadu: Do you plan to extend a software library like "lablqt"?
M-Illandan has joined #ocaml
<Kakadu> If somebody will use it and/or will explain in which direction I should extending -- I will.
<orbifx> Kakadu: I got some ideas on that, but one step at a time.
vpm has quit [Quit: co'o]
<orbifx> and see how mrvn gets on with the moc replacer
slash^ has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
<elfring> Kakadu: Which kind of "OCaml threads" are mentioned in the document "http://kakadu.github.io/lablqt/"?
Emmanuel` has joined #ocaml
ski____ has quit [Ping timeout: 252 seconds]
M-Illandan has quit [Remote host closed the connection]
<orbifx> Should `while x do..` be compiling with an x whose value is 'a ?
<flux> well, yes, because bool is a 'a
shinnya has quit [Ping timeout: 260 seconds]
<flux> however, I don't see how you get a value of polymorphic type 'a :)
vpm has joined #ocaml
Algebr2 is now known as Algebr
<Kakadu> elfring: Thread module
Algebr is now known as Guest29706
Guest29706 is now known as Algebr`
<orbifx> flux: input_value
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
<flux> orbifx, well, it works alright. but the problem of course arises if the value input_value returns isn't really bool.
<flux> though I think in that particular while loop it works.
<flux> well "works", doesn't crash :-)
<orbifx> yeah, probably because it hasn't received something yet :P
aantron has joined #ocaml
<flux> orbifx, it's like this: while assert false; do .. done
<elfring> Kakadu: Would you like to provide a link for this "Thread module"? How do you distinguish between cooperative threads, really parallel threads, fibers and processes?
<flux> assert false is a 'a -typed value as well, but in this case it's not lying about it. because it never returns the value that would be of some other type.
ski has joined #ocaml
yegods has quit [Remote host closed the connection]
<flux> in your case input_value is promising to return a 'a.. so you can consider that it return a value that is bot integer and string and a file descriptor at the same time..
<flux> well, the type system can't prevent this from happening, so you better limit the return type to bool at a very early stage after input_value
<flux> ie. let foo : bool = input_value ..
Emmanuel` has quit [Client Quit]
Emmanuel` has joined #ocaml
yegods has joined #ocaml
<orbifx> flux i'll give it a shot. Can I specify the type inline somehow?
<elfring> Kakadu: Does the wording "Demo with OCaml threads from stdlib Thread module" refer to an interface of threads which are not executed in parallel (on several processors) by the OCaml run time environment so far?
<flux> let foo = (input_value .. : int) works as well
<flux> elfring, yes
M-Illandan has joined #ocaml
<orbifx> thanks Kakadu
slicefd has quit [Quit: WeeChat 1.4]
<elfring> Kakadu, flux: Does any OCaml library provide a process pool?
<Kakadu> elfring: Yeah, it is these concurrent threads. I added a link on github pages
<flux> elfring, opam seems to have nproc
<flux> elfring, and maybe lwt-parallel is related as well
<flux> elfring, out of hunch I would look if ocamlnet has one
<elfring> Kakadu: Have you got an other view about the feedback by "flux"?
th5 has joined #ocaml
<Kakadu> elfring: What are you talking about?
<elfring> Kakadu: Would you like to be a bit more precise under which circumstances the mentioned threads will be executed in parallel?
<Kakadu> the link above says that these threads are not going to be executed in parallel
<seangrove> I'm trying to use my liquid/parser.mly and liquid/lexer.mll from dispatch.ml, and getting this error: + /Users/s/.opam/4.02.3/bin/ocamlyacc liquid/parser.mly, File "liquid/parser.mly", line 15: syntax error: (* part 1 *)
<orbifx> flux got any idea if `select` needs to be called before using input_value?
<seangrove> Bah, forgot -use-menhir
ygrek has joined #ocaml
<hcarty> elfring: OCaml's threads are not executed in parallel, with the exception of IO and some calls to C libraries.
<hcarty> elfring: If you want parallelism in OCaml code then you'll need to use multi-processing with a library such as the ones flux mentioned
<aantron> Drup, for arbitrary attributes and elements, do you prefer the ppx cause errors, or inject them using module Xml and functions Html.tot and friends?
<elfring> Kakadu, hcarty: Is the wording "Lightweight threads for Posix 1003.1c and Win32" too promising in the document ""http://caml.inria.fr/pub/docs/manual-ocaml/libref/Thread.html?
<hcarty> What do you mean by "too promising"?
ski has quit [Ping timeout: 272 seconds]
<hcarty> "real" threads are used internally. As of 4.02.3 OCaml only runs one of those threads at a time.
<elfring> Kakadu, hcarty: May I expect support for parallel execution on several processors from the wording "Lightweight threads for Posix 1003.1c and Win32" in the document "http://caml.inria.fr/pub/docs/manual-ocaml/libref/Thread.html"?
hcarty has quit [Read error: Connection reset by peer]
hcarty has joined #ocaml
<octachron> elfring, threads imply concurrency not parallelism
<aantron> elfring: not presently
Guest89484 is now known as johnelse
M-Illandan has quit [Remote host closed the connection]
<elfring> Kakadu, hcarty, octachron, aantron: Are there any more attempts to express open issues (like the parallelism aspect) in the available documentation besides the wording "Lightweight threads"?
<companion_cube> multicore threading?
<companion_cube> people have complained for years, you don't need to add to it
ski has joined #ocaml
yegods has quit [Remote host closed the connection]
<seangrove> Ok, made tons of progress, just about where I want to be for a hacky prototype
<seangrove> I have a merlin rule: let source_text = ['a'-'z' 'A'-'Z' '0'-'9' '_' ' ' '.' '\n' '=' '#' '?' '*']* (* Anything outside of {{ }} and {* *} *)
<seangrove> But I actually just want it to match anything except {{
<seangrove> (I think this may cause conflicts with other rules, but just exploring it for now)
<elfring> companion_cube: When will anybody dare to extend the affected document "http://caml.inria.fr/pub/docs/manual-ocaml/libref/Thread.html"?
<companion_cube> err, what
<octachron> elfring, the manual is quite explicit here: http://caml.inria.fr/pub/docs/manual-ocaml/libthreads.html
aantron has quit [Remote host closed the connection]
<seangrove> What's a menhir pattern that will match anything except {{ or {% ?
<elfring> octachron: The property "concurrent" is mentioned there. But where is the support for parallel execution on several processors (multi-core threading) explicitly described?
<octachron> elfring, second paragraph
<zozozo> seangrove: i suppose you also don't want to consider spaces and the like ?
<seangrove> zozozo: I'd like to keep all of that. I have a source file: `<h1>{{post.title}}</h1> some text that's always here. Published on {{today_as_date}}`
<elfring> octachron: Will be current OCaml software limitation "The threads library is implemented by time-sharing on a single processor. It will not take advantage of multi-processor machines." be changed anyhow?
<seangrove> I want to parse everything outside of the {{ }} as source_text, while capturing the stuff inside of {{ }} as some other token types
<octachron> elfring, work is in progress on a multicore ocaml implementation
<zozozo> seangrove: is it really important that the token types be different ?
<zozozo> because I would find it simpler to have a single token type, then have the appropriate grammar rules to recognize what you want inside the {{ }}
jwatzman|work has joined #ocaml
yegods has joined #ocaml
<octachron> seangrove, do you have any nested {{}}?
<elfring> octachron: How can OCaml be limited to perform only "time-sharing on a single processor"? Was parrallel multi-threading support improved a bit recently?
elfring has quit [Quit: Konversation terminated!]
<orbifx> do I need to do any preparations before using an `out_channel` from `out_channel_of_descr` ?
<companion_cube> I don't think so
<orbifx> not getting anything... :/
aantron has joined #ocaml
<companion_cube> you might need to flush though
Nairwolf has joined #ocaml
octachron has quit [Quit: Leaving]
<Nairwolf> hi guys, can you help to review a simple ocaml program ? I wonder why I need so much brackets with this file at line 13 : https://github.com/Nairolf21/learning/blob/master/ocaml/bintree.ml
<Nairwolf> The line is "print_endline (string_of_bool (isLeaf leaf));"
<seangrove> zozozo: That makes sense as well, thanks for the pointer
<Nairwolf> without bracket, I can't compile this code
<thizanne> because f a b c means (((f a) b) c)
<orbifx> companion_cube: will try it, although ill be surprised if it cached all i sent.
<ggole> Nairwolf: if you think it is ugly, consider printf "%b\n" (isLeaf leaf) instead
<Nairwolf> thizanne: oh, I see ;) But is it possible to write something like that "print_endline (string_of_bool isLeaf leaf)" ?
ygrek_ has joined #ocaml
<Nairwolf> ggole: I need to import the printf module, right ?
ygrek has quit [Ping timeout: 256 seconds]
<ggole> Or you could prefix with Printf.
warp has quit [Ping timeout: 276 seconds]
<thizanne> Nairwolf: you could use @@
<Nairwolf> ok, I will do that
<Nairwolf> what is @@ ?
<thizanne> f @@ x is like f x, but with lower priority than function application
<thizanne> so f @@ a b is f (a b)
<Nairwolf> oh I didn't know that
<thizanne> f @@ a @@ b is f (a b) too, by the way
<Nairwolf> but why I need two pairs of brackets ?
<thizanne> because you have two function applications
<orbifx> companion_cube: I'll be damned, it was!
<thizanne> print_endline and string_of_bool
<thizanne> (and isLeaf leaf after)
<companion_cube> orbifx: :)
<thizanne> you can write print_endline @@ string_of_bool @@ isLeaf @@ leaf, last @@ is optional
<Nairwolf> ok, thank you ;)
<Nairwolf> I've learned something, I thought functions start from the right to the left
<Nairwolf> but it's the contrary, thank you thizanne
<flux> orbifx, you mean Unix.select? no, don't use blocking io with non-blocking io (ie. Unix.select), there's trouble ahead otherwise
<orbifx> flux: yeah it was caching
<orbifx> Kakadu: going over the example you have provided
<orbifx> in particular obj.magic :P
_andre has quit [Quit: leaving]
aantron has quit [Ping timeout: 256 seconds]
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
aantron has joined #ocaml
<flux> example.. with Obj.magic..
ygrek_ has quit [Ping timeout: 256 seconds]
ygrek_ has joined #ocaml
Emmanuel` has quit [Client Quit]
Emmanuel` has joined #ocaml
<orbifx> lol flux
<Drup> aantron: error
<Drup> except for data-foo
<Drup> then a_user_data
<Drup> seangrove: I put something for you when you weren't there ^^
jwatzman|work has quit [Quit: jwatzman|work]
rpg has quit [Quit: rpg]
Erylisia has quit [Quit: Quitte]
<aantron> Drup, im likely to write a ppx build tool that will run on the Html5_sigs.T and Svg_sigs.T and extract attributes of tables, elements, etc., from the type information. any notes or objections?
<aantron> tables of attributes*
<Drup> Not really, but I'm not sure what's the goal
Denommus has quit [Ping timeout: 260 seconds]
<aantron> to be able to convert attribute values in string form to typed attribute values, e.g. the rewriter needs to know to call float_of_string on an attribute value when the typed attribute expects a float_number
<Drup> Oh, of course
<Drup> that makes sense, yes
<Drup> It's going to be a bit of work, I think
<aantron> shouldnt be too bad. i already have a basic ppx working, but only for some attributes and elements, since i dont have this type information for all values yet. i figured rather than entering it by hand and maintaining it in sync, it would be easier to write this build tool
yegods has quit [Remote host closed the connection]
<Drup> aantron: can you also generate the map of attributes that need to be changed too ?
malik__ has joined #ocaml
<Drup> like "max inside input" -> "a_input_max" ?
<seangrove> Drup: I didn't see it, sorry about that
<Drup> seangrove: no problem, I happen to wake up just after you disconnect :D
<seangrove> But, it all kind of works! My parser kind of mangles input html, but it kinda-sorta is able to do replacements in html
<aantron> not sure you mean by "changed," something like the effects of applying the name conversion tool to each attribute?
<malik__> hello there i'm on mac os x el capitan and i'm trying to use graphics.cma. I'v installed ocaml trough spam but ocamlc -where give me /opt/local/lib/ocaml. Any ideas ?
<Drup> aantron: well, I gave an example
<malik__> *throug opam
yegods has joined #ocaml
<aantron> i am not sure what underlies this example
<Drup> aantron: well, look at all the "max" attributes in html5_f
<Drup> there are, iirc, 2 of them
<aantron> yes
<Drup> they are prefixed
<Drup> will you have to enter those manually ?
<Drup> or will they be recognized by your tool ?
ggole has quit [Ping timeout: 276 seconds]
<aantron> so you are saying that what is needed is a map: (context * name) -> tyxml_name?
<aantron> anyway, i will take care of it somehow
<aantron> malik__: opam is probably using your system compiler installation, which is normal
<aantron> how are you trying to use graphics.cma? i.e. what command line, package tags, etc.?
<Drup> aantron: precisely
yegods has quit [Remote host closed the connection]
<malik__> aantron: well i'm trying under emacs with the following command to open ocaml top level /opt/local/bin/opam config exec -- ocaml to do #load "graphics.cma";; but i get the following error : Cannot find file graphics.cma.
<aantron> interesting. it works for me
th5 has quit [Ping timeout: 276 seconds]
<orbifx> Kakadu: have you tried your example btw? certain that is works ok?
<malik__> aantron: do you have something specific in your .emacs concerning your ocaml top level environment ?
<aantron> no, but i do in .ocamlinit. but i commented out and it worked without it
<aantron> have you done eval `opam config env` since installing opam?
<malik__> it's in my bash .profile
<aantron> i noticed that i dont have graphics.cma in my system ocaml directory, but do in opam
<malik__> aantron: do i have to do something like spam install graphics ?
Lis has joined #ocaml
<aantron> what does "opam switch show" say?
<malik__> aantron: system
<aantron> i dont remember ever doing anything special, perhaps somebody else knows
<aantron> okay it doesnt work on my system switch either
<aantron> i would suggest doing "opam switch 4.02.3" though this is a bit of a "nuclear" way of taking care of it. perhaps someone knows a more precise solution
<aantron> because this will install a whole new compiler through opam, but it should have graphics.cma included in the libraries
<aantron> actualyl first
<aantron> can you do "opam list" ?
malc_ has joined #ocaml
<aantron> im guessing you used macports? its possible that the ocaml macports package doesnt include graphics.cma
<aantron> there doesnt appear to be a separate opam "graphics" package for installing it separately, either
Emmanuel` has quit [Quit: Konversation terminated!]
<malik__> aantron: well i ran "opam switch 4.02.3" and it worked for me than you
Emmanuel` has joined #ocaml
sgnb` has quit [Remote host closed the connection]
kushal has quit [Ping timeout: 240 seconds]
<Drup> seangrove: don't you want review on your current version ? :p
malik__ has quit [Quit: Page closed]
Emmanuel` has quit [Quit: Konversation terminated!]
larhat has quit [Quit: Leaving.]
Emmanuel` has joined #ocaml
freehck has quit [Ping timeout: 250 seconds]
orbifx has quit [Quit: WeeChat 1.3]
Kakadu has quit [Quit: Page closed]
aantron has quit [Ping timeout: 256 seconds]
alexst has joined #ocaml
orbifx-m has joined #ocaml
BitPuffin has quit [Ping timeout: 250 seconds]
aantron has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
foolishmonkey has joined #ocaml
Emmanuel` has joined #ocaml
darkf has joined #ocaml
hanshenrik__ has joined #ocaml
JacobEdelman_ has quit [Quit: Connection closed for inactivity]
th5 has joined #ocaml
alexst has quit [Ping timeout: 252 seconds]
Algebr` has quit [Ping timeout: 250 seconds]
Algebr` has joined #ocaml
aantron has quit [Ping timeout: 256 seconds]
lokien_ has quit [Quit: Connection closed for inactivity]
Emmanuel` has quit [Quit: Konversation terminated!]
sgnb has joined #ocaml
Emmanuel` has joined #ocaml
rand__ has joined #ocaml
alexst has joined #ocaml
Haudegen has quit [Ping timeout: 256 seconds]
hanshenrik__ is now known as hanshenrik
shinnya has joined #ocaml
elfring has joined #ocaml
Algebr` has quit [Ping timeout: 260 seconds]
Kakadu has joined #ocaml
rpg has joined #ocaml
seangrove has quit [Ping timeout: 248 seconds]
Haudegen has joined #ocaml
jbrown has quit [Remote host closed the connection]
infinity0 has quit [Ping timeout: 250 seconds]
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
infinity0 has joined #ocaml
jbrown has joined #ocaml
Emmanuel` has quit [Client Quit]
Emmanuel` has joined #ocaml
ygrek_ has quit [Ping timeout: 265 seconds]
Emmanuel` has quit [Client Quit]
Emmanuel` has joined #ocaml
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
groovy2shoes has quit [Quit: Leaving]
Emmanuel` has quit [Client Quit]
Emmanuel` has joined #ocaml
Anarchos has joined #ocaml
Simn has quit [Quit: Leaving]
zozozo has quit [Ping timeout: 240 seconds]
slash^ has quit [Read error: Connection reset by peer]
Lis has joined #ocaml
seangrove has joined #ocaml
dhil has quit [Ping timeout: 260 seconds]
Algebr`` has quit [Remote host closed the connection]
yegods has joined #ocaml
seangrove has quit [Ping timeout: 265 seconds]
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
sepp2k has quit [Quit: Leaving.]
malc_ has quit [Ping timeout: 256 seconds]
yegods has quit [Remote host closed the connection]
yegods has joined #ocaml
foolishmonkey has quit [Quit: Leaving]
BitPuffin has joined #ocaml
Janni has quit [Quit: Leaving]
BitPuffin has quit [Remote host closed the connection]
MercurialAlchemi has quit [Ping timeout: 276 seconds]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
lmaury has left #ocaml ["Leaving"]
seangrove has joined #ocaml
ygrek_ has joined #ocaml
<seangrove> Drup: Review my current parser?
<seangrove> Absolutely. It's probably fairly atrocious :) But working on it incrementally has been good. Add a feature (or ability to parse just a bit more), then fix a few bugs, iterate.
rpg has quit [Quit: rpg]
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
elfring has quit [Quit: Konversation terminated!]
Nairwolf has left #ocaml ["WeeChat 1.4"]
antkong_ has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
malik_ has joined #ocaml
Emmanuel` has joined #ocaml
<malik_> hello there i'm trying to use (Unix.select [] [] [] sec) to make a pause of some seconds (float) in my program but i get the following exception : Unix.Unix_error(Unix.EINTR, "select", "") does anyone have an idea ?
<Drup> If you want to make a pause, why not use sleep ?
<malik_> Drup: i want to make a pause of less than a second ...
slicefd has joined #ocaml
sgnb has quit [Read error: Connection reset by peer]
sgnb has joined #ocaml
tani has joined #ocaml
Maelan has quit [Ping timeout: 250 seconds]
tobiasBora has quit [Ping timeout: 256 seconds]
tane has quit [Ping timeout: 240 seconds]
hcarty has quit [Quit: WeeChat 1.4]
aantron has joined #ocaml
tobiasBora has joined #ocaml
Haudegen has quit [Ping timeout: 260 seconds]
Maelan has joined #ocaml
<Drup> Is using select for that even supported ? The error is a unix one, not an ocaml one
ril has joined #ocaml
<smondet> Drup: (and malik_ ) it is supposed to work; but implementations of `select` accross unixes...
dksong has joined #ocaml
lokien_ has joined #ocaml
<Drup> right
<Drup> a binding of nanosleep would be more reliable, I think
yegods has quit [Remote host closed the connection]
<tani> generally, using select for sleeping only is ok and has been favored by some due to alleged high accuracy
silver has quit [Quit: rakede]
tani is now known as tane
dksong has quit [Ping timeout: 272 seconds]
damason has joined #ocaml
yegods has joined #ocaml
<edwin> next version of ocaml will probably have a better select
<edwin> I mean sleep
th5 has quit [Quit: Textual IRC Client: www.textualapp.com]
Haudegen has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
damason has quit [Ping timeout: 240 seconds]
Emmanuel` has joined #ocaml
struk|desk is now known as struk|desk|away
j_king has quit [Remote host closed the connection]
zozozo has joined #ocaml
<pierpa> a sleep with a float arg, implemented with nanosleep or whatever is available would be great
ygrek_ has quit [Remote host closed the connection]
yegods has quit [Read error: Connection reset by peer]
ygrek has joined #ocaml
yegods has joined #ocaml
infinity0 has quit [Remote host closed the connection]
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
yegods has quit [Remote host closed the connection]
infinity0 has joined #ocaml
seangrove has quit [Ping timeout: 276 seconds]
Emmanuel` has quit [Client Quit]
Emmanuel` has joined #ocaml
ril is now known as ril[away]
ril[away] is now known as ril
pierpa` has joined #ocaml
tane has quit [Quit: Verlassend]
reynir1 has joined #ocaml
apache2_ is now known as apache2
caw_ has joined #ocaml
axiles has quit [Ping timeout: 248 seconds]
mehdi___ has joined #ocaml
Algebr` has joined #ocaml
igoroliveira_ has joined #ocaml
oskarth_ has joined #ocaml
Asmadeus_ has joined #ocaml
lopex_ has joined #ocaml
igitoor_ has joined #ocaml
Reventlo1 has joined #ocaml
wagle_ has joined #ocaml
oldmanistan__ has joined #ocaml
S11001001_ has joined #ocaml
seangrove has joined #ocaml
mankyKitty_ has joined #ocaml
chenglou_ has joined #ocaml
stephe_ has joined #ocaml
asmanur_ has joined #ocaml
luigy_ has joined #ocaml
wagle_ is now known as wagle__
tobiasBora has quit [*.net *.split]
pierpa has quit [*.net *.split]
igoroliveira has quit [*.net *.split]
keteim has quit [*.net *.split]
yawnt has quit [*.net *.split]
Reventlov has quit [*.net *.split]
mehdi_ has quit [*.net *.split]
S11001001 has quit [*.net *.split]
oldmanistan_ has quit [*.net *.split]
asmanur has quit [*.net *.split]
lyxia has quit [*.net *.split]
cartwright has quit [*.net *.split]
martintrojer has quit [*.net *.split]
rossberg has quit [*.net *.split]
jyc has quit [*.net *.split]
oskarth has quit [*.net *.split]
Asmadeus has quit [*.net *.split]
fluter has quit [*.net *.split]
luigy has quit [*.net *.split]
chris2 has quit [*.net *.split]
jlarocco has quit [*.net *.split]
wagle has quit [*.net *.split]
igitoor has quit [*.net *.split]
mankyKitty has quit [*.net *.split]
caw has quit [*.net *.split]
reynir has quit [*.net *.split]
lopex has quit [*.net *.split]
chenglou has quit [*.net *.split]
stephe has quit [*.net *.split]
igoroliveira_ is now known as igoroliveira
oldmanistan__ is now known as oldmanistan_
wagle__ is now known as wagle
lopex_ is now known as lopex
reynir1 is now known as reynir
lopex is now known as Guest91418
fluter has joined #ocaml
stephe_ is now known as stephe
martintrojer has joined #ocaml
S11001001_ is now known as S11001001
alexst has quit [Quit: leaving]
so has quit [Ping timeout: 250 seconds]
cartwright has joined #ocaml
mankyKitty_ is now known as mankyKitty
chenglou_ is now known as chenglou
caw_ is now known as caw
oskarth_ is now known as oskarth
malik_ has quit [Ping timeout: 252 seconds]
tobiasBora has joined #ocaml
lyxia has joined #ocaml
jlarocco has joined #ocaml
igitoor_ has joined #ocaml
igitoor_ has quit [Changing host]
igitoor_ is now known as igitoor
rossberg has joined #ocaml
keteim has joined #ocaml
yawnt has joined #ocaml
yawnt has quit [Changing host]
yawnt has joined #ocaml
Emmanuel` has quit [Quit: Konversation terminated!]
Emmanuel` has joined #ocaml
aantron has quit [Remote host closed the connection]
jyc has joined #ocaml
chris2 has joined #ocaml
rand__ has quit [Quit: leaving]