<companion_cube>
whitequark: [%pp] doesn't exist, is it by design?
arj has quit [Ping timeout: 255 seconds]
malc_ has joined #ocaml
madroach has quit [Ping timeout: 250 seconds]
ollehar has quit [Quit: ollehar]
madroach has joined #ocaml
<companion_cube>
I'd like to remove the dependency on camlp4 for every mirage project ;_;
<companion_cube>
but that mostly means removing sexplib
MrScout_ has joined #ocaml
NoNNaN has quit [Remote host closed the connection]
NoNNaN has joined #ocaml
MrScout has quit [Ping timeout: 258 seconds]
natrium1970 has joined #ocaml
<natrium1970>
companion_cube: I have a question about a comment you made the other day: “ if you are motivated, it would be very nice to adapt Zarith to a pure ocaml implementation of bignums”
MrScout_ has quit [Ping timeout: 245 seconds]
choeger_tu has joined #ocaml
jwatzman|work has quit [Quit: jwatzman|work]
arj has joined #ocaml
arj has quit [Ping timeout: 244 seconds]
jonludlam has quit [Quit: Coyote finally caught me]
rand000 has quit [Quit: leaving]
ousado has quit [Ping timeout: 258 seconds]
pierpa`` has joined #ocaml
pierpa` has quit [Ping timeout: 244 seconds]
arj has joined #ocaml
pierpa has quit [Ping timeout: 272 seconds]
arj has quit [Ping timeout: 245 seconds]
badkins has joined #ocaml
AltGr has joined #ocaml
yomimono has quit [Ping timeout: 265 seconds]
yomimono has joined #ocaml
Simn has quit [Quit: Leaving]
seanmcl has joined #ocaml
choeger_tu has quit [Quit: choeger_tu]
manud_ has quit [Quit: Be back later ...]
badon has quit [Remote host closed the connection]
shinnya has quit [Ping timeout: 255 seconds]
arj has joined #ocaml
seanmcl has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
arj has quit [Ping timeout: 265 seconds]
badon has joined #ocaml
natrium1970 has quit [Quit: natrium1970]
darkf has joined #ocaml
lopex has quit [Quit: Connection closed for inactivity]
<whitequark>
companion_cube: what do you mean by [%pp]?
darkf_ has joined #ocaml
seanmcl has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
darkf has quit [Ping timeout: 258 seconds]
darkf has joined #ocaml
darkf_ has quit [Ping timeout: 258 seconds]
arj has joined #ocaml
chambart has quit [Ping timeout: 256 seconds]
struk_at_dtut has quit [Ping timeout: 264 seconds]
arj has quit [Ping timeout: 240 seconds]
struktured_ has quit [Ping timeout: 258 seconds]
struktured_ has joined #ocaml
struk has joined #ocaml
bytbox has quit [Remote host closed the connection]
q66 has quit [Quit: Leaving]
boogie has quit [Remote host closed the connection]
MrWuffles has joined #ocaml
SomeDamnBody has joined #ocaml
<SomeDamnBody>
how can I test if a string contains a null byte?
arj has joined #ocaml
<malc_>
# String.contains "moo\000" '\000';;
<malc_>
- : bool = true
arj has quit [Ping timeout: 272 seconds]
seanmcl has joined #ocaml
seanmcl has quit [Client Quit]
arj has joined #ocaml
malc_ has quit [Quit: leaving]
arj has quit [Ping timeout: 240 seconds]
manud_ has quit [Quit: Be back later ...]
manud_ has joined #ocaml
boogie has joined #ocaml
thetabyte has quit [Quit: Leaving.]
sooheon has joined #ocaml
struk has quit [Ping timeout: 258 seconds]
arj has joined #ocaml
arj has quit [Ping timeout: 256 seconds]
ousado has joined #ocaml
bytbox has joined #ocaml
thetabyte has joined #ocaml
ousado has quit [Changing host]
ousado has joined #ocaml
jao has quit [Ping timeout: 264 seconds]
arj has joined #ocaml
arj has quit [Ping timeout: 265 seconds]
enitiz has joined #ocaml
darkf_ has joined #ocaml
darkf has quit [Ping timeout: 258 seconds]
darkf_ is now known as darkf
samrat has joined #ocaml
enitiz has quit [Remote host closed the connection]
arj has joined #ocaml
manud_ has quit [Quit: Be back later ...]
badon_ has joined #ocaml
arj has quit [Ping timeout: 264 seconds]
bitbckt has quit [Ping timeout: 272 seconds]
bitbckt has joined #ocaml
badon has quit [Ping timeout: 250 seconds]
badon_ is now known as badon
struk has joined #ocaml
mcclurmc has quit [Remote host closed the connection]
boogie has quit [Remote host closed the connection]
darkf_ has joined #ocaml
darkf has quit [Ping timeout: 258 seconds]
mcclurmc has joined #ocaml
luqi has joined #ocaml
luqi has left #ocaml [#ocaml]
luqi has joined #ocaml
arj has joined #ocaml
sooheon has quit [Ping timeout: 255 seconds]
arj has quit [Ping timeout: 255 seconds]
manizzle has quit [Ping timeout: 255 seconds]
luqi has quit [Quit: Leaving.]
badkins has quit [Remote host closed the connection]
samrat has quit [Quit: Computer has gone to sleep.]
yomimono has quit [Ping timeout: 250 seconds]
arj has joined #ocaml
luqi has joined #ocaml
expo873 has joined #ocaml
ljs has joined #ocaml
arj has quit [Ping timeout: 265 seconds]
Jaood has joined #ocaml
ljs has quit [Client Quit]
struk has quit [Ping timeout: 256 seconds]
kapil_ has joined #ocaml
mcclurmc has quit [Remote host closed the connection]
darkf_ is now known as darkf
arj has joined #ocaml
boogie has joined #ocaml
arj has quit [Ping timeout: 240 seconds]
luqi has quit [Quit: Leaving.]
boogie has quit [Ping timeout: 265 seconds]
samrat has joined #ocaml
luqi has joined #ocaml
luqi has quit [Client Quit]
ljs has joined #ocaml
MercurialAlchemi has joined #ocaml
ygrek has quit [Ping timeout: 255 seconds]
manizzle has joined #ocaml
samrat has quit [Ping timeout: 255 seconds]
arj has joined #ocaml
samrat has joined #ocaml
arj has quit [Ping timeout: 264 seconds]
samrat has quit [Ping timeout: 240 seconds]
samrat has joined #ocaml
Jaood has left #ocaml [#ocaml]
<ljs>
hello there. I am using Lwt to do data sending and receiving, but I find the sending and receiving do not cooperate very well. Ideally, I want the receiving thread to send out an response back when receive K bytes data. However, what I got here is that receiving thread receives many K bytes data in a row(say receive 10 times) and then send response back in a row. Is there
<ljs>
anyway to make the threading better?
samrat has quit [Ping timeout: 255 seconds]
<ljs>
To be general, what I want is thread1->thread2->thread1->thread2->..., but what I got was thread1->....->thread1->thread2->thread2->..->thread2
samrat has joined #ocaml
<whitequark>
define "sending and receiving"
<whitequark>
how exactly are you exchanging data?
MrWuffles has quit [Ping timeout: 255 seconds]
<ljs>
whitequark: what about something like TCP? receive an segment of data and sending the ACK of data back
samrat has quit [Ping timeout: 265 seconds]
siddharthv_away is now known as siddharthv
pierpa has joined #ocaml
samrat has joined #ocaml
<whitequark>
then it's working exactly as expected
thetabyte has left #ocaml [#ocaml]
<whitequark>
TCP does not guarantee that the data will arrive in any particular chunks, it's stream-based
<whitequark>
also, why are you using TCP to communicate within a single process?
<ljs>
whitequark: no exactly. If I receive data a bunch of data without sending ACK back, that's bad
<ljs>
the problem is, sending ACK is starving....
<ljs>
whitequark: Ha, you won't be interested why I have to do this...
<ljs>
I assume it is safe to write recursive call in Lwt, right?
arj has joined #ocaml
bytbox has quit [Remote host closed the connection]
ggole has joined #ocaml
<whitequark>
it
<whitequark>
*it's not different than ordinary in ocaml
arj has quit [Ping timeout: 265 seconds]
<ljs>
right. I guess the only way to do is to write simple scheduler to balance the two threads.
<whitequark>
you seem to be solving a self-inflicted problem.
<ljs>
why self-inflicted?
samrat has quit [Ping timeout: 258 seconds]
samrat has joined #ocaml
<whitequark>
because you shouldn't use TCP for this
<ljs>
Hah, right. in this case TCP only needs to send one ACK back.
<ljs>
ACK the furthest bytes and done.
<flux>
maybe you want to disable the nagle's algorithm
<flux>
tcp stacks like to collect data so as to minimize the number of sent packages
<whitequark>
that still won't guarantee a context switch
<flux>
sure, no guarantees
<whitequark>
Lwt will send data in a loop until the socket blocks, i.e. the buffer is full
<whitequark>
or rather, Lwt never switches context until something blocks
<ljs>
That's what I observed.
<whitequark>
that's working as intended.
<whitequark>
you can try using Lwt.yield
<ljs>
If I have Lwt_unix.sleep 0.001, it works better.
<flux>
ljs, is it that you want to preserve message boundaries?
<flux>
or you're really implementing a scheduler by using TCP?
<ljs>
flux: Oh no, I am implementing TCP....
<ljs>
Itself.
<ljs>
so..
<flux>
I'm not sure what does implementing TCP has got to do with threads :)
<whitequark>
doesn't mirage already have a TCP impl?
samrat has quit [Ping timeout: 264 seconds]
manizzle has quit [Remote host closed the connection]
manizzle has joined #ocaml
<ljs>
I think it has. I never did it before, so...never mind, Thanks guys.
arj has joined #ocaml
samrat has joined #ocaml
<ljs>
Wow, I think yield is what I am looking for!
<ljs>
Thanks!
arj has quit [Ping timeout: 264 seconds]
<johnf>
hi, camlp4 question. I have a system of camlp4 quotations that I wrote up, then I decided I wanted to feed the parser input directly from stdin so I hooked it up to Scanf.fscanf which works ok but handling statements across multiple lines is a bit tricky because finding a deliminator for a statement is not always possible.
<whitequark>
have you considered not using camlp4?
samrat has quit [Ping timeout: 256 seconds]
<johnf>
yeah I don't really have a solid reason for using it I think menhir would have worked... but its what I've been using. And when I use it in ocaml its handy to be able to have antiquotes.
samrat has joined #ocaml
<whitequark>
menhir doesn't work?
<whitequark>
oh, it would have. okay
<johnf>
not sure if menhir can handle the antiquotations which gets me a lot for what I'm doing.
<whitequark>
it's not really in the scope of menhir
<whitequark>
rather you handle those on lexer level.
<whitequark>
if you want to embed your code in OCaml, you can do that with ppx and {x| |x} delimited strings. if you want to embed OCaml in your code, you can also do it using Pparse.
ygrek has joined #ocaml
<whitequark>
neither really requires camlp4
<johnf>
The ppx is fairly recent right in the last release or two?
<whitequark>
4.02+, yes
<johnf>
I guess I want to do both. In some simple cases its handy to read in stdin directly in other cases where I have more sophisticated things going on I want it embedded in ocaml where the quotation system works well. The stdin is mostly just a debug/testing vehicle I guess complaining about a few extra <:myq< ... >> key strokes is not a big deal.
<johnf>
I'll read up on the ppx I sort of knew it was there but hadn't really got to looking into it.
psy has quit [Ping timeout: 250 seconds]
ljs has quit [Quit: None]
<johnf>
whitequark: I assume the first google hit on "ppx ocaml" is your blog :)
<whitequark>
yes
<whitequark>
you reminded me, I should update that
<SomeDamnBody>
so um, I'm getting unbound value Array.fold_left ??
<SomeDamnBody>
but only if I have open mymodule_piqi;; at the top
<SomeDamnBody>
but only if I have open mymodule_piqi;; at the top
samrat has quit [Ping timeout: 240 seconds]
psy has joined #ocaml
arj has joined #ocaml
AlexRussia has quit [Ping timeout: 272 seconds]
arj has quit [Ping timeout: 265 seconds]
samrat has joined #ocaml
arj has joined #ocaml
manud_ has joined #ocaml
<ggole>
SomeDamnBody: module names are uppercase, that could be causing problems
<SomeDamnBody>
oh right, I did that
<SomeDamnBody>
I think my issue has to do with zmq now...
<SomeDamnBody>
I'm using the ocaml zmq wrapper
arj has quit [Ping timeout: 255 seconds]
<SomeDamnBody>
and right now, I have a request reply, where the request sends a request, gets a reply but then does not send a second request. The reply gets 2 requests...??!
WraithM has quit [Ping timeout: 258 seconds]
WraithM has joined #ocaml
<MercurialAlchemi>
"To put it simply, it is a comfortable, XML-style way to describe your installation requirements"
<MercurialAlchemi>
"comfortable", "XML-style way"
<whitequark>
johnf: refresh it
<whitequark>
I've updated the post with latest info
<johnf>
whitequark: great thanks.
<whitequark>
annnnd refresh again
<whitequark>
should be done now
<johnf>
refreshed again. thanks.
<johnf>
I'll port over some of my camlp4 stuff tomorrow. should have time anywyas.
<whitequark>
cool
<whitequark>
[✔] bring camlp4 a little closer to its death today
manizzle has quit [Remote host closed the connection]
<johnf>
whitequark: although camlp4 still looks fairly active at least on github although the wiki front page says its been replaced by ppx
arj has joined #ocaml
<whitequark>
johnf: that's because 2/3 of ocaml ecosystem still depends on camlp4
<whitequark>
you can't just leave it broken
<johnf>
thats what I was going to ask.
<johnf>
is there an intent to port that stuff over with time?
<whitequark>
it slowly happens
<whitequark>
I myself have ported five or so packages, and others did it to a degree, too
<johnf>
sure takes time, can't introduce regressions, etc.
<whitequark>
review can be slow as well
<flux>
and it will break user code, which isn't that great :/
govg has quit [Quit: leaving]
<whitequark>
not always
<whitequark>
dependencies on optcomp, say, can be removed quite safely
bezirg has quit [Quit: Leaving.]
bezirg has joined #ocaml
zpe has joined #ocaml
pgas has joined #ocaml
zwer has quit [Remote host closed the connection]
zwer has joined #ocaml
HACKING-FACEBOOK has joined #ocaml
zwer has quit [Remote host closed the connection]
zwer_w has joined #ocaml
cyanure__ has joined #ocaml
HACKING-FACEBOOK has quit [Ping timeout: 244 seconds]
<johnf>
whitequark: the extend gram; parser bits in camlp4 seem to work OK, what is the equivalent in ppx? It looks like the Ast_mapper.
<whitequark>
ppx does not provide extensible grammars
bezirg has left #ocaml [#ocaml]
<whitequark>
i.e. it only recognizes fixed syntax, no matter which extensions are loaded
<johnf>
fixed syntax being an AST 'remap' essentially right
<whitequark>
what you want for quotations is to find Const_string marked with your language, corresponding to {x| |x} literals (here the mark is "x") and do... something to them
<whitequark>
well, ppx extensions map an OCaml AST to OCaml AST
emery has quit [Ping timeout: 250 seconds]
HACKING-FACEBOOK has joined #ocaml
<johnf>
I think all I was pointing out is that the parser notation is easier to grok then the mapper notation. Take ["first"; second = LIST0; "third"l forth = LIDENT; ";" -> ...]
<johnf>
typo s/|/;
Thooms has joined #ocaml
emery has joined #ocaml
thomasga has joined #ocaml
zwer_w has quit [Ping timeout: 250 seconds]
zwer_w has joined #ocaml
psy has quit [Quit: Leaving]
argp has left #ocaml [#ocaml]
Thooms has quit [Quit: WeeChat 1.0.1]
Thooms has joined #ocaml
<companion_cube>
whitequark: there is [%show:int list] [1;2;3] with ppx_deriving, but ppx_deriving.show actually makes 2 functions (pp and show)
ia0 has quit [Quit: leaving]
larhat has joined #ocaml
zpe has quit [Remote host closed the connection]
emery has quit [Ping timeout: 250 seconds]
nojb has joined #ocaml
HACKING-FACEBOOK has quit [Ping timeout: 240 seconds]
HACKING-FACEBOOK has joined #ocaml
ikaros has joined #ocaml
kapil_ has quit [Quit: Connection closed for inactivity]
emery has joined #ocaml
avsm has joined #ocaml
lopex has joined #ocaml
avsm has quit [Client Quit]
psy has joined #ocaml
HACKING-FACEBOOK has quit [Ping timeout: 245 seconds]
Thooms has quit [Quit: WeeChat 1.0.1]
ia0 has joined #ocaml
thomasga has quit [Quit: Leaving.]
George___ has joined #ocaml
thomasga has joined #ocaml
rossberg has quit [Remote host closed the connection]
zpe has joined #ocaml
<whitequark>
companion_cube: oh
avsm has joined #ocaml
avsm has quit [Client Quit]
<whitequark>
companion_cube: yeah, this was planned at some point, but I forgot
<whitequark>
can you send a PR? :]
<companion_cube>
so, seeing how many packages depend on sexplib and camlp4, I'm really tempted to make ppx_deriving_sexp
<companion_cube>
hmmm
<whitequark>
do it!
<companion_cube>
of course it would produce ([`Atom of string | `List of 'a list] as 'a) ;>
<whitequark>
that'd break the interface though
<whitequark>
I think a drop-in replacement is worthwhile
<companion_cube>
maybe so :/
<whitequark>
you can make it an option, though
<companion_cube>
but then it would need to depend on sexplib, which depends on camlp4
<companion_cube>
yeah, probably
<companion_cube>
where is [%show] exactly in the code?
<whitequark>
ppx_deriving_show at the bottom
<whitequark>
register deriver
<whitequark>
deriver = "show"
AlexRussia has joined #ocaml
<thomasga>
companion_cube: yes, please, do ppx_deriving_sexp
arj has quit [Ping timeout: 264 seconds]
<thomasga>
and ppx_deriving_bin_prot :p
manud_ has quit [Quit: Be back later ...]
<companion_cube>
erf
<companion_cube>
I don't know bin_prot and I don't want to know
<companion_cube>
there ppx_deriving_protobuf for binary serialization
<companion_cube>
:p
arj has joined #ocaml
arj has quit [Client Quit]
divyansh_ has joined #ocaml
kapil_ has joined #ocaml
<thomasga>
might try this protobuf at one point indeed
Simn has joined #ocaml
arj has joined #ocaml
samrat has quit [Quit: Computer has gone to sleep.]
samrat has joined #ocaml
George___ has quit [Ping timeout: 246 seconds]
_5kg has quit [Ping timeout: 240 seconds]
AltGr has left #ocaml [#ocaml]
ollehar has joined #ocaml
pgomes has joined #ocaml
<pgomes>
Hi All
<pgomes>
is there a difference between 'let square x = x * x;;' and 'let square = fun x -> x * x;;'
<pgomes>
is that only syntatic sugar for the lambda part?
<nojb>
yes
<pgomes>
what is more correct form ?
<nojb>
they are equivalent
<pgomes>
I assume the latter is more clear no ?
<nojb>
no
<adrien>
former
<nojb>
yes
<pgomes>
without the 'func'?
<adrien>
except when you want to show the function is "staged"
<nojb>
yes
<pgomes>
ok
<pgomes>
I dont what that is yet :P
<adrien>
i.e. you'd typically call it first with part of its arguments applied
<pgomes>
curried?
<adrien>
more like
<pgomes>
Understand
<adrien>
let uid_gen () = let i = ref (-1) in (fun () -> incr i; !i)
ygrek has quit [Ping timeout: 255 seconds]
<pgomes>
Thanks
<nojb>
adrien: uid_gen is the constant function 0
<nojb>
you mean let uid_gen = let i = ref (-1) in fun () -> (incr i; !i)
<adrien>
it works as I've written it
<adrien>
but anyway
<adrien>
I'm actually surprised it was valid ocaml considering I wrote it right in my irc client
<adrien>
as long as it carried the idea
<pgomes>
it does work yes :P
jpdeplaix has quit [Ping timeout: 240 seconds]
zwer_w has quit [Remote host closed the connection]
zwer_w has joined #ocaml
choeger_tu has joined #ocaml
jpdeplaix has joined #ocaml
_5kg has joined #ocaml
pierpa`` has quit [Ping timeout: 245 seconds]
pierpa has quit [Ping timeout: 264 seconds]
cyanure__ has quit [Remote host closed the connection]
Thooms has joined #ocaml
zelines has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 250 seconds]
choeger_tu has quit [Ping timeout: 255 seconds]
<flux>
pgomes, the latter is more clear if you want to have the same signatures both in the interface and the implementation: let square : int -> int = fun -> x * x
<flux>
this can happen when you first design the .mli and just use some editor magic to convert them into let foo : signarure = fun _ -> failwith "not implemented"
<pgomes>
I did not thought of that :P
MercurialAlchemi has joined #ocaml
<whitequark>
or just write the ml manually
<whitequark>
seriously, how lazy can you be
<pgomes>
as much as possibe :P
<ggole>
The second form can be necessary if you want to use polymorphic recursion, too
<pgomes>
That's too much infromation for me at this time ... but I will check it out :P
divyansh_ has quit [Quit: Computer has gone to sleep.]
<Leonidas>
wasn't there some camlp4 extension that wrote the mli for you?
<Leonidas>
I wonder whether it makes sense to wrap each polymorphic variant type into it's own type definition
<Leonidas>
that way, when referencing them, you don't create them by accident via typos.
<Leonidas>
thoughts?
q66[lap] has joined #ocaml
<companion_cube>
that's an ok idea
<companion_cube>
also you can "inline" such a definition with #type
<companion_cube>
type foo = [ #bar | `Foo ], something like this
<Leonidas>
yes, that is exactly what I'm doing
<Leonidas>
actually, you don't need the '#' there
<Leonidas>
type bar = [ `Bar ]
<ggole>
It's deprecated for some reason
<Leonidas>
it is? ok
<ggole>
No, the # is deprecated
<Leonidas>
will it also disappear from pattern matches?
<ggole>
type foo = [bar | `Foo] is what you are supposed to use now.
<ggole>
I don't think so.
<companion_cube>
oh, ok
<Leonidas>
| #bar as whatever -> whatever
seanmcl has joined #ocaml
<Leonidas>
is there some way to force ocamldoc to also generate descriptions via @param for unnamed parameters?
badkins has joined #ocaml
chambart has joined #ocaml
expo873 has quit [Quit: Connection closed for inactivity]
badkins has quit []
badkins has joined #ocaml
enitiz has joined #ocaml
chambart has quit [Ping timeout: 240 seconds]
malc_ has joined #ocaml
avsm has joined #ocaml
<zozozo>
hi, can anyone tell me why the behavior of '%a' un format strings for Lwt_io differs greatly from Format.fprintf ? specifically, in lwt, it requires the function to be of type unit -> 'a -> string, and not Lwt_io.output_channel -> 'a -> unit Lwt.t as one could expect ?
chambart has joined #ocaml
mort___ has joined #ocaml
struk has joined #ocaml
<nojb>
The printf functions in Lwt_io are implemented with ksprintf
<nojb>
the signature of ksprintf and fprintf (in Pervasives) are different
mcclurmc has joined #ocaml
<zozozo>
so it's a design choice ?
<nojb>
no it is an unfortunate consequence of the tricks needed to get a typed printf function
<Unhammer>
from `Html5.Manip.childElements elt` – how do I get a Html5.elt?
<Unhammer>
`List.map Html5.Of_dom.of_element` says it has no classList
<Unhammer>
(which is fine, it could be a text node, but I should be able to otherelt.appendChild it)
bytbox has joined #ocaml
WraithM has quit [Quit: leaving]
avsm has quit [Quit: Leaving.]
MrWuffles has joined #ocaml
<Unhammer>
*sigh* this Eliom stuff is so nice until you have to convert between Dom.node/Dom.element/Dom_html.element and suddenly have wasted 4 hours reading type signatures
Thooms has joined #ocaml
<flux>
there should be a tool that answer to the question: given I have a value of this type, how do I get a value of that type :)
<flux>
or maybe: what types can I get out from this and how
vogler has joined #ocaml
<flux>
then you could add that to the compiler as a ppx extension and your code could be like: let a = magic b in ... ;-)
<nojb>
Haskell has something like it : Hoogle and it is pretty cool IMHO
<flux>
yes, hoogle is nice but I don't think it'd be sufficient with eliom
<flux>
it would need to be hoogle + djinn
struk has quit [Ping timeout: 240 seconds]
enitiz has quit [Remote host closed the connection]
vogler has quit [Quit: WeeChat 1.0.1]
<Unhammer>
camoogle would be a great first step though
<flux>
goocaml ;-)
<Unhammer>
camlcamlgo
voglerr has joined #ocaml
<flux>
now that's the terrible name! let's go with that :)
BitPuffin has quit [Remote host closed the connection]
ysz has joined #ocaml
bezirg has quit [Ping timeout: 240 seconds]
sheijk has joined #ocaml
bytbox has quit [Remote host closed the connection]
BitPuffin has joined #ocaml
ysz has quit [Quit: This computer has gone to sleep]
davine has joined #ocaml
olauzon has joined #ocaml
martintrojer has quit [Max SendQ exceeded]
martintrojer has joined #ocaml
<ddosia>
hi, why when I do: utop # "";; I see - : bytes = "" signature, but in plain "ocaml" repl I see - : string = "" signature ?
<Drup>
utop probably calls the compiler with -short-path by default
<Unhammer>
Drup, in my case it feels like an inconsistency in eliom; "Html5.Manip.childElements elt" returns "Dom.element Js.t" while all the Html5.Manip functions work on Eliom_content.Html5.elt's
<Unhammer>
I have added a span around some stuff. Now I want to remove it again.
mcclurmc has joined #ocaml
<Drup>
hum
<Unhammer>
ie. grab the children of the span, append them before the span, remove the span
<Drup>
returns the reference where you create it instead of wrap/unwrap ?
<Unhammer>
?
<Unhammer>
sorry, that went over over my head :)
<Drup>
the moment you do (span x)
<Unhammer>
oh, but text might have changed in the meanwhile
<Drup>
instead of doing that, you returns (x, span x)
<Unhammer>
it's a contentEditable
<Drup>
If it's a D semantic, not a problem, it's just a reference
jonludlam has quit [Ping timeout: 264 seconds]
mcclurmc_ has quit [Ping timeout: 255 seconds]
<Drup>
(that's the whole point of the D semantic :p)
<Unhammer>
if I turned <em>foo</em>bar into <span class='e'><em>foo</em>bar</span>, and then the user cut <em>foo</em> out of the span and pasted it elsewhere, then I can't replace the span by <em>foo</em>bar
<Unhammer>
I have to replace it by the *current* children
davine has quit [Quit: Leaving]
slash^ has joined #ocaml
<Drup>
I see.
ysz has joined #ocaml
<Drup>
Ah, I see why I didn't know those functions, they are hidden in the documentation :<
choeger_tu has quit [Quit: choeger_tu]
govg has joined #ocaml
govg is now known as Guest17962
Guest17962 has quit [Client Quit]
<Unhammer>
(Html5.Manip in general seems very handy, except for that one thing)
<Drup>
getting the internal nodes of a nodes as html elements is ... discouraged :D
<Unhammer>
I should use an external .js file?
<Drup>
No, no
<Drup>
It's discourage because 1) you don't actually know if the dom childs are really html nodes 2) You can't type them in tyxml's typesystem.
<Drup>
+d
<Drup>
the thing you did is the right thing
<Drup>
maybe we could make that more handy, but it would still be untyped :(
<Drup>
Unhammer: usually, we get away by just doing things differently
<Drup>
but in your case .. hmm.
<Unhammer>
yeah … I'm not sure I see a way to do what I'm doing differently though without cluttering with unused spans everywhere
BitPuffin has quit [Ping timeout: 265 seconds]
choeger_tu has joined #ocaml
ollehar has joined #ocaml
zelines has joined #ocaml
tharugrim has joined #ocaml
<Drup>
Unhammer: are you doing an editor in eliom ?
martintrojer has quit [Max SendQ exceeded]
martintrojer has joined #ocaml
<Unhammer>
Sort of. We make a grammar checker (as-a-service) at work, I've been wanting for a while to make a web UI that handles rich text and checks more or less as you type
divyansh_ has quit [Ping timeout: 244 seconds]
<Drup>
engil: where is your prototype colaborative editor in eliom ?
MrScout has quit [Remote host closed the connection]
<Drup>
(iirc, you were the one doing that)
<Unhammer>
heh I was looking at collaborative editing, but after reading some comment about how "OT took two years to implement and would take two more years if we were to do it over again" I figured put that on the "maybe-someday" list for now …
<Unhammer>
(or just use sharejs)
<Drup>
:D
divyansh_ has joined #ocaml
bezirg has joined #ocaml
divyansh_ has quit [Ping timeout: 240 seconds]
divyansh_ has joined #ocaml
davine has joined #ocaml
MrScout has joined #ocaml
choeger_tu has quit [Quit: choeger_tu]
govg_ has joined #ocaml
larhat has joined #ocaml
MrScout has quit [Ping timeout: 255 seconds]
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
MrScout has joined #ocaml
kakadu has quit [Quit: Page closed]
sheijk has quit [Ping timeout: 240 seconds]
<engil>
Unhammer: OTs aren't really friendly to implement yeah.