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
sh0t has quit [Quit: Leaving]
darkf has joined #ocaml
pyx has joined #ocaml
pyx has quit [Client Quit]
silver has quit [Quit: rakede]
<Drup> Nazral: By curiosity, what is this tyxml_js tutorial ?
darkf has quit [Ping timeout: 250 seconds]
Kakadu has quit [Remote host closed the connection]
<Nazral> it's not so much of a tutorial as an example but it's this http://roscidus.com/blog/blog/2015/06/22/cuekeeper-internals-irmin/#tyxml
<Drup> oh, right
<aantron_> "I’d come across TyXML before, but had given up after being baffled by the documentation. "
<Drup> é_è
<Nazral> with tyxml, how do I change the pcdata of an element after it being created ?
<Drup> Either you don't, or you use the R module
darkf has joined #ocaml
<Nazral> thanks !
Algebr` has joined #ocaml
seangrove has quit [Ping timeout: 248 seconds]
Algebr` has quit [Ping timeout: 250 seconds]
yunxing has quit [Remote host closed the connection]
yunxing has joined #ocaml
Algebr` has joined #ocaml
foolishmonkey has quit [Quit: Leaving]
yunxing has quit [Remote host closed the connection]
hxegon has quit [Ping timeout: 248 seconds]
chindy has quit [Remote host closed the connection]
yunxing has joined #ocaml
dexterph has quit [Ping timeout: 250 seconds]
Algebr` has quit [Ping timeout: 244 seconds]
tennix has quit [Ping timeout: 276 seconds]
shinnya has quit [Ping timeout: 244 seconds]
FreeBirdLjj has joined #ocaml
jeffmo has quit [Quit: jeffmo]
yunxing has quit [Remote host closed the connection]
yunxing has joined #ocaml
seangrove has joined #ocaml
Algebr` has joined #ocaml
tennix has joined #ocaml
yunxing has quit [Remote host closed the connection]
tennix has quit [Ping timeout: 240 seconds]
tennix has joined #ocaml
ygrek_ has quit [Ping timeout: 244 seconds]
hxegon has joined #ocaml
Algebr` has quit [Ping timeout: 250 seconds]
sz0 has quit [Quit: Connection closed for inactivity]
teknozulu has joined #ocaml
johnelse has quit [Ping timeout: 255 seconds]
johnelse has joined #ocaml
seangrov` has joined #ocaml
seangrove has quit [Ping timeout: 255 seconds]
Algebr` has joined #ocaml
struk|desk|away is now known as struk|desk
seangrov` has quit [Remote host closed the connection]
seangrov` has joined #ocaml
antkong has quit [Quit: antkong]
antkong has joined #ocaml
teknozulu has quit [Ping timeout: 244 seconds]
yunxing has joined #ocaml
yunxing has quit [Remote host closed the connection]
yunxing has joined #ocaml
seangrov` has quit [Ping timeout: 276 seconds]
struk|desk is now known as struk|desk|away
struktured has joined #ocaml
struk|desk|away is now known as struk|desk
nicholasf has quit [Ping timeout: 248 seconds]
Mercuria1Alchemi has joined #ocaml
struktured has quit [Ping timeout: 248 seconds]
malc_ has joined #ocaml
teknozulu has joined #ocaml
Mercuria1Alchemi has quit [Ping timeout: 240 seconds]
AlexRussia has quit [Ping timeout: 240 seconds]
teknozulu has quit [Ping timeout: 244 seconds]
teknozulu has joined #ocaml
yunxing_ has joined #ocaml
pierpa has quit [Ping timeout: 248 seconds]
yunxing has quit [Ping timeout: 240 seconds]
asdf12z_ has joined #ocaml
antkong has quit [Quit: antkong]
antkong has joined #ocaml
antkong has quit [Client Quit]
JacobEdelman_ has quit [Quit: Connection closed for inactivity]
ldg has joined #ocaml
teknozulu has quit [Ping timeout: 240 seconds]
seangrov` has joined #ocaml
hxegon has quit [Quit: BRB]
etherael has quit [Remote host closed the connection]
seangrov` has quit [Remote host closed the connection]
Simn has joined #ocaml
tane has joined #ocaml
larhat has joined #ocaml
johnf_ has joined #ocaml
struk|desk is now known as struk|desk|away
silver has joined #ocaml
FreeBird_ has joined #ocaml
kushal has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 240 seconds]
nojb has joined #ocaml
<malc_> hola nojb
<Nazral> https://github.com/talex5/js-skeleton/blob/master/main.ml#L20 < I've got a bit of trouble understanding that. Does it set the "current" variable as the return value of set_current ?
sepp2k has joined #ocaml
larhat has quit [Quit: Leaving.]
<nojb> Hi malc_
<nojb> Hola :)
<Algebr`> S.create gives back a tuple and its just pattern matching assigning the names instantly.
aantron_ has quit [Remote host closed the connection]
<Nazral> Algebr`: oh ok thanks
<Algebr`> I like to write that as let (current, set_current) = .... to make it more explicit
sz0 has joined #ocaml
<Nazral> that's clearer indeed
<flux> I wouldn't mind if ocaml needed the explicit parens for tuples, but I'll manage.. and maybe sometimes not use them either ;)
Haudegen has quit [Ping timeout: 240 seconds]
copy` has quit [Quit: Connection closed for inactivity]
<companion_cube> I like to never put ( ) around tuples :]
* Maxdamantus doesn't even put () around zero-tuples.
kolko has quit [Ping timeout: 244 seconds]
rand__ has joined #ocaml
ontologiae has joined #ocaml
<malc_> nojb: FWIW, I've managed to build the stuff your way.. but getting no sensible output in the window
<Nazral> Is it bad that I need the +js_of_ocaml/weak.js option when compiling the bytecode to js with jsoo ?
octachron has joined #ocaml
<Drup> Not exactly
Sorella has quit [Quit: Connection closed for inactivity]
sepp2k has quit [Quit: Leaving.]
<Nazral> a bit though
<Nazral> I've just got the feeling it's not amazing
<Nazral> by the way I'm using tyxml now, with react and everything, the link your gave me helped a lot :)
<Drup> It's a fake implementation of weak pointers
<Drup> it's not really weak, which means you can get space leak
<nojb> malc_: ok, thanks for the report - it is in a *very* rough state, so I'm not surprised - I will try to work on it more this weekend
sepp2k has joined #ocaml
julien_t has joined #ocaml
wolfcore has quit [Ping timeout: 276 seconds]
Haudegen has joined #ocaml
warp has joined #ocaml
wolfcore has joined #ocaml
<malc_> nojb: moi bien, the weekend is just around the corner ;)
<malc_> muy... sigh
<nojb> :)
<malc_> me llama angela, me van a matar - basically sums up my spanish vocabulary anyways
<Nazral> la araña discoteca
<Nazral> Ok I want to do some operations on strings and the standard library doesn't satisfy me (for example I want to be able to split strings without using regexps), should I rather write some functions myself or are there some nice string manipulation libraries around ?
Sim_n has joined #ocaml
foolishmonkey has joined #ocaml
wolfcore has quit [Ping timeout: 255 seconds]
<companion_cube> stringext, astring...
Simn has quit [Ping timeout: 240 seconds]
jwatzman|work has joined #ocaml
wolfcore has joined #ocaml
<edwin> hmm my opam version 1.2.0 complains about {test} in the build section (tried to install tree_layout)
<edwin> is it too old?
<companion_cube> no idea, I use 1.2.2
j0sh has quit [Ping timeout: 240 seconds]
<Algebr`> Nazral: if using jsoo then use js's own regexp, its available to you in jsoo
Kakadu has joined #ocaml
<Nazral> Algebr`: I would like not to use regexp for simple things like splitting a string around newline characters
<malc_> Nazral: why?
<Nazral> I've been taught not to use regular expressions for simple things because they are computationally expensive
<Enjolras> malc_: this is overkill and slow
<malc_> Enjolras: do you have something to back that claim up?
<Enjolras> yes, i have run a simple benchmark. This is slow not because of computation time, but because of allocations
<Enjolras> if you run this in a loop, it will trigger many more GCs
<Enjolras> of course, it depends on the regexp lib, re2 is much better than pcre for instance, but still to split by a single char, a plain ocaml function is much much faster
<malc_> Enjolras: that's with precompiled re?
<Enjolras> i haven't even bothered to try with re :p
<malc_> erm..
<malc_> # #load "str.cma";;
<malc_> # let r = Str.regexp "abc";;
<malc_> val r : Str.regexp = <abstr>
<malc_>
<malc_> did you do this inside or outside of the loop?
<Enjolras> of course. I'm not than dumb ;)
<Enjolras> you can try by yourself
<Enjolras> i was always told that re is crap and shouldn't be used, like Str
<malc_> letter composition of the nick on the IRC is hardly an indication of an intelligence level, so forgive me for assuming the worst
<Nazral> Since my code is going to be ran by computers capable of running firefox, I guess I can safely assume that using regexp a few times isn't going to kill them
<malc_> Nazral: it wont
<Enjolras> we are talking about 10% difference
<Enjolras> not 10x slower anyway. But since functions are avaible in good library to do that without regexp and it's faster, and it's not harder to use, i don't see the point not to use a plain function
<malc_> Enjolras: do you still have that testing code available?
<Enjolras> malc_: probably. But on my laptop, i am at work right now
<Nazral> Enjolras: I'm trying to use the astring library right now
<Enjolras> Nazral: i like it
<malc_> Enjolras: ok
<Nazral> but I'm doing something wrong because I can't convert a string to Astring.string.sub
<companion_cube> anyway Str is ugly
<Nazral> String.sub.(of_string ~start:3 ~stop:10 s) < I'd expect that to work but nope
<malc_> String.(sub ...)
<malc_> perhaps
<malc_> then again
<malc_> what do i know
<Enjolras> malc_: i hope you didn't feel like my remark was directed against you :/
haxor has joined #ocaml
<haxor> How can I show information about the declaration of a type SomeModule.t in utop?
<haxor> Or alternatively in an ocaml toplevel?
<malc_> Enjolras: not even sure what you are referring to
<malc_> regardless, no offense was taken
<octachron> haxor, #show SomeModule.t?
<Drup> "Enjolras: i was always told that re is crap and shouldn't be used, like Str" What ?!
<Drup> I want name, who said that ?
<Drup> x)
<malc_> `--> sdcv re | sed -n 5,7p
<malc_> RE
<malc_> Research and Engineering, "R&E"
<malc_>
<malc_> so i guess opposite of that are to blame (fine artisans)
<haxor> octachron:where is the documentation for #show and other commands?
<malc_> Drup: I remember Jeromes announcement on the mailing list a long long time ago, and then it appeared that the library went dormant
pgiarrusso has quit [Quit: pgiarrusso]
<octachron> haxor, in the manual
<Drup> Well, it works very well, the API is decent, if a bit arid (it was improved a bit) and it's very efficient.
<Nazral> are you saying I should use it to build a dom tree from a string ?
<Drup> Nazral: just use one of the string libraries
<malc_> Drup: can you elaborate on the arid part?
<Drup> malc_: jérôme is not know for his documentation writing skills :D
<octachron> haxor, next ocaml version will also have a #help directive (and a more organized manual section)
* Drup throws flowers at octachron: thanks to you!
<Drup> malc_: To be more precise: the API is very complete, but it lacks a tutorial to help newcommers
<octachron> Drup, this point is more gasche's work, I have just lifted the #help directive structure to the manual
<malc_> Drup: hah, lend him a hand, if your sentence shows anything it's that you are quite apt in the writing dépârtmènt (http://xkcd.org/1647/)
haxor has quit [Quit: http://www.kiwiirc.com/ - A hand crafted IRC client]
<Drup> jérôme is my phd advisor, I would not dare write his name without the necessary decorations!
haxor has joined #ocaml
<malc_> Drup: touché :)
<Enjolras> Drup: sorry, i was talking of re support in Str, not about ocaml-re
<Enjolras> (etoomanyrelibs)
<Enjolras> i have never tried re, re2 is quite good
<Drup> re2 is not pure, though
<Enjolras> what does it mean ? it is in C++, yes, or do you mean pure like in stateless ?
<Drup> purely ocaml*
<Enjolras> ah, yes. I don't bother too much for external libs :)
<malc_> i think you meant you do not "care too much"
<companion_cube> re is nice
lmaury has joined #ocaml
<malc_> next one should be called apRÈs_nous_le_déluge
<haxor> octachron:perhaps an idea to also map the symbol "help" to #help.
<haxor> octachron:and ? and \?.
<haxor> octachron:thanks for your help.
<Algebr`> I like re2
<snhmib> man i thought it was a good idea to use a bunch of different objects with the same base class instead of a variant type and pattern matching everywhere
<snhmib> fuck me
<Drup> It can be a good idea, but you have recursion in your system
<snhmib> :(
_andre has joined #ocaml
<snhmib> here is my new attempt: http://pastebin.com/x8BfDHxZ , but ocaml says "Type bar is not a subtype of foo"
<snhmib> which is obviously insane because it says INHERIT FOO RIGHT THERE
* snhmib pulls hairs
antkong has joined #ocaml
<malc_> snhmib: have you actually tried to compile that snippet (exactly as pastebined)?
<Drup> snhmib: you forgot the definition of mkfoo
<mrvn> How would you define that? let rec mkfoo ... and class bar = ... doesn't seem right?
<snhmib> malc_: i tried to load it in ocaml interpreter
<mrvn> snhmib: you probably tried multiple times and then class bar used an older mkfoo
<snhmib> o.O
<mrvn> and that mkfoo used an older class foo which isn't a subtype of the new class foo
<mrvn> snhmib: Do I see it right that you want a base class that has several children but is also a factory for all those children?
Algebr` has quit [Ping timeout: 250 seconds]
<snhmib> yes
<snhmib> malc_: thanks :D i get a more sane error now
<snhmib> how do can i define a function that uses a class and a class that uses that function ?
<snhmib> right now i either get "unbound function" or "unbound class" errors
<mrvn> snhmib: recursive modules, which is rather ugly. But I can't think of another way.
<snhmib> how does that work? i make a module A with the function and a module B with the classes or something?
<mrvn> yep. And for both you have to specify the type of the module
<mrvn> you could lift the recursion, passing constructors for all the classes as argument to mkfoo.
j0sh has joined #ocaml
j0sh is now known as Guest58127
<malc_> snhmib: zonder die
<mrvn> snhmib: keep is as method in the class: http://paste.debian.net/404966/
noplamodo has quit [Remote host closed the connection]
noplamodo has joined #ocaml
ontologiae has quit [Ping timeout: 252 seconds]
<snhmib> ah that's nice! thanks :D
<mrvn> opening the recursion would allow you to keep the classes in seperate files and then have one file that defines mkfoo and all the final classes.
Sim_n has quit [Read error: Connection reset by peer]
pgiarrusso has joined #ocaml
mettekou has joined #ocaml
rand__ has quit [Ping timeout: 252 seconds]
mettekou has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<Nazral> 42 let s = file.XmlHttpRequest.content ^ "\ntest" in
<Nazral> 43 let ss = String.sub.(of_string ~start:3 ~stop:10 s) in
<Nazral> shouldn't that work .
<Nazral> ?
kushal has quit [Quit: Leaving]
haxor has quit [Quit: http://www.kiwiirc.com/ - A hand crafted IRC client]
haxor has joined #ocaml
ggole has joined #ocaml
pgiarrusso has quit [Quit: pgiarrusso]
malc_ has quit [Remote host closed the connection]
mettekou has joined #ocaml
antkong has quit [Quit: antkong]
abbiya has joined #ocaml
seshachalam_ has joined #ocaml
abbiya has quit [Ping timeout: 240 seconds]
rand__ has joined #ocaml
<flux> I don't think so..
<flux> do you mean String.sub (of_string ..) instead?
<flux> or maybe String.Sub.(..), maybe Core has such a module?
<flux> or maybe String.sub is a value that can be indexed by a local indexing operator that takes strings, but I somehow doubt that
<Nazral> flux: I'm trying to use astring
<Nazral> I'm not using core (at least I think)
<flux> astring? a string?
<flux> what libraries do you use?
<Nazral> astring
<Nazral> this one
<flux> well, String.sub is a function
<flux> so String.sub.(xxx) makes no sense
<flux> String.Sub.(xxx) would make sense, because that would locally open the String.Sub module and evalute xxx in that scope
<flux> it seems like you are trying to do String.Sub.(..)
tane has quit [Quit: Verlassend]
<flux> but actually in this case you could just write String.Sub.of_string ~start..
<flux> no need to use the .(xx)-syntax
<Nazral> frak
<Nazral> thanks
<Nazral> I didn't realize that I was missing the capital
<Nazral> so I can even use String.Sub.v directly, with the options
<Nazral> perfect :)
seshachalam_ has quit [Ping timeout: 244 seconds]
seshachalam_ has joined #ocaml
malc_ has joined #ocaml
Haudegen has quit [Ping timeout: 240 seconds]
AlexRussia has joined #ocaml
julien_t has quit [Ping timeout: 244 seconds]
JacobEdelman_ has joined #ocaml
foolishmonkey has quit [Quit: Leaving]
foolishmonkey has joined #ocaml
larhat has joined #ocaml
julien_t has joined #ocaml
Haudegen has joined #ocaml
<Nazral> How can I make a reactive node list with React ?
<Nazral> instead of div [R.pcdata stuff] something like div [R.list stuff]
<Drup> the RList module, in particular
<Drup> that's the one that is used for lists in tyxml_js
<Nazral> Ok, so it's not the normal React package ?
hcarty1 has joined #ocaml
<Drup> It builds on react
seshachalam_ has quit [Ping timeout: 276 seconds]
antkong has joined #ocaml
seshachalam_ has joined #ocaml
copy` has joined #ocaml
jeffmo has joined #ocaml
jeffmo has quit [Client Quit]
spirty has joined #ocaml
spirty has quit [Client Quit]
spirty has joined #ocaml
warp has quit [Ping timeout: 248 seconds]
struk|desk|away is now known as struk|desk
eeks_ has joined #ocaml
tennix has quit [Ping timeout: 252 seconds]
spirty has quit [Remote host closed the connection]
spirty has joined #ocaml
hxegon has joined #ocaml
spirty has quit [Client Quit]
seshachalam__ has joined #ocaml
seshachalam_ has quit [Ping timeout: 252 seconds]
Haudegen has quit [Remote host closed the connection]
<Nazral> Drup: weren't there a "RList.make_from" function at some point ?
<Drup> It was renamed, where did you see it ?
<Drup> Where does that comes from ? ^^'
<Nazral> Armael (he is on #ocaml-fr)
<Drup> I see
<Nazral> I think I generate the data I want to put in my pre [] correctly
<Nazral> but I don't know what to write in the []
Haudegen has joined #ocaml
<Drup> It's called RList.from_signal now, iirc
darkf has quit [Quit: Leaving]
<Nazral> ah... well then it means I'm not constructing the data properly :p
Haudegen has quit [Remote host closed the connection]
<Nazral> because I tried it and had a big scary error
<Drup> So, in tyxml_js, there are two kinds of constructors
<Drup> the normal ones (module Html5) that take a list of things
Haudegen has joined #ocaml
julien_t has quit [Ping timeout: 240 seconds]
<Drup> and the reactive one (module R), that take a reactive list of things
<Drup> what do you have as input ?
jwatzman|work has quit [Quit: jwatzman|work]
<Nazral> I have a list of span []
<Drup> Is it reactive ?
<Nazral> http://paste.debian.net/hidden/1adcae81/ I generate it with the reveal function, line 28, while updating the list line 40
<Nazral> the pre in which I put the span are reactive, but the span themselves no
<Nazral> the pre is reactive*
<Drup> ok, then you should use R.pre
Haudegen has quit [Ping timeout: 244 seconds]
<Nazral> Error: The type of this expression, (_[< Html5_types.pre_content_fun > `Span ] as 'a) R.elt ReactiveData.RList.data React.signal * (?step:React.step -> 'a R.elt ReactiveData.RList.data -> unit), contains type variables that cannot be generalized
<Nazral> _[< Html5_types.pre_content_fun > `Span ] < shouldn't it be something more general than `Span there ?
<Drup> It is more general than `Span
<Drup> So, it's a bit delicate to explain
<Drup> but you can solve it by putting a type annotation to avoid the type variable
<Drup> let (stuff, set_stuff) = S.create ([] : Html5_types.pre_content_fun elt list)
dario1 has joined #ocaml
<Drup> (which reads as "a list of elements that can be put inside a Pre")
pgiarrusso has joined #ocaml
seshachalam__ has quit [Remote host closed the connection]
<Nazral> it works ! thanks !
<Nazral> So if I understand well is that the declaration was too general to be properly infered ?
<Drup> It was properly infered
<Drup> but it contains polymorphism
<Drup> in this case, the polymorphism is not harmful, even in presence of mutation, but the type system doesn't really know it. See https://realworldocaml.org/v1/en/html/imperative-programming-1.html#the-value-restriction
<Drup> This could also be solved by not putting the signal at the toplevel.
<Nazral> Where should I put it ?
<Nazral> I mean, in an ideal scenario ?
<Drup> It depends ^^
struk|desk is now known as struk|desk|away
pgiarrusso has quit [Quit: pgiarrusso]
pgiarrusso has joined #ocaml
dario1 has quit [Quit: Konversation terminated!]
nojb has quit [Quit: Leaving]
pgiarrusso has quit [Client Quit]
th5 has joined #ocaml
<octachron> Drup, question: is the type parameter 'a in 'a R.elt purely a phantom type?
mcc has joined #ocaml
malc_ has quit [Quit: ERC (IRC client for Emacs 25.0.50.2)]
<Drup> yes
<octachron> then I have a related question, is there any case where generalizing a phantom type can be unsound?
FreeBirdLjj has joined #ocaml
<flux> nazral, if you don't intend to export the symbol to other modules, you can fix those issues by putting an empty modulename.mli file alongside the implementation
NingaLeaf has quit [Quit: Leaving]
<octachron> mimicking the argument for the relaxed value restriction +_'a t can be generalised to +'a t because in any context where '_a appears, it can be replaced by ⊥
FreeBird_ has quit [Ping timeout: 255 seconds]
<ggole> It would be nice if there were a type printer that showed variance annotations
igoroliveira has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 240 seconds]
<octachron> the replaceable by ⊥ argument seems to be even more true for type variable appearing in phantom position than for type appearing in covariant position
<Drup> octachron: it might violate the invariants internal to the type/API, though
tennix has joined #ocaml
<octachron> ggole, I had a branch of the compiler typed tree printer that printed the variance annotation, would you be interested?
<octachron> Drup, you mean case where the value restriction is helpful and not utterly annoying? Any examples?
julien_t has joined #ocaml
<ggole> octachron: sure... is it on opam or would I have to build the compiler?
aantron has joined #ocaml
<Drup> -dtypedtree is quite terrible, it would be a good project to improve it
<octachron> ggole, it is nowhere right now, only in an out-of-sync private branch
MercurialAlchemi has quit [Ping timeout: 248 seconds]
<ggole> octachron: hmm, tempting, but I'd probably better just work on what I'm doing (I've procastinated enough as it is).
JacobEdelman_ has quit [Quit: Connection closed for inactivity]
kushal has joined #ocaml
haxor has quit [Quit: http://www.kiwiirc.com/ - A hand crafted IRC client]
rossberg has quit [Ping timeout: 240 seconds]
<aantron> Drup: pa_tyxml looks awfully simple, does it generate untyped (in the sense of tyxml HTML and SVG types) trees? at a glance, i cant find code that is specific to the kind of elements that are actually being represented
<aantron> except for a few small match expressions that dont seem to do it all
<Drup> aantron: It .. cheats
<Drup> It uses the unsafe combinators and give it a type at the toplevel
<aantron> yeah, thats what i assumed
<aantron> okay. and the ppx actually uses the types throughout the trees. i presume you are happy with that :)
jwatzman|work has joined #ocaml
<Drup> I'm much happier with that, yes
<aantron> i was just surprised to discover late last night that the ppx code is longer than the camlp4 code
<Drup> I'm not surprised
Sorella has joined #ocaml
<aantron> well, it makes sense given the above information
rossberg has joined #ocaml
johnf_ has quit [Remote host closed the connection]
please_help has joined #ocaml
<please_help> I'm trying to write some bindings with ctypes, and I get "Error: Unbound type constructor uint64_t" when trying to use that type. I have "open PosixTypes" (I assume it's supposed to be defined in there)
orbifx has joined #ocaml
<adrien> I don't know ctypes but uint64_t is not a "posix types", it's C99
<please_help> [u]int{8|16|32}_t are posixtypes even though they are part of the c99 ISO standard as well, so they could be defined in the posixtypes module.
<please_help> (uint64_t is not posix though)
ygrek_ has joined #ocaml
<orbifx> Wouldn't it be neat if one could do: Float.(x + y * z) ??
<orbifx> Or can they?
<aantron> with the suitable operators
<aantron> dont know how old those docs are. dont use batteries or know their version numbers.. let me look again
<copy`> orbfix: That's how I use it mostly
<orbifx> copy`: which module? Batteries, like aantron is saying?
<copy`> Core
ygrek_ has quit [Ping timeout: 252 seconds]
MercurialAlchemi has joined #ocaml
<orbifx> JaneStr's equivalent of batteries?
<copy`> Yep
<orbifx> Kk
<orbifx> Thanks
kushal has quit [Quit: Leaving]
<aantron> Drup, if you have already decided to merge https://github.com/ocsigen/tyxml/pull/88, it would save me 10 minutes of work if done soon.. but if you dont want to merge it, thats fine. ill just write that extra function that i need to write to support those attributes :)
<aantron> ok thanks
<Drup> :]
<Drup> :press the button:
Algebr` has joined #ocaml
<aantron> fastest merge in the west
<Drup> I like to merge things, it's pleasing.
pierpa has joined #ocaml
yunxing_ has quit [Ping timeout: 240 seconds]
haxor has joined #ocaml
haxor has quit [Client Quit]
<please_help> is there no way to convert an array to a c pointer without going array -> list -> carray -> pointer?
<Drup> ocaml arrays are not fixed in memory, so you have to go through carrays anyway
<please_help> I would have at least liked to see a CArray.of_array or something
<Drup> Add it :)
<please_help> ;)
<ggole> Bigarrays are C friendly, you could use one of those
mettekou has quit [Read error: Connection reset by peer]
<please_help> I have to pass the dimensions of the bigarray which I'm using to the C function I'm calling, so I convert the Bigarray.genarray.dims int array toward a uint64_t pointer.
<companion_cube> you can use Bigarray.Array1
Haudegen has joined #ocaml
<please_help> That wouldn't change anything since the shape of the array is necessary.
<hcarty1> please_help: You can also use CArray.make to create your carray, then Array.iteri + CArray.set to fill the carray with the contents of your array without going through a list.
<please_help> good point
hcarty1 is now known as hcarty
seangrove has joined #ocaml
tane has joined #ocaml
slash^ has joined #ocaml
kushal has joined #ocaml
haxor has joined #ocaml
haxor has quit [Client Quit]
Haudegen has quit [Ping timeout: 244 seconds]
kdas__ has joined #ocaml
freehck has quit [Quit: rcirc on GNU Emacs 24.4.1]
kushal has quit [Ping timeout: 244 seconds]
kdas__ is now known as kushal
kushal has quit [Changing host]
kushal has joined #ocaml
shinnya has joined #ocaml
octachron has quit [Quit: Leaving]
mettekou has joined #ocaml
hcarty has quit [Ping timeout: 248 seconds]
antkong has quit [Quit: antkong]
reynir1 has joined #ocaml
inr_ has joined #ocaml
deavidsedice has joined #ocaml
ousado_ has joined #ocaml
julien__ has joined #ocaml
Mercuria1Alchemi has joined #ocaml
jerith_ has joined #ocaml
j_king_ has joined #ocaml
ski_ has joined #ocaml
Maxdaman1us has joined #ocaml
eagleflo_ has joined #ocaml
hnrgrgr_ has joined #ocaml
zxqdms_ has joined #ocaml
gustav__1 has joined #ocaml
Nazral_ has joined #ocaml
Reventlo1 has joined #ocaml
zoobab_ has joined #ocaml
Khady_ has joined #ocaml
gargawel_ has joined #ocaml
<seangrove> Has e.g. window.location been bound/wrapped already in jsoo?
<aantron> yes
Nazral has quit [Disconnected by services]
<seangrove> \o/
stomp_ has joined #ocaml
teiresia1 has joined #ocaml
Haudegen has joined #ocaml
Nazral_ is now known as Nazral
<seangrove> Hrm, I guess that makes sense. I didn't expect it to be under Dom_html initially
__rlp_ has joined #ocaml
<seangrove> I'm trying to get the query params
teiresia1 has quit [Changing host]
teiresia1 has joined #ocaml
teiresias has quit [Disconnected by services]
stux|RC has joined #ocaml
teiresia1 is now known as teiresias
<aantron> yeah, the jsoo organization of things takes a bit of getting used to, but it makes sense
jave_ has joined #ocaml
nullcatxxy_ has joined #ocaml
tumdum_ has joined #ocaml
<seangrove> This obviously doesn't work: Printf.printf "currently at: %s" (Html.window.location).href
MercurialAlchemi has quit [*.net *.split]
julien_t has quit [*.net *.split]
maker has quit [*.net *.split]
al-maisan has quit [*.net *.split]
djellemah has quit [*.net *.split]
ousado has quit [*.net *.split]
MasseR has quit [*.net *.split]
zoobab has quit [*.net *.split]
deavid has quit [*.net *.split]
Khady has quit [*.net *.split]
asdf12z_ has quit [*.net *.split]
swistak35 has quit [*.net *.split]
stux|RC-only has quit [*.net *.split]
j_king has quit [*.net *.split]
gargawel has quit [*.net *.split]
Reventlov has quit [*.net *.split]
eagleflo has quit [*.net *.split]
asmanur has quit [*.net *.split]
jerith has quit [*.net *.split]
jave has quit [*.net *.split]
Ravana has quit [*.net *.split]
reynir has quit [*.net *.split]
hnrgrgr has quit [*.net *.split]
SimonJF has quit [*.net *.split]
pdewacht has quit [*.net *.split]
nullcatxxx_ has quit [*.net *.split]
Maxdamantus has quit [*.net *.split]
zxqdms has quit [*.net *.split]
stomp has quit [*.net *.split]
gustav___ has quit [*.net *.split]
inr has quit [*.net *.split]
__rlp has quit [*.net *.split]
ski has quit [*.net *.split]
tumdum has quit [*.net *.split]
swistak35_ has joined #ocaml
al-maisan_ has joined #ocaml
<Drup> Html.windo##.location##.href
mettekou has quit [Ping timeout: 244 seconds]
<Drup> Js object fields, not module fields ;)
ygrek_ has joined #ocaml
<seangrove> Ahh, yes
<seangrove> So much to keep straight
pdewacht has joined #ocaml
<seangrove> And ## is the not-deprecated syntax, right?
Ravana has joined #ocaml
SimonJF has joined #ocaml
asmanur has joined #ocaml
<seangrove> And how do I print out a Js.js_string? Printf.printf "currently at: %s\n" Html.window##.location##.href has the incorrect type
<aantron> Firebug.console##log
<Drup> Or just make it a string
sooheon has joined #ocaml
<aantron> Js.to_string :)
<Nazral> Is there a way to define a function depending on a variable that doesn't exist yet ? For example, I want to define a function with global scope and this function will always depend on a node that doesn't exist yet in the dom but that will exist
<seangrove> Bah, makes sense!
<seangrove> `No errors` - so nice
<Nazral> I'm thinking about using a closure and Lwt but I'm not sure how
<Drup> Nazral: can't you bind the function later, when the node actually exists ?
<ggole> Nazral: you can close over an option ref that is populated after the closure is constructed
djellemah has joined #ocaml
<seangrove> And before I start doing this myself, anything in js_of_ocaml that can give me query params easily?
<aantron> Nazral: you can also look up this node and memoize it when the function is called (equivalent to what ggole said actually)
MasseR has joined #ocaml
<ggole> Lazy.from_fun is the easy way to do that
maker has joined #ocaml
jwatzman2 has joined #ocaml
<Nazral> ok thank you all, I'm going to look into that !
jwatzman|work has quit [Ping timeout: 240 seconds]
malc_ has joined #ocaml
<ggole> Like that
reynir1 is now known as reynir
yunxing has joined #ocaml
<Nazral> ggole: thanks
shinnya has quit [Ping timeout: 250 seconds]
<seangrove> Bah, is Str not available in jsoo?
<aantron> nope.
<seangrove> Hrm, so what's my best bet for splitting a string then?
<seangrove> (ideally not using js for now)
<Algebr`> seangrove: I would just use JS's own Regexp
cyraxjoe has quit [Remote host closed the connection]
<seangrove> Ok, suppose I can do that
<seangrove> Makes much more difficult to test in utop though
<aantron> some helper functions are here http://ocsigen.org/js_of_ocaml/2.7/api/Js
<aantron> yeah
<Algebr`> for query params I thought there's like decodeURI encode, and their components too
cyraxjoe has joined #ocaml
<Algebr`> would be a nice feature in utop to maybe call out to node or somethign like that
wiredsister has joined #ocaml
<Algebr`> or we could embed javascriptcore
<Algebr`> heh
<Drup> You can create your own with your custom libraries with jsoo_mktop
<seangrove> I'm getting `Unbound module Js.Regexp`, although plenty of other Js. stuff works
<aantron> its just Regexp
* seangrove sighs
<Algebr`> seangrove: yea that was unexpected for me too
<seangrove> aantron: What's the trick for figuring that out?
<aantron> look in the left bar in the API docs
<Algebr`> go to ocisgen docs and look on sidebar on the left
<aantron> all those modules are on the same level
<aantron> Js is on the same level as Regexp, so they are both top level
<seangrove> Ahh, ok
<aantron> Drup: this thing is pretty sick
<aantron> however despite the anchor in the URL, it says: OCaml version 4.01.0
<Drup> (The tyxml demo is very cool)
spirty has joined #ocaml
jerith_ is now known as jerith
rand__ has quit [Quit: leaving]
julien__ has quit [Ping timeout: 276 seconds]
Algebr` has quit [Ping timeout: 252 seconds]
spirty has quit []
gustav__1 is now known as gustav___
kushal has quit [Ping timeout: 244 seconds]
kushal has joined #ocaml
spirty has joined #ocaml
orbifx has quit [Quit: AtomicIRC: The nuclear option.]
tcpc has joined #ocaml
sepp2k has quit [Quit: Leaving.]
sepp2k has joined #ocaml
Kakadu has quit [Quit: Page closed]
seangrove has quit [Ping timeout: 240 seconds]
sgnb has quit [Remote host closed the connection]
<Nazral> is there a way to access the pcdata of an element defined with tyxml using tyxml ?
<Nazral> or do I have to do let el = Dom_html.getElementById "stuff" in let txt = Js.to_string el##.textContent ?
sgnb has joined #ocaml
spirty has left #ocaml [#ocaml]
jwatzman2 has quit [Ping timeout: 240 seconds]
<Drup> the later
max3 has joined #ocaml
<max3> are there mutable data structures in ocaml?
<aantron> max3: yes
<aantron> for example, array
<Drup> Nazral: but tbh, the best solution is ... to not go through html. Just use ocaml data structures to store the text
<max3> are ref and array the only ones?
teknozulu has joined #ocaml
<Drup> You can build any mutable datastructure you want
<max3> wooooooooooo
<aantron> ^, and there are also Buffer and Bytes in the stdlib
<Nazral> Drup: mhh I'l not sure how to do that. Right now, I'm having a pcdata that has to be modified with react and through events also (keyboard)
<aantron> not to mention language support for the "mutable" keyword for record fields
<Nazral> on a contenteditable
<Drup> (which does not mean than you can mutate any datastructure ! Some are define immutable)
<max3> that's fine
<aantron> Hashtbl is also mutable
octachron has joined #ocaml
<Drup> Nazral: Is the pcdata stored somewhere in ocaml ?
<Drup> (A map, bound to a variable, in a signal ...)
<Nazral> in a signal
<max3> i wish i could have the power of lisp with mutable data structures
<Drup> Nazral: Then just access the value of the signal
<Drup> and you have your pcdata.
Haudegen has quit [Ping timeout: 244 seconds]
<Nazral> All right, thanks
Reventlo1 has quit [Quit: leaving]
Reventlov has joined #ocaml
kushal has quit [Quit: Leaving]
slash^ has quit [Read error: Connection reset by peer]
max3 has quit [Ping timeout: 252 seconds]
sooheon has quit [Remote host closed the connection]
Haudegen has joined #ocaml
hcarty has joined #ocaml
octachron has quit [Quit: Leaving]
Haudegen has quit [Ping timeout: 240 seconds]
sillyotter has joined #ocaml
sillyotter has quit [Client Quit]
Kakadu has joined #ocaml
<Guest58127> companion_cube: in sequence, is there a way to 'sum' up two sequences , eg 'a t -> 'b t -> ('a, 'b) t2 without going through a O(n^2) product? (assuming both sequences are the same length)
Guest58127 is now known as j0sh
nicoo has quit [Remote host closed the connection]
<aantron> i hope :p
<Algebr> what directive is needed to make #require work again, with plain ocaml, something like #load "topfind" or whatever
nicoo has joined #ocaml
<Kakadu> #use "topfind";;
<aantron> #use "topfind";;
<aantron> :)
<Algebr> yes, right right thanks, need to make a cheatsheet for these directives. Also aantron LOVE that PR
<aantron> thank you :)
hxegon has quit [Ping timeout: 244 seconds]
ggole has quit []
<j0sh> companion_cube: came up with https://gist.github.com/j0sh/0c6cdc1372370f79db23 which requires two extra passes over the input and O(n) extra space, i wonder if there's a nicer way
nicholasf has joined #ocaml
<Drup> aantron: do we agree than when you say "errors generated by Markup.ml" you mean errors that you can recover from ?
<Drup> (Are then even errors that are really fatal, when parsing html ?)
teknozulu has quit [Ping timeout: 252 seconds]
<lyxia> j0sh: where does this Sequence.t type come from?
jeffmo has joined #ocaml
asdf12z__ has joined #ocaml
<lyxia> thanks
_andre has quit [Quit: leaving]
<Algebr> I was thinking about making a special thing for OS X, like a OS X app desktop app that collects all the of docs that are make, aka the HTML docs, and is a singular place to check for OCaml docs
<Algebr> that are available*
<Algebr> because right now there is no coherent singular place to put all docs, people either don't make them at all or dump them on their websites, etc.
Mercuria1Alchemi has quit [Ping timeout: 276 seconds]
<Algebr> or maybe reuse code from ocp-browser, aka the reading of the cmis, and lift it to a prettier GUI rather than terminal app
teknozulu has joined #ocaml
Maxdaman1us is now known as Maxdamantus
nuuit has quit [Remote host closed the connection]
nuuit has joined #ocaml
wiredsister has quit [Remote host closed the connection]
teknozulu has quit [Ping timeout: 252 seconds]
mettekou has joined #ocaml
alexst has joined #ocaml
alexst has quit [Client Quit]
sepp2k has quit [Quit: Leaving.]
max3 has joined #ocaml
<aantron> Algebr: this kind of thing is either my next project, or the one after, but minus the OS X app part (at a basic level). presumably you could build an OS X app on top of that
teknozulu has joined #ocaml
<aantron> Drup: thats correct. the Markup.ml errors are errors that an HTML parser is required to report, and all HTML errors are recoverable
<aantron> i may already have a few errors that are not required, and i definitely plan to add some (like deprecated element errors). again recoverable
<Drup> right
<aantron> Drup: im going to add commits to the PR during review, to be squashed later, before merge. are you fine with this workflow?
<apache2> I have a question about `cmdliner`: I'd like to be able to pass several --name [NAME] and get a list of all the names. --name is an optional parameter (that is, it appears 0 or more times). is this currently possible?
lmaury has quit [Read error: Connection reset by peer]
<Drup> aantron: sure
<Drup> you don't even have to squash
<Drup> The important part is that the commit log is clean
<aantron> it wont be that clean, i would prefer to squash. i dont like generating a ton of commits for one logical change, but if i squash as i go, its going to be very unpleasant to review using the web ui
<aantron> so ok :)
<smondet> apache2: yes it is possible with `Arg.opt_all`
<apache2> smondet: thanks!
malc_ has left #ocaml ["ERC (IRC client for Emacs 25.0.50.2)"]
<aantron> Drup: i am puzzled by this statement in the context it was made it: "(type systems are not know to bend gracefully when constrained)" what are you referring to? also what is the implication of the reference to the comment in #68?
<aantron> made in*
<Drup> aantron: I can't turn typechecking errors into warnings inside html code :D
<Drup> (At least, not in OCaml)
<aantron> but you would like them to be warnings, is that what you mean?
<Drup> I would like to have the option, certainly
<aantron> so given that you would like the tyxml errors to be changeable to warnings, it is better to have that possibility for at least the subset of new errors where it is possible (from the parser)..
<Drup> aantron: You have to imagine that into it's context
<Drup> its*
<aantron> you mean usage for arbitrary html? if so, i thnk i understand
<Drup> This syntax extension is here for almost entierly one reason : being able to take pieces of html from the web and put them in your application
<aantron> i just wanted to make sure i get your comment, it seemed cryptic at first
<aantron> right
<aantron> but it does also make it easier to write tyxml
<aantron> you dont have to look up how to pass stuff to an img tag for example
<Drup> (or, alternatively, for #68, allowing to have this whole template thing)
<Drup> Given merlin, that's not a great argument
<aantron> yeah but not everyone uses merlin. i dont
<Drup> Not even ocp-index ?
<aantron> fair enough. but one thing about HTML errors is that they are for relatively "severe" situations. for example <p>foo<p>bar is not an error
<aantron> (i do agree with making this toggleable, just saying)
<aantron> i use ocp-index occasionally
<Drup> Oh, right
<Drup> I though errors where just for everything that is not strictly compliant
<aantron> <p>foo<p>bar is strictly compliant.. to HTML :)
<aantron> of course not XHTML
<Drup> yeah
<Drup> The default should be an error, clearly
<Drup> Or maybe a warning, I'm not sure
<Drup> And there should be an option to silence the whole thing
<aantron> im really fine either way, just informing. it is easy to alter this as many times as necessary before merging, and even after
<Drup> Yes
<aantron> yeah. but the "microformat" parsers that have to construct parse trees are always going to generate errors if they cant. obviously
<aantron> (for attribute values)
<Drup> Yes
<Drup> (But that's almost already a type error)
badon has quit [Disconnected by services]
badon_ has joined #ocaml
badon_ is now known as badon
<Algebr> aantron: why do you not use merlin
<aantron> couldnt get the sublime plugin working and didnt want to spend any more time on it.. and lack of merlin doesnt seem to impede my productivity very much, though it would be nice
<Drup> It's the kind of things you never realize you were missing until you taste it
<hannes> I use merlin mainly for 'jump to definition' and 'show type'... but getting errors on saving is very nice
<hannes> (had to remap keys to have M-. as jump-to-definition, the same as slime does) :)
teknozulu has quit [Ping timeout: 244 seconds]
th5 has quit [Ping timeout: 250 seconds]
<aantron> ill give it a try. should have some downtime soon with this PR out :)
<hannes> (but I used 2 years no merlin, and was pretty happy with that)
hcarty has quit [Ping timeout: 240 seconds]
<Algebr> I thinking a merlin plugin for atom needs to be made
<Algebr> the github editor
<aantron> i actually downloaded atom just because its merlin plugin supposedly worked. still using sublime
<aantron> or whatever plugin it has. dont quote me
<Algebr> I wasn't aware that there was a publically available one...although I know someone might be working on it
mettekou has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<Algebr> ideally using ocaml-nodejs of course :)
<Drup> I recently got merlin working back on my branch of the compiler, jump to definition is life saving
mettekou has joined #ocaml
<Algebr> love jump to def, I mainly use C-c C-t and C-c C-l,
<Algebr> and the new doc popup is awesome too
<Maxdamantus> <p/foo/<p/bar/
<Maxdamantus> Better.
<Maxdamantus> (that's valid HTML4 Strict)
shinnya has joined #ocaml
<hannes> Algebr: which doc-popup?
<aantron> Maxdamantus: i guess despite HTML5's claim to be kind of backwards compatible, that isnt valid HTML5
nicholasf has quit []
<copy`> Can we use doc-popup in vim too?
<Maxdamantus> I'm not sure it's valid HTML4 Transitional even.
<Maxdamantus> It might only be HTML4 Strict.
<aantron> what is it supposed to mean anyway?
<Algebr> copy`: I think its something that is working with just company-quick-help at the moment
<Maxdamantus> <p>foo</p><p>bar</p>
<aantron> some SGML-inspired voodoo going on? trying to avoid a trip into the HTML4 docs :)
antkong has joined #ocaml
<Drup> Algebr ( def` ) : Why is this not enabled by default ?
mcc has quit [Quit: Connection closed for inactivity]
mxv has joined #ocaml
<Maxdamantus> Current versions of Chromium and Firefox don't seem to support it though.
<Maxdamantus> but: This document was successfully checked as HTML 4.01 Strict!
<Maxdamantus> It seems to confuse the warning generator on validator.w3.org too.
<aantron> i think modern browsers have moved to implementing the html5 parser as exactly as possible, judging by messages i saw in their issue trackers. so they should complain about this,a s does markup.ml
<aantron> it produces no output but 5 errors, including unexpected end of input in tag
hxegon has joined #ocaml
yunxing has quit [Remote host closed the connection]
<asdf12z__> going to learn ocaml... and best way to learn is to use it right? i wonder if there are wrappers for win32 api ?
yunxing has joined #ocaml
<Algebr> Drup: I think its cause it requires another thing, company-quickhelp, not sure, ought to be :)
teknozulu has joined #ocaml
<Algebr> asdf12z__: if you're learning OCaml then dealing with low level C bindings for win32 is not gonna be fun
<Drup> Algebr: it doesn't require it
<Drup> it's better with quickhelp
<Algebr> asdf12z__: can you use a unix system? Will make learning and getting stuff done easier.
<Algebr> yes, much much better.
<asdf12z__> Algebr: yea, i am just thinking about stuff i can do with ocaml and have a learning project while i read realworldocaml.org
yunxing has quit [Ping timeout: 240 seconds]
<Algebr> asdf12z__: are you in the bay area?
<asdf12z__> no i'm not, why?
<Algebr> ah, I am doing OCaml office hours to help newcomers get their projects up and running.
<aantron> asdf12z__: i used ocaml on windows for a long time back in the day, but i dont think the situation in terms of win32 bindings has changed much. as long as you are using it for command-line programs, it should be easy. otherwise, you will have difficulty learning both basic ocaml and its ffi or ctypes simultaneously
<aantron> though i think opam doesnt install on win32. whats the latest status?
<Drup> Algebr: how do I show the help/doc thingy on a given identifier ?
<Algebr> aantron: I think this is the best right now https://www.typerex.org/ocpwin.html
eeks_ has quit [Quit: Textual IRC Client: www.textualapp.com]
<Algebr> Drup: that I don't know how, I was using it for when scorlling through potential auto complete hits. would love to know as well
silver has quit [Read error: Connection reset by peer]
<Drup> It's the function merlin-document
<Drup> I only have to find a new keybinding for it
<Algebr> haha, I was literally typing the "need a new keybinding" message as well
<Maxdamantus> Lies! He's actually just tunnelling to the outside system that's running VirtualBox.
<copy`> :MerlinDocument works on vim, nice
<Algebr> all hail def.
<Drup> C-d is used by destruct and C-h is for emacs help :(
<Drup> :emacs problems:
<Algebr> C-C C-d?
pgiarrusso has joined #ocaml
<Drup> Yes, I was talking after a C-c
<Algebr> Actually somehwat related to this ticket: https://github.com/the-lambda-church/merlin/issues/448 would be nice if just leaving the point on top of an identifier autopmatically brought up the quickhelp doc in the mini buffer
<Drup> in the caml-mode, there is a feature to have the minibuffer showing the type of thing under the mouse cursor, you can move your mouse around
<Drup> it's not very useful
<Drup> (it works with annot files, of course)
<Algebr> I end up opening a second buffer just for merlin-types
<Algebr> and C-c C-t should work in a merlin-types buffer but doesn't.
<Algebr> lots of elisp oppurtunity :)
<Nazral> How are input events handled with content editable elements ?
<Nazral> because I can't do a To_dom.of_input
<Algebr> are you trying to make like a wysiwyg editor?
tane has quit [Quit: Verlassend]
<Nazral> nope
<Nazral> just playing a bit with css
<Nazral> I'm actually trying to recode my website with jsoo
yunxing has joined #ocaml
mettekou has quit [Ping timeout: 240 seconds]
foolishmonkey has quit [Quit: Leaving]
Kakadu has quit [Remote host closed the connection]
mxv has quit [Ping timeout: 255 seconds]
Haudegen has joined #ocaml
max3 has quit [Ping timeout: 260 seconds]
<Algebr> I tried doing something similar, like make a site with jsoo and using org-mode files as blog posts.
<Algebr> Nazral: