ChanServ changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml 4.02.1 announcement at http://ocaml.org/releases/4.02.html | Public channel logs at http://irclog.whitequark.org/ocaml
<tobiasBora> Before to get the content of a module in Toplevel I used something like "module A = String";;
<tobiasBora> but now it doesn't work anymore
<tobiasBora> I saw a few weeks ago a workaround with a #... command, but I can't remember it's name and I can't find the link anymore
<Leonidas> cmtptr: well, that's a first step. Awaiting your progress on Saturday and Sunday :)
<Leonidas> tobiasBora: still works for me in utop…
<Leonidas> module A = String;;
<tobiasBora> Leonidas: But it does not work in the classic ocaml "shell" (just run ocaml)
<Leonidas> tobiasBora: does anyone still use that? :p
lnich has quit [Remote host closed the connection]
<tobiasBora> Yes me :D I use it with tuared mode in emacs and I don't see what's wrong with it ^^
<Leonidas> but yeah, it doesn't work. Not sure why. Maybe because it is an instruction of the "module language"?
<Leonidas> I think you can use utop in tuareg-mode too, but no idea, vim user here
<Leonidas> oh yeah, that's described in the utop readme
<thizanne> tobiasBora: #show_module A;;
<tobiasBora> Leonidas: I just tried to install utop (it's pretty beautifull ^^), but It does't work either : http://paste.ubuntu.com/10638793
<tobiasBora> thizanne: Thank you :D
<thizanne> and yes it does not work anymore with module A = String, because this phrase used to define a new module A, which had the same definition as List
<thizanne> and now it defines a new name for the same module List
<thizanne> (so the top-level tells you "module A = List" to show it's really the same one)
<tobiasBora> I see, it's clearer now !
nullcat has joined #ocaml
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
alpen has quit [Ping timeout: 256 seconds]
avsm has joined #ocaml
alpen has joined #ocaml
madroach has quit [Ping timeout: 264 seconds]
<Drup> Leonidas: are you sure you are not using an old ocaml ?
madroach has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
JuggleTux has joined #ocaml
mengu has joined #ocaml
mengu has quit [Ping timeout: 265 seconds]
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
sdothum has quit [Quit: ZNC - 1.6.0 - http://znc.in]
ygrek has joined #ocaml
AlexRussia has quit [Ping timeout: 256 seconds]
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
idegen has joined #ocaml
AlexRussia has joined #ocaml
nullcat has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
avsm has quit [Quit: Leaving.]
swgillespie has joined #ocaml
Haudegen has quit [Ping timeout: 245 seconds]
Haudegen has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
zoetus has joined #ocaml
<zoetus> how do you get ppx_deriving to work in utop?
tianon has joined #ocaml
darkf has joined #ocaml
ygrek_ has joined #ocaml
ygrek has quit [Ping timeout: 246 seconds]
<Drup> #require "ppx_deriving" ;;
<Drup> probable .show or .thing at the end
<zoetus> that doesn't seem to work for me
<zoetus> i've opam installed it
<zoetus> when i type `#ppx "`, it doesn't show up in the autocomplete list either
<Drup> I never said #ppx
<zoetus> i know, i tried it both ways :)
<zoetus> just following your steps though didn't seem to work
ollehar1 has quit [Quit: ollehar1]
<zoetus> the require works fine, but i get syntax errors when i try something like `type t = Foo of int [@@deriving show]`
<zoetus> i tried requiring ppx_deriving.show also
<Drup> remove one @
<zoetus> ah! that did it! thanks so much!
<zoetus> the examples use `@@`, what is the difference?
<Drup> if the examples use @@, they are wrong :D
<zoetus> then its own readme is wrong: https://github.com/whitequark/ppx_deriving#plugin-show
<Drup> hum, or not.
<Drup> "type t = Foo of int [@@deriving show] ;;" works fine in my top level after doing "#require "ppx_deriving.show";;"
<zoetus> it's weird though, typing `type t = Foo of int [@deriving show] ;; ` doesn't generate a show_t function (in utop)
<Drup> and after double checking, @@ is the rgith thing
<zoetus> hmm, i wonder if i missed a step installing this then?
<zoetus> i just did `opam install ppx_deriving`
<Drup> it should be enough
<Drup> and anyway, you wouldn't get a *syntax* error
<Drup> you would get a loading error
<zoetus> hmm
<Drup> oh !
<Drup> do you have camlp4 loaded ?
tianon has quit [Read error: Connection reset by peer]
<zoetus> `Error: Parse error: [str_item] or ";;" expected (in [top_phrase]) `
<Drup> yeah, you have camlp4 ...
tianon has joined #ocaml
<zoetus> oh, maybe not?
<zoetus> probably i do...
<Drup> I assure you, it's a camlp4 error message
<Drup> camlp4 doesn't recognise @@ ppx attributes
<zoetus> ah, makes sense
<zoetus> i thought that looked a lot like a camlp4-type error
<Drup> syntax error*
<zoetus> (i mean camlp4-ish error, not "type error")
<zoetus> how do you not load that in utop?
<zoetus> (i'm not explicitly loading it)
<Drup> look at your .ocamlinit
<zoetus> oh bummer, i'm using core.syntax in some of my projects
<Drup> well, don't :D
<Drup> which one are you using ?
<zoetus> i guess there's no easy way to still use things like `with sexp` along with ppx stuff?
<Drup> no way to do that, sorry
<zoetus> ah, that's too bad
<Drup> but if you are using sexp, you have acces to type-conv and other things like that which have some features of ppx_deriving
<zoetus> i wonder if there's an effort to move that stuff to extension points
<zoetus> oh cool
<Drup> yes, jst is working on moving to ppx
boogie has joined #ocaml
reem has quit [Remote host closed the connection]
reem has joined #ocaml
<zoetus> so i just removed the `#require core.syntax" from my .ocamlinit
<zoetus> now in utop i get: `Error: Error while running external preprocessor `
<zoetus> Command line: ppx_deriving '/var/folders/38/0jv05jtd7k9cwlbmd_2_x0lw0000gp/T/camlppxcc9f92' '/var/fold ers/38/0jv05jtd7k9cwlbmd_2_x0lw0000gp/T/camlppx822e04'
<Drup> that's ... interesting
<Drup> it should put things in /tmp/ iirc
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
boogie has quit [Remote host closed the connection]
reem has quit [Remote host closed the connection]
oriba has quit [Quit: Verlassend]
antkong has joined #ocaml
swgillespie has joined #ocaml
kandu has quit [Remote host closed the connection]
reem has joined #ocaml
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
kandu has joined #ocaml
ghostpl_ has quit [Remote host closed the connection]
reem has quit [Remote host closed the connection]
<seangrove> I have two documents I've created with Xmlm - I want to place one inside the other, but looking at the library, I can't figure out how to do it
<seangrove> I definitely feel like OCaml is a big reorientation away from data structures compared to e.g. clojure
zoetus has quit [Ping timeout: 246 seconds]
idegen has quit [Ping timeout: 245 seconds]
<Drup> well, if you take xmlm as an example, obviously ... it's a library with literally no data structure in it. You are supposed to design your own and use Xmlm as a streaming input to construct your data structure
<seangrove> Drup: Ah, that makes sense
antkong has quit [Quit: antkong]
pyon is now known as pyon-tractible
swgillespie has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
`eeks has joined #ocaml
tianon has joined #ocaml
badon has quit [Quit: Leaving]
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
reem has joined #ocaml
swgillespie has joined #ocaml
`eeks has quit [Quit: Textual IRC Client: www.textualapp.com]
ygrek_ has quit [Ping timeout: 252 seconds]
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
shinnya has quit [Ping timeout: 264 seconds]
<_obad_> is cohttp the only lwt-enabled http client library? it seems like it does not support pipelining, but I may be wrong
<_obad_> hmm looks like ocsigen can also work as an http client
ggole has joined #ocaml
virtualeyes has joined #ocaml
yomimono has joined #ocaml
rszeno has joined #ocaml
badon has joined #ocaml
rszeno has left #ocaml [#ocaml]
marynate has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
tianon has quit [Changing host]
tianon has joined #ocaml
antkong has joined #ocaml
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
antkong has quit [Ping timeout: 246 seconds]
madroach_ has joined #ocaml
madroach has quit [Read error: Connection reset by peer]
psy_ has quit [Remote host closed the connection]
psy_ has joined #ocaml
psy_ has quit [Max SendQ exceeded]
psy_ has joined #ocaml
swgillespie has joined #ocaml
slash^ has joined #ocaml
pyon-tractible is now known as pyon-tractable
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
psy_ has quit [Quit: Leaving]
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
Simn has joined #ocaml
ygrek has joined #ocaml
ygrek has quit [Ping timeout: 250 seconds]
boogie has joined #ocaml
MercurialAlchemi has joined #ocaml
shinnya has joined #ocaml
keen________ has joined #ocaml
keen_______ has quit [Ping timeout: 245 seconds]
pobivan has joined #ocaml
psy_ has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
reem has quit [Remote host closed the connection]
reem_ has joined #ocaml
kakadu has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
pyon-tractable is now known as not-not-pyon
marynate has quit [Quit: Leaving]
antkong has joined #ocaml
codefo has joined #ocaml
codefo has quit [Client Quit]
hsuh has quit [Ping timeout: 240 seconds]
antkong has quit [Ping timeout: 252 seconds]
hsuh has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
Submarine has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
reem_ has quit [Read error: Connection reset by peer]
reem has joined #ocaml
milosn has quit [Ping timeout: 264 seconds]
milosn has joined #ocaml
freling has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
reem has quit [Remote host closed the connection]
reem has joined #ocaml
pobivan has quit [Quit: pobivan]
reem has quit [Ping timeout: 265 seconds]
avsm has joined #ocaml
Haudegen has quit [Ping timeout: 265 seconds]
ollehar1 has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
reem has joined #ocaml
Haudegen has joined #ocaml
freling has quit [Quit: Leaving.]
mengu has joined #ocaml
dant3 has joined #ocaml
dant3 has quit [Ping timeout: 264 seconds]
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
Oejet has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
boogie has quit [Remote host closed the connection]
sdothum has joined #ocaml
Haudegen has quit [Ping timeout: 245 seconds]
lordkryss has joined #ocaml
antkong has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
mengu has quit [Read error: Connection reset by peer]
mengu has joined #ocaml
ZenosDance has joined #ocaml
ollehar1 has quit [Ping timeout: 250 seconds]
dant3 has joined #ocaml
freling has joined #ocaml
freling has quit [Client Quit]
freling has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
Haudegen has joined #ocaml
Haudegen has quit [Ping timeout: 264 seconds]
antkong has quit [Ping timeout: 244 seconds]
xificurC has joined #ocaml
avsm has quit [Quit: Leaving.]
Haudegen has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
AlexRussia has quit [Ping timeout: 250 seconds]
Haudegen has quit [Ping timeout: 244 seconds]
Haudegen has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
JuggleTux has quit [Ping timeout: 256 seconds]
thomasga has joined #ocaml
AlexRussia has joined #ocaml
darnuria has quit [Remote host closed the connection]
darnuria has joined #ocaml
AlexRussia has quit [Ping timeout: 252 seconds]
AlexRussia has joined #ocaml
TheLemonMan has joined #ocaml
ghostpl_ has joined #ocaml
oscar_toro has joined #ocaml
thomasga has quit [Quit: Leaving.]
ChristopheT has joined #ocaml
myyst has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
mxv has quit [Ping timeout: 250 seconds]
mxv has joined #ocaml
myst has quit [Ping timeout: 256 seconds]
thomasga has joined #ocaml
thomasga has quit [Client Quit]
myyst is now known as myst
idegen has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
reem has quit [Remote host closed the connection]
JuggleTux has joined #ocaml
struktured has quit [Ping timeout: 265 seconds]
freling has quit [Quit: Leaving.]
mort___ has joined #ocaml
ChristopheT has left #ocaml ["ERC Version 5.3 (IRC client for Emacs)"]
freling has joined #ocaml
Oejet has left #ocaml [#ocaml]
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
ghostpl_ has quit [Remote host closed the connection]
ghostpl_ has joined #ocaml
struktured has joined #ocaml
Submarine has quit [Ping timeout: 246 seconds]
meteo has quit [Ping timeout: 246 seconds]
meteo has joined #ocaml
<bernardofpc> Drup: http://tests.ocsigen.org/suffixform is broken (500) as, are many other in the page http://ocsigen.org/eliom/4.1/manual/server-links
<bernardofpc> besides, I see a lot of <<>> syntax there, instead of the functions (head (body (... ))
<Drup> ah yes
<Drup> I know.
<Drup> I should just remove them, I think
cmtptr has quit [Ping timeout: 246 seconds]
cmtptr has joined #ocaml
<bernardofpc> I'm looking for a nice way of 1) Managing a list of items, 2) displayed in a table, 3) which can have some data altered by user input
<mrvn> so a hashtbl or mutable records?
<mrvn> persistent? how many?
<bernardofpc> mrvn: the problem is not the datastructure, is the iteraction in Eliom
<bernardofpc> more precisely, how to make a "click / input / <Enter>" trigger an action on server side
<bernardofpc> (that knows which "row" was affected, probably by using some hidden id as in a database)
tizoc has quit [Quit: Coyote finally caught me]
tizoc has joined #ocaml
<kakadu> It is interesting topic
<bernardofpc> mrvn: it's toyish for the moment, so I can definetely handle this fully loaded on memory
* kakadu just found Object.observe() in google
<mrvn> QT has a nice model/view conept for that
<kakadu> Qt !
tianon has quit [Read error: Connection reset by peer]
<bernardofpc> yeah
<mrvn> evry gui should have one
tianon has joined #ocaml
<Drup> bernardofpc: there are several way to do this, and it depends a lot of various details
<Drup> but a simple way is to build the list of html elements
<Drup> put them in a table
<Drup> and attach an handler (using Lwt_js_events for example) to the element to replace the element on click by some form (and replace back when you are done)
<Drup> the rest is server-side and/or rpc
<bernardofpc> thanks Drup
<bernardofpc> I'll read on Lwt_js_events
waneck has joined #ocaml
<adrien> (actually MVC is awful when it has to be cross-language, especially when the other language has limited expressivity)
<Drup> bernardofpc: you can have a (rather general a bit overkill) example https://github.com/ocsigen/eliom-widgets/blob/master/src/ew_editable.eliom
shinnya has quit [Ping timeout: 264 seconds]
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
darkf has quit [Quit: Leaving]
waneck has quit [Quit: Leaving]
Submarine has joined #ocaml
darnuria has quit [Remote host closed the connection]
darnuria has joined #ocaml
ygrek has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
ygrek has quit [Ping timeout: 256 seconds]
axiles has quit [Ping timeout: 264 seconds]
ygrek has joined #ocaml
axiles has joined #ocaml
<cmtptr> let rec insert x xs = match xs with [] -> [x] | head :: tail -> if x <= head then x :: xs else head :: insert x tail;; (* why does "insert -1 [1; 2; 5];;" give the error: This expression has type 'a -> 'a list -> 'a list but an expression was expected of type int? *)
<companion_cube> yes, the problem is your expression is parsed as (insert - 1) [1;2;5]
<companion_cube> try: insert (-1) [1;2;5]
jbalint has quit [Quit: Bye!]
<cmtptr> ah, makes sense. thanks
avsm has joined #ocaml
seangrove has quit [Remote host closed the connection]
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
<_obad_> hi everyone. is there an existing program for grepping into s-expressions?
<companion_cube> what would such regex look like?
<_obad_> companion_cube: that's syntax, but semantically it could be something like css node selectors.
<_obad_> in more concrete terms, I'm using sexplib and I have code that dumps a bunch of data, which are generally records. and I want to search them.
<_obad_> let's say you have a sequence of sexps that have been serialized from type foo = { blah : int; baz :string } and you want to extract all the baz values
<companion_cube> well, I don't think there is anything like that, but it would certainly be interesting
<_obad_> ok I just pushed a simple prototype that does the job at https://github.com/berke/fling ; there is no input syntax as I'm using sexplib to deserialize the ast
<Drup> _obad_: fieldslib ?
<ggole> I've pondered some kind of heap search utility that worked like that (in the toplevel, say)
<_obad_> drup: let me google that
<Drup> it's part of the core stuff
<Drup> with sexplib.
<_obad_> drup: ok I was looking for a command-line tool like grep
<Drup> oh, ok
<ggole> There's sgrep
<ggole> But that's for xml
<_obad_> ggole: is that the structured grep?
<_obad_> it's actually more general than that and interesting, but I always found it too difficult to use.
<ggole> Yeah, I've never actually fired it up in anger
<_obad_> anyway I uploaded a prototype called "fling" and the usage looks like this: fling '(Tag My_tag (Seq ((Fields (foo bar baz) Emit) Newline)))' <foo.sexp
<_obad_> so if you have type bar = My_tag of blah | Other_tag of other and blah = { foo : int; bar : string; baz : string }
<_obad_> the expression would select fields foo, bar, baz from entries having the tag My_tag. needs conrete syntax.
<Drup> basically lenses ? :D
ygrek has quit [Ping timeout: 245 seconds]
<_obad_> dunno, is that what lenses are? maybe there is a command-line lens tool
TheLemonMan has quit [Quit: leaving]
<ggole> Lenses are a Haskell library for exercising the type checker.
ZenMatt has joined #ocaml
<ggole> (They actually seem kinda cool, but hell if I can understand the more abstract parts.)
<Drup> the base concept is very simple, and then haskell people generalized it :D
boogie has joined #ocaml
<ZenMatt> HI foks, beginner @ ocaml here. I have a question, if I write a function signature like : let somefun : (int -> int) -> int -> int = .... with the intention beign that (int->int) will be a function of itself, applied to the next arguement, how would that look?
<ZenMatt> so I want to call the program somefun (fun x -> x / 2) would return an int
<ggole> ZenMatt: What do you mean by 'how would that look'? Are you asking us to supply a possible definition of somefun here?
<Drup> ZenMatt: to what would you apply (fun x -> x /2) in this example ?
<ZenMatt> sorry I missed an int. I essentially want to create something like somefun (fun x -> x / 2) 10 or somefun (fun x -> x * 2) 5 where I'm applying the latter number. I'm not asking so much for a solution, but moreso if anonymous functions can be made in this way
<dmbaturin> ZenMatt: let apply f x y = f x y
<dmbaturin> Or, let apply (int -> int) -> int -> int = fun f -> fun x -> fun y -> f x y
<Drup> dmbaturin: the y is not necessary.
<dmbaturin> Sorry. missed the colon.
<ZenMatt> oh I see!
<ggole> (Or just (@@).)
<dmbaturin> ZenMatt: Why would you want it not to be polymorphic though?
<ZenMatt> well
<ZenMatt> ultimately I'm trying to create a function as above, and will return the number of times the function can be called, until a negative number is given
<dmbaturin> Drup: Not just not necessary, I misread the original type. :)
<dmbaturin> So it would be even harmful.
<ggole> You want to repeatedly call the function (on its result, I assume) until it returns a negative result?
<bernardofpc> Drup: Unbound module Eliom_content.Html5.Manip :/
<ZenMatt> yes exacly
<bernardofpc> installed-version: 4.1.0 [4.02.1]
<ZenMatt> my problem was that I saw some tutorials online regarding anonymous functions, how to create them etc
<ggole> let until_neg f init = let rec loop count x = let r = f x in if r < 0 then count else loop (count + 1) r in loop 0 init
<ZenMatt> but I wasnt sure how to create an anonymous function that could be called unto itself
<ggole> (Not tested.)
_um has joined #ocaml
<ZenMatt> regardless if x * y or x / y or x - y etc
mengu has quit [Remote host closed the connection]
<ZenMatt> ah interesting, let me go try that
struktured has quit [Ping timeout: 265 seconds]
larhat has joined #ocaml
<dmbaturin> ZenMatt: Well, in this case there is no anonymous recursion, the thing that is called recursively is named.
<dmbaturin> You can make a recursive function without naming it (the keyword is "Y combinator"), but it's a different story. :)
<ZenMatt> I see. Do you know of any good web resources for more on using ocaml in this way?
<dmbaturin> Did you check the Learn section of ocaml.org?
mengu has joined #ocaml
<dmbaturin> There's also a list of books, many of which are free.
<ZenMatt> I've been reading that yes and some of the 99 problems which are good
<ZenMatt> oh any books you recommend?
<ZenMatt> I've been reading Real World Ocaml
<ZenMatt> A very good book
<dmbaturin> RWO is good, just watch for Core.
<dmbaturin> If you like Core and use it, it's not a problem of course.
<cmtptr> and if you don't? I had to abort rwo because I don't like learning languages by first installing 20 packages on top of it, obfuscating everything
<dmbaturin> You may also like notes from this course: http://www.cs.cmu.edu/~./15150/lect.html
<dmbaturin> "dmbaturin, advocating SML in #ocaml since 2014"
<ZenMatt> cmtptr I felt that way too in some parts
<ZenMatt> thanks for the link
* destrius learnt SML first, and it was a great language to learn functional programming in
<Drup> cmtptr: that doesn't make much sense in OCaml though, most of the stuff that is including in the stdlib in most languages are in "user space" in OCaml.
<dmbaturin> Regardless, the concepts it teaches are equally applicable to any language, and SML syntax is easy to read if you know some ocaml.
<destrius> its similar enough to ocaml that you can move between the two quite easily.
_um has quit [Remote host closed the connection]
<cmtptr> Drup, I respect that, but still. I don't see why I need this utop thing when I have an perfectly fine ocaml repl that came with the compiler
<dmbaturin> cmtptr: I enjoyed the book even though I had to mentally filter the coreness out because I don't use it.
<Drup> ahah, perfectly fine repl
<Drup> utop is better.
<cmtptr> does it somehow read, evalulate, and print better?
<dmbaturin> cmtptr: Yes, no, yes.
<Drup> it autocompletes.
<cmtptr> I have no use for that
<Drup> actually, it also evaluates better, since it has custom support for lwt too.
<dmbaturin> No use for command history too? :)
<cmtptr> anyway, my point is: even if there are things like that out there, that's fine. but my first steps into a language shouldn't be trying to make heads or tails of that shit
<dmbaturin> For SML and Scheme REPLs I have to resort to rlwrap.
<cmtptr> I just want to learn the language right now. I can decide later whether I want utop
<companion_cube> the very first start could be the tutorial on ocaml.org, which doesn't require much
mort___ has quit [Quit: Leaving.]
<cmtptr> I'm reading the manual now
<dmbaturin> It has some interesting bits about implemeneting persistent datastructures.
<Drup> cmtptr: I find that weird, since in most languages, the right tooling helps tremendously when starting.
<dmbaturin> Personally I find lack of command line editing and history unbearable.
<cmtptr> yeah, that's irritating but it doesn't prevent me from learning the basics
<cmtptr> and as you mentioned earlier, there's always rlwrap
<Drup> (doesn't give you autocompletion though)
<cmtptr> I seriously have never used or even wanted autocompletion in my life
<cmtptr> in any language
<ZenMatt> dmaturin: Much appreciated !
<cmtptr> well, unless we're talking about file paths in a shell
<Drup> cmtptr: which languages ? by curiosity
<cmtptr> any of them
<lyxia> cmtptr: What about command history in a REPL?
<cmtptr> lyxia, < cmtptr> yeah, that's irritating but it doesn't prevent me from learning the basics < cmtptr> and as you mentioned earlier, there's always rlwrap
<dmbaturin> ZenMatt: http://www.cs.cornell.edu/courses/cs3110/2011sp/lecturenotes.asp This one if in OCaml!
<ZenMatt> Bingo !
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
kakadu has quit [Ping timeout: 252 seconds]
boogie has quit [Remote host closed the connection]
<dmbaturin> ZenMatt: Also, http://www.cl.cam.ac.uk/teaching/Lectures/funprog-jrh-1996/ It's in CAML Light, which was _mostly_ a subset of OCaml, with rare subtle differences.
boogie has joined #ocaml
<ZenMatt> thanks pal, I have a few saved now which would keep me going :-)
boogie has quit [Ping timeout: 265 seconds]
<dmbaturin> As long as it still runs on classroom machines, people tend to put effort into improving the course content rather than translating it to another language, so CAML Light is still alive in long running courses.
badkins has joined #ocaml
virtualeyes is now known as nullremains
_um has joined #ocaml
<Drup> unfortunatly
<Drup> making generations of students thinking ocaml is a completely dead language, as caml light is.
<dmbaturin> We teach people dead literary works, dead natural science concepts, dead math... Teaching dead programming languages is consistent with it. :)
larhat has quit [Quit: Leaving.]
tianon has quit [Read error: Connection reset by peer]
<Drup> I disagree with the analogy :D
<def`> +1 :P
tianon has joined #ocaml
<dmbaturin> Drup: Why? (If anything, I'm no _advocating_ it, just making observations)
<Drup> dead literary works is not always dead and is sometimes quite relevant (it's done terribly in france though)
<Drup> dead math is not dead math, just building blocks.
<dmbaturin> Well, if it's still relevant, it's not so dead.
<Drup> that's my point, it is not.
<Drup> caml light is neither relevant nor active.
<Drup> it's just deprecated
<Drup> It's not even simpler than OCaml, since you can pretty much restrain yourself to specific parts of OCaml
<dmbaturin> By dead math I mean things like trigonometric formula transformation techniques that were once useful for calculations with tables and a slide rule, and aren't good for anything now.
<mrvn> dmbaturin: I just implemented a cos/sic table yesterday.
<mrvn> cos/sin
<Drup> dmbaturin: still a basic block, simpler than the later stuff
<mrvn> dmbaturin: C++ code though and the compiler realy doesn't like templates with 16384 parameters.
<dmbaturin> I'm not saying trigonometry is useless. What I'm talking about is teaching it by artificial and complicated examples instead of really fundamental concepts and practical examples.
<mrvn> dmbaturin: when you implement 3D graphics yourself instead of just using GL you still use all that trigonometric stuff.
<Drup> dmbaturin: that's not dead then, just badly explained.
<Drup> it's another point.
<mrvn> Doing something like this http://postimg.org/image/kdhgkvvad/full/ is a good way to teach it.
boogie has joined #ocaml
<dmbaturin> mrvn: Doing a great trigonometric survey of the school yard is also a good start. :)
AlexRussia has quit [Ping timeout: 255 seconds]
<mrvn> dmbaturin: like. pick 2 points a known distance appart and measure all the angels so you can compute the size?
mengu has quit [Ping timeout: 250 seconds]
<dmbaturin> Measure the angels? Sounds like applied theology. :)
<mrvn> or just bad typing.
<dmbaturin> Back to serious, yes, that's what I meant.
boogie has quit [Remote host closed the connection]
<mrvn> never did that in school. We measured the length of a hallway using different devices to show cummulative errors.
ZenosDance has quit [Ping timeout: 265 seconds]
boogie has joined #ocaml
not-not-pyon has quit [Ping timeout: 245 seconds]
AlexRussia has joined #ocaml
boogie has quit [Remote host closed the connection]
kakadu has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
tianon has quit [Changing host]
tianon has joined #ocaml
ZenMatt has quit [Quit: Page closed]
not-not-pyon has joined #ocaml
not-not-pyon has quit [Client Quit]
pyon has joined #ocaml
<bernardofpc> Drup: I could only make it work using D.fake_input, not F.fake_input as in your example
<bernardofpc> maybe I'll stick to using D everywhere, at least until I understand better why some elements must be D
<bernardofpc> (I guess to be sent through %() something must be a D ?)
<bernardofpc> (it's strange, since everything is supposed to be running on the client side...)
<Drup> you can send both with %
<Drup> but if you are trying to transform it with To_dom, or attach an event handler to it, it must be a D
<Drup> (or use Manip)
<bernardofpc> I need to_dom to extract its ##innerHTML
<bernardofpc> (I'm trying to adapt the example with minimal overhead)
<bernardofpc> nice to know the "evet_handler" part as well
Hannibal_Smith has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
freling has quit [Quit: Leaving.]
thomasga has joined #ocaml
JuggleTux has quit [Read error: Connection reset by peer]
JuggleTux has joined #ocaml
thomasga has quit [Client Quit]
Jefffrey has joined #ocaml
rgrinberg has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
antkong has joined #ocaml
swgillespie has joined #ocaml
larhat has joined #ocaml
antkong has quit [Ping timeout: 256 seconds]
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
seangrove has joined #ocaml
nullremains has quit [Ping timeout: 272 seconds]
matason has joined #ocaml
antkong has joined #ocaml
rand000 has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
rand000 has quit [Ping timeout: 246 seconds]
bugabinga has quit [Ping timeout: 264 seconds]
<seangrove> I'm trying to build a custom toplevel, but getting an error from ocmalfind: ocamlfind ocamlc -c -g -annot -bin-annot -safe-string -principal -package threads,utop -o myutop_main.cmo myutop_main.ml ====> ocamlfind: Error from package `threads': Missing -thread or -vmthread switch
slash^ has quit [Read error: Connection reset by peer]
<Drup> add -thread ? ^^'
<Drup> (on top of (-package threads, yes)
<seangrove> Drup: I'll try that...
<Drup> (the tag is "thread")
rgrinberg has quit [Ping timeout: 256 seconds]
mort___ has joined #ocaml
antkong has quit [Quit: antkong]
swgillespie has joined #ocaml
thomasga has joined #ocaml
oriba has joined #ocaml
ZenosDance has joined #ocaml
oriba_ has joined #ocaml
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
swgillespie has joined #ocaml
oriba has quit [Ping timeout: 245 seconds]
swgillespie has quit [Client Quit]
pyon is now known as transient-pyon
Simn has quit [Read error: Connection reset by peer]
swgillespie has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
ggole has quit []
struktured has joined #ocaml
avsm has quit [Quit: Leaving.]
reem has joined #ocaml
oriba_ is now known as oriba
mort___ has quit [Quit: Leaving.]
es917 has joined #ocaml
es917 has quit [Client Quit]
_um has quit [Remote host closed the connection]
Jefffrey has quit [Remote host closed the connection]
Jefffrey has joined #ocaml
Hannibal_Smith has quit [Quit: Leaving]
Jefffrey has quit [Ping timeout: 256 seconds]
meteo has quit [Quit: Leaving]
tianon has quit [Read error: Connection reset by peer]
Haudegen has quit [Ping timeout: 265 seconds]
tianon has joined #ocaml
rgrinberg has joined #ocaml
Haudegen has joined #ocaml
reem has quit [Remote host closed the connection]
rgrinberg has quit [Ping timeout: 265 seconds]
rand000 has joined #ocaml
reem has joined #ocaml
reem has quit [Remote host closed the connection]
reem has joined #ocaml
Nahra has joined #ocaml
<xificurC> I see polymorphic variants used as "enums", e.g. oUnit has type log_severity = [ `Error | `Info | `Warning ]. Why not just type log_severity = Error | Info | Warning? What makes one choose polyvars here?
tropico has joined #ocaml
tropico has quit [Client Quit]
<mrvn> keeps them out of the module namespace
ollehar1 has joined #ocaml
Haudegen has quit [Ping timeout: 250 seconds]
<xificurC> mrvn: not sure I understand
<axiles> you can also do subtyping
<mrvn> xificurC: you can use "match foo with `Error -> " instead of "match foo wiht OUnit.Error -> "
<xificurC> mrvn: I see, so it's just for brevity?
<mrvn> xificurC: i don't know if that is why the oUnit author choose them here. But that is one reason one can choose them.
<xificurC> mrvn: thanks
tianon has quit [Read error: Connection reset by peer]
<seangrove> What is this signature saying? val rope_of_string : string -> ('a, Blueprint.prov) XmlRope.t
<mrvn> converts a string into a rope
<seangrove> It takes a string, and returns a tuple of (sometype, Blurprint.prov) XmlRope.t
tianon has joined #ocaml
<seangrove> I guess I'm not clear on (sometype, Blurprint.prov) XmlRope.t
<seangrove> What is the XmlRope.t doing there - parameterizing the tuple?
<mrvn> that depends on the module
<mrvn> the tupöe is the parameter for the rope
<mrvn> like 'a list
Submarine has quit [Remote host closed the connection]
<seangrove> Ah, ok, so I was reading it backwards then
<seangrove> It's returning a XmlRope.t parameterized by said tuple
bugabinga has joined #ocaml
ZenosDance has quit [Ping timeout: 265 seconds]
<xificurC> the postfix notation still feels strange to me (e.g. 'a list)
<companion_cube> it's strange, yes
<xificurC> test package tips? Someone recommended oUnit not too long ago here on IRC, but I'm tempted to try something quickcheckish
<companion_cube> they serve different purposes
<companion_cube> you can combine both
<companion_cube> what are you testing?
Haudegen has joined #ocaml
The_Mad_Pirate has joined #ocaml
<xificurC> companion_cube: not much yet, slowly (very slowly) working on the hold'em AI
<xificurC> I only have some input reading done yet
<companion_cube> oh
<xificurC> no AI yet, just checks all the time :)
<companion_cube> well if you're used to unit tests, OUnit it is
<companion_cube> imho, quickcheck is nice if you want to check some invariant
<xificurC> companion_cube: sadly I'm not used to tests as VBA has 0 support for that and that's what I have to use at work
<companion_cube> :D
<xificurC> but I know them
tianon has quit [Read error: Connection reset by peer]
<companion_cube> well then, give a try to both, but for input I think regular tests (ounit) are simpler
<companion_cube> or even writing a small .ml file and run it on an input
<companion_cube> the compiler does that
<xificurC> what about stuff like pa_test or ppx_test
tianon has joined #ocaml
<companion_cube> I don't like camlp4 so the first is out for me, and ppx_test requires my code t be >= 4.02, so right now I tend to use qtest (tests in comments, pretty hackish)
<whitequark> ppx_test is super ugly inside
<companion_cube> :D
<companion_cube> it's written by a beginner, isn't it?
<whitequark> i feel dirty just reading the source
kakadu has quit []
<companion_cube> or do I confuse it with something else?
<whitequark> oh wait, no, not ppx_test
rgrinberg has joined #ocaml
<whitequark> ppx_test is not that bad actually
<whitequark> ppx_ounit
<xificurC> quickly reading through it's bitbucket main page I don't have a clue what it is
<ollehar1> possible problem: parsing xml leads to one giant match case for different tags.
<ollehar1> any meaning trying to split it?
<Leonidas> xificurC: I can recommend QCheck by companion_cube :)
<companion_cube> quickcheck-like stuff would be so much better with typeclasses
<xificurC> Leonidas: heh didn't notice it's companion_cube's
<xificurC> companion_cube: well they are coming, no?
<companion_cube> I hope so
<xificurC> or is it still distant
<xificurC> many things would probably look nicer with them
<companion_cube> but don't sell the fur before you shot the bear
<companion_cube> (or whatever translation)
<companion_cube> good night, anyway!
<nicoo> Was the sheriff a bear?
<whitequark> the hide
<nicoo> 'night, companion_cube
<whitequark> not the fur
<companion_cube> thanks whitequark
<companion_cube> but don't sell the fur (or the moustache) either
<xificurC> companion_cube: night
<whitequark> ... moustache?
<whitequark> companion_cube: fun fact, in russian version of the proverb it's not "sell", it's "divide"
<whitequark> [a joke about capitalism and communism]
<companion_cube> :)
<ia0> lol
<whitequark> dividing the hide of an undead bear
AlexRussia has quit [Ping timeout: 256 seconds]
<whitequark> (unkilled, to translate it literally, but undead is funnier)
<companion_cube> you still must kill the undead bear, but it's harder
<mrvn> whitequark: I don't have to run faster than the bear. I only have to run faster than you.
<whitequark> that went dark quickly.
<mrvn> it's allways darkest before the dawn^Wthe approaching train enters the tunnel
antkong has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
antkong has quit [Ping timeout: 256 seconds]
xificurC has quit [Ping timeout: 252 seconds]
oriba has quit [Quit: Verlassend]
Sorella has quit [Quit: Connection closed for inactivity]
MercurialAlchemi has quit [Ping timeout: 256 seconds]
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
Algebr has joined #ocaml
axiles has quit [Ping timeout: 264 seconds]
yomimono has quit [Ping timeout: 252 seconds]
antkong has joined #ocaml
<Algebr> For Cohttp.Header's map, I'm wondering if there is some reason other than convience for why it passes the value of the key of the Headers as a list rather than just a string.
<Algebr> the mli doesn't say anything in particular for map
segmond has quit [Ping timeout: 252 seconds]
axiles has joined #ocaml
RossJH has joined #ocaml
ptc has joined #ocaml
keen_________ has joined #ocaml
matason has quit [Ping timeout: 244 seconds]
keen________ has quit [Ping timeout: 246 seconds]
antkong has quit [Ping timeout: 250 seconds]
ghostpl_ has quit [Remote host closed the connection]
ptc has quit [Client Quit]
yomimono has joined #ocaml
WraithM has joined #ocaml
kaustuv has joined #ocaml
<kaustuv> Can someone explain this error (on OCaml 4.02.1)? http://pastebin.com/hBuwTQpS
<lyxia> kaustuv: I don't get an error with "type ('a, 'b) op = 'a -> 'b"
<lyxia> Oh you're asking about that error not how to fix it...
<kaustuv> Yes. I want to know what precisely is meant by "another type constructor with the same type parameters" as stated in http://caml.inria.fr/pub/docs/manual-ocaml/extn.html#sec234
<kaustuv> Specifically, why does -> not qualify as such as type constructor
ghostpl_ has joined #ocaml
j0sh has joined #ocaml
shinnya has joined #ocaml
<j0sh> does cohttp support multipart file uploads?
<j0sh> for the server component
rgrinberg has quit [Ping timeout: 264 seconds]
Algebr has quit [Ping timeout: 252 seconds]
kaustuv has left #ocaml ["ERC Version 5.3 (IRC client for Emacs)"]
transient-pyon is now known as memoized-pyon
lordkryss has quit [Quit: Connection closed for inactivity]
Jefffrey has joined #ocaml