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
<struktured> companion_cube (or the room): is it good practice to end a sequence of unit function calls with () ? I see that pattern in your code and like it to some degree as it's very clear what the function returns that way.
<Drup> what do you mean ?
<Drup> oh, foo () ; bar () ; () ?
<struktured> yeah
<Drup> I am undecided on the question
<struktured> it's definitely not a huge deal either way
<ousado> fwiw, I started doing it for some reason I'm not sure of
<dmbaturin> struktured: Well, since a sequence can return anything, I think making it clear that it returns unit is a good idea. But that's my opinion and I'm not going to force it on anyone. :)
<struktured> pros: (1) instantly know return type from a glance (2) enforces unit within an explicity type signature (3) marks the end of the chain visually
<struktured> cons: (1) 2 more characters, thus more verbose (2) the signature enforces the return value, make pro of (2) less useful
<struktured> sorry 3 more chars
<struktured> if u count the semi
<Drup> I think it would depend if the expression is within a "let () = ..."
<dmbaturin> Hhm, if you write the signature explicitly, it's more characters than ()!
<struktured> dmbaturin: yes but its kind of a necessary burden for most modules anyhow
<struktured> dmbaturin: (as in sig is in the mli file, thus enforced by type checker at compile time)
<dmbaturin> What if it's not exposed in the signature?
<struktured> Drup: yeah, I was mostly referring to top level module functions
<struktured> dmbaturin: yeah, that's a better case for ; ()
<dmbaturin> Back to my earlier question, if I want to zip to lists of unequal length ('a list -> 'b list -> ('a * 'b) option list), are there good ways to do it without checking which one is longer first?
<Drup> why do you need an option ?
<Drup> just and the list
<dmbaturin> Are patterns like ([], x) -> (None, Some x) and (x, []) -> (Some x, None) a good idea?
<Drup> I mean, zip until one of them ends and stop there
<Drup> not a bad idea, but that's not the type you wrote :p
<dmbaturin> Oh, yeah, wrong type.
<dmbaturin> ('a option, 'b option) list is what I was going to write.
reem has joined #ocaml
<dmbaturin> *
<Drup> then yes, your pattern is fine
<Drup> (but not tail-rec)
<dmbaturin> Competence goes away earlier than wakefulness. :)
reem has quit [Remote host closed the connection]
<dmbaturin> Maybe I don't need to zip it this way actually.
avsm has joined #ocaml
avsm has quit [Client Quit]
madroach has quit [Ping timeout: 264 seconds]
WraithM has quit [Quit: leaving]
madroach has joined #ocaml
reem has joined #ocaml
reem has quit [Remote host closed the connection]
teiresias has quit [Ping timeout: 246 seconds]
teiresias has joined #ocaml
MrScout has quit [Ping timeout: 250 seconds]
reem has joined #ocaml
ptc_ has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
grb has quit [Remote host closed the connection]
MrScout has joined #ocaml
MrScout has quit [Read error: Connection reset by peer]
Pepe__ has quit [Read error: Connection reset by peer]
Pepe_ has joined #ocaml
shinnya has quit [Ping timeout: 256 seconds]
in-pyon-itesimal is now known as cloud-pyon
darkf has joined #ocaml
jao has quit [Ping timeout: 246 seconds]
ygrek has joined #ocaml
ghostpl_ has quit [Remote host closed the connection]
badkins has quit []
<sdegutis> What do you think of http://chaudhuri.info/misc/fwocaml/ ?
q66 has quit [Quit: Leaving]
teiresias has quit [Ping timeout: 240 seconds]
Denommus has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
teiresias has joined #ocaml
bytbox has quit [Ping timeout: 252 seconds]
<tokenrove> sdegutis: i thought that was pretty sane. i don't disagree with the ocaml developers' decision to maintain strict backwards-compatibility (especially since i recently built some of my own code untouched since 2002 with only warnings), but i sometimes wish there was a "modern mode".
<dmbaturin> Substantial part of it is about reviving SML features that were omitted from ocaml. :)
<tokenrove> (and of course, some of that stuff is changing, like immutable strings)
<tokenrove> since we know historically that Worse is Better wins, clearly OCaml was a gambit to worse-is-better SML and it seems to have done a great job.
teiresias has quit [Ping timeout: 246 seconds]
reem has quit [Remote host closed the connection]
teiresias has joined #ocaml
<sdegutis> tokenrove: hmmmmmm
ghostpl_ has joined #ocaml
reem has joined #ocaml
<sdegutis> tokenrove: Thanks for your feedback. It helped me realize that I'll probably always be on-the-fence about using OCaml, because it's in a class of languages which are all so much better than other languages, so that they make me want to aim for perfection, and the smallest, most-first-world problems seem like show-stoppers.
<sdegutis> tokenrove: in other words, OCaml is so good that it makes me want it to be perfect, and it makes me completely dissatisfied when I find any shortcomings in it, which cause me to stick with the crappier tools I already use
<tokenrove> i understand that completely.
<sdegutis> That's why I switched back and forth between OCaml and Haskell several times.
<sdegutis> But ultimately I haven't written anything in either!
ghostpl_ has quit [Ping timeout: 256 seconds]
reem has quit [Remote host closed the connection]
tnguyen has quit [Quit: tnguyen]
tnguyen has joined #ocaml
reem has joined #ocaml
manud has quit [Quit: manud]
uris77 has joined #ocaml
cloud-pyon is now known as whn-pyon
psy_ has quit [Ping timeout: 256 seconds]
matason has joined #ocaml
matason has quit [Ping timeout: 265 seconds]
<whitequark> companion_cube: containers.io? no
ghostpl_ has joined #ocaml
ghostpl_ has quit [Ping timeout: 244 seconds]
<struktured> sdegutis: nothing in that link makes me really upset with ocaml, although some of those things would be nice
<dmbaturin> In SML pervasives there's composition operator named "o" to imitate the mid dot, so you can't call a variable "o" without having something else in your code break in spectacular way.
<whn-pyon> dmbaturin: You can use "nonfix o" and only then redefine o.
<sdegutis> lol
<whn-pyon> But I have no idea why anyone would deprive themselves of the function composition operator.
<sdegutis> thats a facepalm feature
<dmbaturin> (In defense of non-special character operators, SML orelse and andalso are probably the most intuitive names for respective boolean functions)
<whn-pyon> lol, ok, those are silly
<whn-pyon> But I suspect they're deliberately so, to encourage you to use pattern matching instead of booleans.
<dmbaturin> whn-pyon: I'm not against the operator, just the name. :)
<whn-pyon> dmbaturin: I guess the problem is that . is already used for using module members. And they did not want to complicate the language definition by treating . in two different ways.
<dmbaturin> Yeah, and andalso probably comes from "and" already used for mutually recursive definitions.
uris77 has quit [Quit: leaving]
<whn-pyon> Standard ML lacks lots of no-brainer features - as in, "not advanced at all, anyone sane would add it".
<whn-pyon> One of the most annoying IMO are guards. Although most of the time I want to use pattern matching, sometimes a guard is nice.
antkong has quit [Ping timeout: 252 seconds]
<dmbaturin> But I genuinely like andalso and orelse anyway. Unlike || and && their semantics should be obvious to those who see them the first time.
<whn-pyon> You have a point there.
<dmbaturin> I wonder if anyone tried to teach ML to school kids with no prior exposure to programming at all.
<sdegutis> which ML would be best for that?
<dmbaturin> School courses tend to stay the same for many years once developed, a fossilized ML like SML or CAML Light would work best.
whn-pyon is now known as sus-pyon-sion
psy_ has joined #ocaml
<dmbaturin> (The biggest problem with teaching anything to kids is that schools are not at all free in their choice of course material)
ebzzry has quit [Remote host closed the connection]
antkong_ has joined #ocaml
sdegutis has quit [Quit: Leaving...]
Axle has joined #ocaml
Axle has quit [Client Quit]
<sus-pyon-sion> dmbaturin: Standard ML would probably be best for kids. It is nice that Standard ML prevents stuff like "val rec xs = 1 :: xs", so you can actually reason about datatypes by induction. Also, "abstype", while underpowered compared to the module system, is probably easier to teach to kids, so you can give them a taste of type abstraction, without going down the rabbit hole with modules and functors.
ghostpl_ has joined #ocaml
ghostpl_ has quit [Ping timeout: 246 seconds]
myst has quit [Read error: Connection reset by peer]
MercurialAlchemi has joined #ocaml
<dmbaturin> sus-pyon-sion: A compiler for kids probably should have more extensive error reporting and some guessing about common errors though.
leowzukw has joined #ocaml
swgillespie has joined #ocaml
sus-pyon-sion has quit [Quit: I'm sorry but... I don't have any interest in three-dimensional girls.]
AlexRussia has quit [Ping timeout: 246 seconds]
teiresias has quit [Ping timeout: 256 seconds]
teiresias has joined #ocaml
AlexRussia has joined #ocaml
symmetric-pyon has joined #ocaml
swgillespie has quit [Quit: Textual IRC Client: www.textualapp.com]
antkong_ has quit [Quit: antkong_]
ygrek has quit [Ping timeout: 255 seconds]
Simn has joined #ocaml
antkong has joined #ocaml
reem has quit [Remote host closed the connection]
reem has joined #ocaml
reem has quit [Remote host closed the connection]
larhat has joined #ocaml
antkong has quit [Ping timeout: 244 seconds]
ghostpl_ has joined #ocaml
ghostpl_ has quit [Remote host closed the connection]
ghostpl_ has joined #ocaml
reem has joined #ocaml
huza has joined #ocaml
martintrojer has quit [Max SendQ exceeded]
reem has quit [Remote host closed the connection]
martintrojer has joined #ocaml
reem has joined #ocaml
reem has quit [Remote host closed the connection]
Haudegen has quit [Ping timeout: 264 seconds]
psy_ has quit [Quit: Leaving]
leowzukw has quit [Remote host closed the connection]
reem has joined #ocaml
reem has quit [Remote host closed the connection]
teiresias has quit [Ping timeout: 252 seconds]
teiresias has joined #ocaml
reem has joined #ocaml
Haudegen has joined #ocaml
reem has quit [Remote host closed the connection]
reem has joined #ocaml
huza has quit [Quit: WeeChat 0.3.8]
freling1 is now known as freling
<freling> dmbaturin: I learned programming with OCaml, I had no prior experience
govg has quit [Ping timeout: 250 seconds]
<flux> hmm, is the "A with type t := u" -syntax documented in the manual?
AlexRussia has quit [Ping timeout: 252 seconds]
dsheets_ has quit [Ping timeout: 252 seconds]
symmetric-pyon is now known as undecidable-pyon
tane has joined #ocaml
psy_ has joined #ocaml
psy_ has quit [Max SendQ exceeded]
psy_ has joined #ocaml
govg has joined #ocaml
zpe has joined #ocaml
ontologiae has joined #ocaml
dsheets_ has joined #ocaml
ontologiae has quit [Ping timeout: 264 seconds]
huza has joined #ocaml
<Leonidas> companion_cube: yeah, that's what I did in the end.
matason has joined #ocaml
captain_furious has joined #ocaml
Kakadu has joined #ocaml
reem has quit [Remote host closed the connection]
AlexRussia has joined #ocaml
reem has joined #ocaml
thomasga has joined #ocaml
AlexRussia has quit [Ping timeout: 250 seconds]
leowzukw has joined #ocaml
dav has quit [Remote host closed the connection]
huza has quit [Quit: WeeChat 0.3.8]
ousado has quit [Remote host closed the connection]
ousado has joined #ocaml
ousado has quit [Changing host]
ousado has joined #ocaml
litter has joined #ocaml
yaewa has joined #ocaml
Simn has quit [Read error: Connection reset by peer]
moei has quit [Ping timeout: 272 seconds]
Guest23129 has joined #ocaml
reem has quit [Remote host closed the connection]
Haudegen has quit [Ping timeout: 245 seconds]
reem has joined #ocaml
avsm has joined #ocaml
keen__________74 has quit [Read error: Connection reset by peer]
govg has quit [Quit: leaving]
myyst has joined #ocaml
myyst is now known as myst
keen__________74 has joined #ocaml
reem has quit [Ping timeout: 265 seconds]
vanila has joined #ocaml
Guest23129 is now known as Simn
Haudegen has joined #ocaml
_andre has joined #ocaml
Anarchos has joined #ocaml
litter has quit [Ping timeout: 264 seconds]
litter has joined #ocaml
avsm has quit [Quit: Leaving.]
undecidable-pyon is now known as in-pyon-itesimal
octachron has joined #ocaml
thomasga has quit [Quit: Leaving.]
ebzzry has joined #ocaml
yomimono has joined #ocaml
Nahra has quit [Remote host closed the connection]
dmiles_afk has quit [Ping timeout: 246 seconds]
ygrek has joined #ocaml
dsheets_ has quit [Ping timeout: 255 seconds]
ggole has joined #ocaml
litter has quit [Ping timeout: 250 seconds]
litter has joined #ocaml
ygrek has quit [Ping timeout: 245 seconds]
teiresias has quit [Ping timeout: 255 seconds]
teiresias has joined #ocaml
Submarine has quit [Remote host closed the connection]
<haesbaert> I'm slightly confused, how to I char if a char/byte is ascii ?
<haesbaert> shoudl I do int_of_char and compare against < 127 ?
<def`> how do you what?
<haesbaert> I'm reading a file with input_char, and I want to determine if the char in question is ascii or not
<def`> (a verb is missing)
<def`> ok, if c < '\x80' maybe
<haesbaert> got it, second question, should I be using bytes or char ?
<haesbaert> ah Bytes is a collection, my bad.
<def`> yep
<companion_cube> struktured: I like to end with (), yes, because it's harder to break when you add/remove a statement
shinnya has joined #ocaml
<haesbaert> def`: but if char is 8bit unsigned, what is the use of input_byte, is it equivalent to: int_of_char (input_char stdin)
<haesbaert> doc says: Same as Pervasives.input_char, but return the 8-bit integer representing the character. Raise End_of_file if an end of file was reached.
rwmjones has quit [Read error: Network is unreachable]
rwmjones has joined #ocaml
<flux> external input_char : in_channel -> char = "caml_ml_input_char"
<flux> external input_byte : in_channel -> int = "caml_ml_input_char"
<flux> so they are literally the same, only different type :)
<haesbaert> awesome, thanks :D
<Drup> haesbaert: char = int
<Drup> they are literally the same.
matason has quit [Ping timeout: 245 seconds]
psy_ has quit [Remote host closed the connection]
AlexRussia has joined #ocaml
<whitequark> Drup: um, no? it's private int
<Drup> yes, I know ...
madroach has quit [Quit: leaving]
octachron has quit [Quit: Leaving]
dsheets_ has joined #ocaml
thomasga has joined #ocaml
<whitequark> i mean, it's a different type. it has a different range
<whitequark> same representation, sure
<Drup> that's what I wanted to express :)
<companion_cube> it would be interesting if char was actually a private alias to int
<haesbaert> are the iscntrl/isalpha/isdigit/isprint... so on from libc anywhere ?
<haesbaert> iscntrl seems pointless to rewrite, need to import a table and a bunch of stuff.
<Drup> huuum
<Drup> in BatChar ;D
* Drup launches companion_cube at the Char module
<haesbaert> ohhhhhhh
<companion_cube> hey
<haesbaert> Drup: no iscntrl :(
<companion_cube> that would actually be interesting to have, but I'm far too lazy right now
<companion_cube> it's funnier playing with Lwt_pipe :>
<Drup> haesbaert: add it !
tane has quit [Quit: Verlassend]
<haesbaert> can do
<whitequark> put it into your Lwt_pipe and smoke it
<companion_cube> tsk tsk
AlexRussia has quit [Ping timeout: 256 seconds]
Submarine has joined #ocaml
AlexRussia has joined #ocaml
govg has joined #ocaml
dsheets_ has quit [Ping timeout: 252 seconds]
<ggole> The char operations aren't really safe on ints though
madroach has joined #ocaml
<ggole> You can easily get the toplevel to segfault by playing with Char.unsafe_chr
osheeta has joined #ocaml
avsm has joined #ocaml
tane has joined #ocaml
govg has quit [Quit: leaving]
govg has joined #ocaml
testcocoon has quit [Ping timeout: 246 seconds]
AlexRussia has quit [Ping timeout: 250 seconds]
darkf has quit [Quit: Leaving]
AlexRussia has joined #ocaml
<companion_cube> (o/ Drup)
<Drup> yeah
dsheets_ has joined #ocaml
testcocoon has joined #ocaml
paolooo has joined #ocaml
mengu has joined #ocaml
<MercurialAlchemi> is there a nicer idiomatic solution to the issue of getting the user info from a type like 'SubscribedUser of userinfo | UnsubscribedUser of userinfo' than a get_userinfo function?
<Drup> let (SubscribedUser user | UnsubscribedUser user) = foo in ..
<Drup> not much better, and harder to update
<Drup> but ...
<MercurialAlchemi> yeah
<MercurialAlchemi> you don't want to have many different types of users you manipulate in different places with this system :)
<companion_cube> rha, I miss linear types
<MercurialAlchemi> why?
ghostpl_ has quit [Remote host closed the connection]
<companion_cube> I need to express the fact that some operators consume their arguments
<companion_cube> because: resource handling
<companion_cube> this is the hard part about IO iterators
<MercurialAlchemi> hm
<MercurialAlchemi> can't you use a monad?
<Drup> you can still leak the ressource using a reference and all taht
<MercurialAlchemi> well, it's not foolproof
<MercurialAlchemi> but neither is the lock on my house
larhat has quit [Quit: Leaving.]
larhat has joined #ocaml
larhat has quit [Client Quit]
Algebr has joined #ocaml
<Algebr> What's the best way to go about the following, you are using third party code that you have src and now want to put a breakpoint/print in. Is there an elegant opam way to recompile the code?
<companion_cube> if you have the repository in foo/, opam pin add <package> foo can help
<companion_cube> if the changes are committed, opam pin add <package> -k git <path>
WraithM has joined #ocaml
<Drup> the -k git is not very useful now
<Algebr> can I then recompile the package?
<Drup> Algebr: opam will recompile it
badkins has joined #ocaml
ptc has joined #ocaml
ptc is now known as Guest60773
shinnya has quit [Ping timeout: 264 seconds]
<Drup> thomasga, dsheets_ : dev-repo is 1.1 or 1.2 ?
<Drup> (opam)
<dsheets_> dunno
<dsheets_> but 1.1 complains when the opam-version is 1 and dev-repo is present
mengu has quit [Remote host closed the connection]
<Drup> I think it's 1.2, I'll let opam downgrade appropriatly, it knows better
MrScout has joined #ocaml
freling1 has joined #ocaml
freling has quit [Ping timeout: 250 seconds]
ned has joined #ocaml
mengu has joined #ocaml
badkins has quit []
paolooo has quit [Ping timeout: 246 seconds]
freling1 has quit [Read error: No route to host]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
freling has joined #ocaml
MrScout has quit [Remote host closed the connection]
JuggleTux has quit [Ping timeout: 256 seconds]
Submarine has quit [Ping timeout: 256 seconds]
badkins has joined #ocaml
<Leonidas> what happened with thelema? I haven't seen him in a long time.
MercurialAlchemi has quit [Remote host closed the connection]
<Drup> he flies by, ocasionnaly
<Drup> I talked to him 3/4 month ago, I think
mengu has quit []
freling has quit [Quit: Leaving.]
MercurialAlchemi has joined #ocaml
cdidd has quit [Ping timeout: 246 seconds]
<dmbaturin> If I want multiple modules to share the same signature, where does the signature go in my source tree?
<dmbaturin> More of a theoretical question, I don't think I need it right now.
AlexRussia has quit [Ping timeout: 255 seconds]
<companion_cube> you can write somewhere in foo.ml (say) module type S = sig ... end , then a.ml and b.ml, such that a.mli is include Foo.S, and b.mli is the same
AlexRussia has joined #ocaml
MrScout has joined #ocaml
<dmbaturin> companion_cube: Ah, sounds reasonable. Thanks.
<Drup> note that if there is only a signature in it, you can have a .mli alone
WraithM has quit [Quit: leaving]
<ggole> You can probably abuse module type of, too.
<companion_cube> probably
<ggole> (If there is no .mli)
<Drup> avoid abusing module type of
<Drup> if you can define a signature for it, it's better
MrScout has quit [Ping timeout: 246 seconds]
<ggole> Doesn't that mean defining it twice (if you don't have a nested signature)?
<Drup> not if you define it only in a .mli and use it everywhere else
<Drup> the issue with that is that ocamldoc is crap
<ggole> How do you "use it everywhere else" without module type of or duplicating?
<Drup> but that's an issue on the verged of being solved
<Drup> ggole: well, module M : S
hilquias has quit [Ping timeout: 250 seconds]
<ggole> Right, but if you have foo.ml and foo.mli and no explicit module, you have to either use module type of or create such a nested module (type).
<Drup> include S
cdidd has joined #ocaml
<Drup> (in foo.mli)
<ggole> I don't see the advantage
<Drup> no duplication.
<Drup> if foo and bar implement the same interface
<ggole> There's no duplication with module type of either?
ned has quit [Ping timeout: 252 seconds]
<Drup> the issue with module type is that it's behavior is very subtle
<dmbaturin> So if I have multiple .mli's with include, ocamldoc gets it right?
<ggole> You have foo.ml, foo.mli with a normal signature, bar.ml, and bar.mli with include module type of Foo
<Drup> also, if you want "the module + an equality", it will be delicate
<ggole> Hrm, OK
<Drup> also, if you want to create a functor, using a signature is nicer
<Drup> dmbaturin: errr, meh.
travisbrady has joined #ocaml
segmond has quit [Ping timeout: 250 seconds]
dmiles_afk has joined #ocaml
<nicoo> Drup: Doesn't `module type of` work in functors? (Not that I advocate its use ...)
weykent has quit [Quit: ZNC - http://znc.in]
<Drup> sure it works
<Drup> it doesn't work nicely, though
olauzon has joined #ocaml
ned has joined #ocaml
segmond has joined #ocaml
ned is now known as Guest24880
psy_ has joined #ocaml
slash^ has joined #ocaml
Guest24880 is now known as ned
sdegutis has joined #ocaml
<sdegutis> Is there an easy way to turn [1,2,3,4] into [[1,2],[2,3],[3,4]]?
<Drup> iterate elements in the list two by two
<Drup> (I guess you meant ";" everywhere)
<sdegutis> Drup: so I have to do this procedurally?
<Drup> nope
<tane> in this special case tail (map (fun i -> (i-1,i)) l) should do
<tane> but i guess it's just an example case :)
<Algebr> Is there a meaning to the . in the signature 'a. ?position:int -> ?expand:bool -> (#t as 'a) -> unit
<mrvn> let conv = function [] -> raise Error | x::xs -> let rec loop x xs = match xs with [] -> [] | y::ys -> [x, y] :: (loop y ys) in loop x xs
<whitequark> it's a separator
<mrvn> Algebr: yes
<Drup> mrvn: stop giving answer ...
<Drup> well, at least not the complete one, it's useless
<sdegutis> mrvn: so there's no built-in function for this?
<sdegutis> Heh.
<Drup> sdegutis: no built in, no
<mrvn> sdegutis: no
ontologiae has joined #ocaml
<sdegutis> Basically I just want clojure.core/partition
<Drup> partition ? that's not a partition
<sdegutis> Drup: I never said clojure names things correctly
<whitequark> it's not ruby, it doesn't have built-in functions for everything and a kitchen sink
<whitequark> containers has some useful stuff
<def`> that's not clojure.core/partition then
<Drup> what is this function doing ?
<mrvn> Drup: useless? # conv [1;2;3;4];;
<mrvn> - : (int * int) list list = [[(1, 2)]; [(2, 3)]; [(3, 4)]]
<Drup> mrvn: you don't understand ...
<Drup> if you give someone the complete solution
<def`> mrvn: he has its teacher hat
<Drup> they are not going to look for it
<sdegutis> Drup: It's like a chunks-of-size function, but lets you change the step (which defaults to chunk-size)
<sdegutis> It's incredibly useful.
<Drup> they will not learn anything
<mrvn> The rest is left to the reader so he doesn't just cut&paste the answere
<sdegutis> I assumed it was a basic FP thing.
<def`> sdegutis: but that's not what your example show
<sdegutis> def`: sure, if you call it with chunkSize=2 and step=1
<Drup> mrvn: you should never give the complete solution directly
<sdegutis> def`: step meaning how far do you go forward after each iteration
<sdegutis> or whatever
<Drup> let the person look a bit, and if he's stuck, then yeah
<def`> ah right, you allow overlap
<def`> ok
<sdegutis> I'm currently using it a bit like a doubly-linked list.
<sdegutis> Although to be honest I think I'll just use a doubly-linked list.
<def`> then write a drop function, a take function, compose both, and that's it. 10 lines.
<Drup> sdegutis: that would not be too difficult to do, you could reimplement it yourself and propose it to batteries
<sdegutis> Drup: sure sure
<sdegutis> def`: 10 lines? wow
<Drup> I must say, it doesn't sound very useful
<companion_cube> why is this useful? chunking by varying sizes
<sdegutis> Drup: I use it to easily give me previous/current/next things out of a list and a given position in the list
yomimono has quit [Ping timeout: 245 seconds]
<sdegutis> I append nil to both ends so that I know if there's nil, there's no previous or next.
<Drup> but that's terribly innefficient and you should not use a list for this purpose to begin with
<ggole> Seems a bit like you should be using an array
<companion_cube> or a list zipper
<sdegutis> ggole: yeah I'm using an array actually
ontologiae_ has joined #ocaml
<Drup> is this kind of thing common in clojure ?
<sdegutis> Drup: probably not
<sdegutis> Drup: I'm not very good at idiomatic Clojure or FP
<sdegutis> Drup: so I'm not representative of Clojurists
q66 has joined #ocaml
<sdegutis> def`: thanks
ontologiae has quit [Ping timeout: 244 seconds]
<def`> (limit conditions may not behave as you expect, that's left as an exercice :D)
<sdegutis> you callin me fat
<Drup> (efficiency is left as an exercise too :D)
<def`> Drup: why do you think it's inefficient ?
<Drup> it will do at least two passes on each elements, you can shave one
<def`> "pfff"
<Drup> (and list is not the right tool :D)
<def`> unless you specialize for step == n case, that's not worth it
<Drup> probably
oriba has joined #ocaml
<ggole> The function itself is inefficient, copying the same subsequence modulo one at the end over and over.
<def`> I can see the use of a function grouping sequences by fixed-size batch for processing
<sdegutis> Drup: would you use array instead?
<ggole> You could use a pair list + n and share all the structure
<Drup> sdegutis: if the goal is just to have a way to get the neighbour, I would use a zipper
<companion_cube> +1
<companion_cube> def`: there's something like this in iterators, in general
Submarine has joined #ocaml
Submarine has joined #ocaml
<companion_cube> e.g., Gen.chunks ;)
<def`> Drup: which would make sense if you need to traverse the structure in both directions, but if you don't, it's less efficient :), you can do that without allocations.
<Drup> some allocations, but far less traversing
Submarine has quit [Ping timeout: 246 seconds]
leowzukw has quit [Quit: Lost terminal]
Submarine has joined #ocaml
thomasga has quit [Quit: Leaving.]
ontologiae_ has quit [Ping timeout: 256 seconds]
MrScout has joined #ocaml
<sdegutis> Drup: um
Kakadu has quit [Quit: Page closed]
Submarine has quit [Ping timeout: 246 seconds]
Submarine has joined #ocaml
<travisbrady> Drup: I’m looking at your lmdb bindings. What is your impression of lmdb? Would you use it or your bindings in production? I have a use case where I think it may work well.
dsheets_ has quit [Ping timeout: 264 seconds]
<Drup> So.
<Drup> the bindings is not finished
<Drup> there is a todo note somewhere
<Drup> I haven't got time to work on it, but if you are motivated, go on
<Drup> my opinion of lmdb is that the C interface is awful and highly annoying to bind.
<Drup> (from the technical point of view, it seems very good though)
<travisbrady> Ay, ok. Thanks you. I read through the lmdb headers and on first glance it did look hairy.
zpe has quit [Remote host closed the connection]
<Drup> yeah, it's very annoying
<travisbrady> I’ve done some rough benchmarking (with the Python lib) and was impressed
<Drup> lot's of conf flag that disable or enable features, dynamic flag that changes if arguments are in or out, and so on
sdegutis has left #ocaml ["Leaving..."]
<Drup> in the python binding, they took the decision not to support the whole library, and I decided to do the same
<Drup> the big spiky point remaining is the iterator interface
<Drup> (I'm rather happy with the functorial thingy)
ggole has quit []
captain_furious1 has joined #ocaml
captain_furious has quit [Ping timeout: 246 seconds]
larhat has joined #ocaml
<Algebr> Anyone used/gone through that Ocaml for scientists book?
<ned> i skimmed it, its not worth buying
<ned> don syme likes it though so..
<Algebr> Its rather pricey
dav has joined #ocaml
Kakadu has joined #ocaml
<Drup> hey but, that's harrop's book =')
<Algebr> I looked through the free chapter 1 and it looked pretty good, imo...
antkong has joined #ocaml
<Algebr> Is there no way to do something like type foo = Bar of {col:int}
<Algebr> rather, is this currently unsupported because its a bad idea
<Drup> next version of ocaml !
<def`> this is currently unsupported because it involves hacking a bit around the type system
<def`> but this feature was requested, so it's integrated in next version
<Algebr> neat
<Algebr> Anyone know any OCaml jobs in NYC besides Jane Street?
<Drup> smondet: you are NYC now, aren't you ?
Haudegen has quit [Ping timeout: 246 seconds]
<Drup> and there is bloomberg too I think
<def`> smondet was at NYU, where they do OCaml in biolab
<def`> and he moved to another position where I think he still work with OCaml but you'll have to wait for him to know more…
octachron has joined #ocaml
Anarchos has joined #ocaml
Haudegen has joined #ocaml
<smondet> Algebr: Drup: yes, I'm in NYC working mostly in OCaml
<smondet> My lab has some OCaml. Bloomberg and facebook are also doing ocaml in NYC + some startups
<Drup> your lab seem to use lots of various languages
<Algebr> smondet: are you in the hammerlabs thing or is that the commericial project for Mount Sinai?
antkong has quit [Ping timeout: 252 seconds]
<smondet> I'm in the hammer lab
<smondet> Algebr: are you already in NYC?
Sim_n has joined #ocaml
<Algebr> yep, Queens. I emailed hammerlabs and was told they were only looking for user experience web developers and applied machine learning programmers.
<Algebr> heh, but I took computational learning theory last semester, which admittely isn't applied =/
Simn has quit [Ping timeout: 252 seconds]
<Algebr> ( in any case what is applied machine learning anyway, coding perceptrons and svms?)
<smondet> you should come by next time: http://www.meetup.com/NYC-OCaml/ some of the startups look for people / contract work
<struk|work> smondet: does hammerlab have a web page listing open positions?
<smondet> struk|work: not yet, it's all pretty young, I can put you in contact with Jeff directly if you want
manud has joined #ocaml
<struk|work> smondet: hm let me mull it over a bit, thanks though . I'm a little expensive I fear
<Algebr> ah, Jeff was the guy that emailed me back.
<smondet> Jeff Hammerbacher, the "hammer" in "hammer lab" :)
<Algebr> smondet: no interns either?
<smondet> not in the computing side (only experience people), we'll get maybe interns on the wetlab side (biology, pipettes and stuff)
<Drup> "I'm a little expensive I fear" =')
<Algebr> bummer.
oriba has quit [Quit: Verlassend]
<smondet> Algebr: did you see that one: http://www.meetup.com/NYC-OCaml/messages/76314929/ ?
octachron has quit [Quit: Leaving]
<struk|work> Drup: it's not cheap living in NYC you know :)
<Drup> I live in paris.
<Algebr> smondet: whoa, I didn't see that, nice thanks!
<Drup> is this for NY or Manhattan ?
<smondet> struk|work: yes it' a better deal but these stats are completely boggus, it's mostly because the US is a 3rd world country
<Drup> (and anyway, as a phd student, my salary is ridiculous, so well)
<struk|work> Drup: all boroughs I think, not sure..93% is pretty funny difference in rent though
<Drup> yeah
<smondet> Drup: in avg Phd-students in france are much better paid than in the US
<Drup> poor american phd students
<struk|work> Drup: don't worry, many of them eventually end up as hedge fund managers
<Drup> (well, getting a phd is very difference in france and in USA)
<Drup> (in france, you are expected to be full time on it, and in science it's supposed to last no more than 3 year)
<struk|work> Drup: the whole use education system / loan programs are such a mess
<ned> Drup, here its 5 years and fulltime at like 30k, unless youre in quant finance, numerical methods, or computational fluid dynamics youre not going to be making much afterwards either ;)
<struk|work> *use/USA
<Drup> struk|work: I know
_andre has quit [Quit: leaving]
slash^ has quit [Read error: Connection reset by peer]
WraithM has joined #ocaml
<Kakadu> Where can I found recursive descent parser with sane error reporting? (need to know how parsers are written)
dsheets_ has joined #ocaml
<Kakadu> I used combinators a lot and now I don't understand how to live without ('rez, 'err) result = Parsed of 'rez * 'err * stream | Failed of 'err
<ned> kakadu, the definitive text on parsers is 'parser techniques second edition'
<ned> its not ocaml specific but it'll go over LR, LALR, LL(k), LL(1) etc
Sim_n is now known as Simn
<Kakadu> thanks, I'll look in it
<Algebr> Drup: say I call something with Lwt_engine.on_timer, how can I later on kill that thread?
<Algebr> oh nvm, stop_event on the returned event i guess?
<Anarchos> ned the dragon book ?
<ned> Anarchos, he wanted something specific on parsing, not lexing, parsing, optimization, code gen, etc
<ned> the dragon book is kinda good too i guess
<Anarchos> ned ok . I find it a bit old nowadays
<Anarchos> like storing types in bit arrays...
<ned> depending on what youre doing that might be useful :v
<Kakadu> I hope whole book is as good as its introduction is, ned
<Drup> and dragon book is very old school
<Drup> compilers are not really done this way anymore
<ned> kakadu, it is
<ned> Drup, no but if he wanted to really get a grasp of how compilers are done he'd probably have to spend an entire phd on it to be honest
<Drup> not really, no
<ned> even writing a front-end to target llvm to do something trivial will take a while
<Drup> not an entire phd :D
<Anarchos> Drup 2 PhD ?
<Drup> I mean, SSA is not that hard to grasp, the algorithms to get in and out of SSA are very well documented
Guest60773 has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
<Drup> code emission is messy, but the good part is that unless you really want, you don't need to care anymore, because llvm
<Anarchos> Drup the only interesting part is the code optimizer...
<Drup> and that part is done in SSA or before
ptc has joined #ocaml
ptc is now known as Guest88462
<Anarchos> Drup static single assignment ?
<Drup> yeah
<Anarchos> i already found this idea of SSA a bit messy
avsm has quit [Quit: Leaving.]
<Anarchos> i am sure compilers miss some optimizations because of it
avsm has joined #ocaml
avsm has quit [Client Quit]
<Drup> considering it makes everything much easier to compose and to write, it's an acceptable trade off
yaewa has quit [Quit: Leaving...]
<Anarchos> Drup maybe it is time to consider other ways to do it ?
travisbrady has quit [Quit: travisbrady]
<Drup> it's always time to consider better way to do things, but unless you have one ... ;)
travisbrady has joined #ocaml
<Anarchos> Drup no idea but the idea that a compiler is not able to do optimal compilation always disturbed my mind
<Drup> errr
<Drup> There is no such thing as optimal compilation
<Drup> first because there is no such thing (it's a trade off between various metrics, space not being the only one)
<Drup> second because processors architectures are insane and it's absolutely impossible to optimize for them
<Anarchos> Drup i know all those points.
<Drup> third, because it's undecidable >_>
<Drup> (how to now if a problem is undecidable : "It is an interesting problem ?" "Yes !" "Then it's undecidable")
raphaelss has joined #ocaml
reem has joined #ocaml
shinnya has joined #ocaml
<Anarchos> interesting argument :)
<Anarchos> apply too at politics lol
<dmbaturin> How is LLVM intermediate representation is normally produced?
<Drup> by a front end ?
<dmbaturin> Yep.
<Drup> what's the question ? ^^'
thomasga1 has joined #ocaml
Thooms has joined #ocaml
<dmbaturin> Drup: How front-ends produce intermediate representation. That is, does LLVM provide some routined to simplify emitting its text?
<dmbaturin> * routines
<Drup> Ah.
<Drup> A little bit, but not much
ghostpl_ has joined #ocaml
<Algebr> Is there a way to do C's static variable in an ocaml function ?
<smondet> struk|work: don't need an excuse to go drink vodka in montreal :)
sdegutis has joined #ocaml
<sdegutis> Hi nerds. Got any recommendations for a superlative ergonomic keyboard? Price is no object. (It's a value.)
tane has quit [Quit: Verlassend]
<Anarchos> Algebr use C interfacing ?
<Anarchos> dmbaturin what kind of keyboard is that ? It reminds me that D. Knuth spoke of such keyboards with some math symbols
Kakadu has quit [Remote host closed the connection]
<dmbaturin> Anarchos: MIT lisp machine keyboard. According to legends, by using the shift/super/hyper/meta keys you could type a lot of symbols, mathematical or otherwise.
travisbrady has quit [Quit: travisbrady]
Submarine has quit [Remote host closed the connection]
<dmbaturin> Also, that keyboard is the reason emacs and some other cross-platform software that makes extensive use of keyboard shortcuts usually refer to "super" and "meta" keys rather than e.g. windows key and alt key.
<sdegutis> This is good joke,
<sdegutis> Thanks,
<Drup> you are welcome :D
travisbrady has joined #ocaml
captain_furious1 has quit [Quit: Leaving.]
<tokenrove> speaking of montreal, any interest in an ML (OCaml, SML, F#, etc) meetup in Montreal?
AlexRussia has quit [Ping timeout: 264 seconds]
<dmbaturin> I would attend, if I lived in Montreal. :)
litter has quit [Quit: Lost terminal]
MrScout has quit [Ping timeout: 250 seconds]
<struktured> tokenrove: I am trying to manufacturer an excuse to go to montreal within next 2 months, start a meetup and host a conference or something :)
<tokenrove> struktured: i'll see what i can do. :-)
<tokenrove> the Haskell meetup is pretty receptive to ML people, but it would be nice to be able to have ML-specific talks.
<Algebr> what package is needed to compile something that uses Lwt.Infix?
<Drup> lwt, last version
<Algebr> hmm, I am using lwt, I guess that means I have outdated lwt
<Algebr> Drup: Just plain old -package lwt right
avsm has joined #ocaml
jao has joined #ocaml
jao has quit [Changing host]
jao has joined #ocaml
olauzon has quit [Quit: olauzon]
Algebr has quit [Remote host closed the connection]
sdegutis has left #ocaml ["Leaving..."]
larhat has quit [Quit: Leaving.]
<struktured> tokenrove: you do ocaml for a living in montreal?
<tokenrove> struktured: yes, although not only ocaml. (much more f# last year than ocaml, and other languages)
<struktured> tokenrove: still not so bad, cool.
<ousado> struktured: are you german?
travisbrady has quit [Quit: travisbrady]
<struktured> ousado: nope, american mutt (italian + irish bloodlines)
<ousado> (just asking because your use of the phrase "not so bad")
<struktured> ousado: that's a german thing? hmm thought it was more common than that
<ousado> germans tend to answer sentences like "I just made a billion $, 2 gold medals in the olympics and saved 5000 lives" with "not bad"
<struktured> understatement, the opposite of american culture
<ousado> in that light it doesn't sound so bad :)
<Simn> ousado, now I'm waiting for the day when you announce that you've finished implementing the GC even more.
<tokenrove> has anyone here used jenga and have any thoughts on it? especially, has anyone used it across both unix and windows platforms?
<struktured> multicore gc??
<ousado> not for ocaml, for haxe
<ousado> Simn: :D
<struktured> tokenrove: I believe jane street uses jenga, but they probably lean on unix predominantly.
<tokenrove> struktured: that's the impression i got. and last time i looked, it depended on pretty linux-y things like inotify.
<tokenrove> i would love to hear that someone also used it successfully under windows, though.
<Drup> ousado: it's a german thing ? I heard that from lot's of different european people
<ousado> Drup: I'm not sure how wide-spread it is across europe, but my impression based on what foreigners told me is that germans use it relatively often
<bernardofpc> well, french people also tend to use "not bad" very often to mean something is "good" (but not excellent)
<Drup> yes, exactly
<struktured> bernardofpc: that was my meaning, in this case
<bernardofpc> (didn't know about this about germans, but I can imagine)
<Drup> and british use it too, for obvious british phlegm reasons.
ollehar1 has joined #ocaml
<Drup> (well, at least I heard it several time)
reem has quit [Remote host closed the connection]
govg has quit [Ping timeout: 246 seconds]
<ousado> Drup: maybe the crucial difference is that germans use it for "excellent" :)
<Drup> Oh, right.
<ousado> it sometimes strikes me as a not-so-subtle way to belittle something
travisbrady has joined #ocaml
Guest88462 has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
avsm has quit [Quit: Leaving.]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
ptc has joined #ocaml
AlexRussia has joined #ocaml
ptc is now known as Guest36665
MercurialAlchemi has quit [Ping timeout: 252 seconds]
moei has joined #ocaml
Simn has quit [Quit: Leaving]
MrScout has joined #ocaml
travisbrady has quit [Quit: travisbrady]
huza has joined #ocaml
AlexRussia has quit [Ping timeout: 245 seconds]
vanila has quit [Quit: Leaving]
AltGr has joined #ocaml
huza has quit [Quit: WeeChat 0.3.8]
reem has joined #ocaml
Guest36665 has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
travisbrady has joined #ocaml
huza has joined #ocaml
reem has quit [Ping timeout: 256 seconds]
reem has joined #ocaml
travisbrady has quit [Quit: travisbrady]
in-pyon-itesimal is now known as simplicial-pyon