flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml MOOC http://1149.fr/ocaml-mooc | OCaml 4.03.0 announced http://ocaml.org/releases/4.03.html | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
fluter has joined #ocaml
agarwal1975 has quit [Quit: agarwal1975]
Jaxan has quit [Ping timeout: 264 seconds]
Jaxan has joined #ocaml
dwwoelfel has joined #ocaml
dwwoelfel has quit [Remote host closed the connection]
groovy2shoes has quit [Ping timeout: 250 seconds]
groovy2shoes has joined #ocaml
agarwal1975 has joined #ocaml
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
darkf has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
vinoski has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
agarwal1975 has quit [Quit: agarwal1975]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
sh0t has joined #ocaml
Algebr` has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
sh0t has quit [Remote host closed the connection]
pierpa has quit [Ping timeout: 250 seconds]
ygrek has quit [Ping timeout: 264 seconds]
sh0t has joined #ocaml
shinnya has quit [Ping timeout: 264 seconds]
lostman has joined #ocaml
basis has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
<lostman> I tried compiling camlp4 with 4.02.3+32bit on mac os and I'm getting this: "Error: Cannot find file dynlink.cmxa". Couldn't find solutions to this problem. Any ideas?
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
sh0t has quit [Remote host closed the connection]
tekknolagi has joined #ocaml
<tekknolagi> I have a question but I don't know quite how to formulate it in order to search the internet. Say I have some user-defined type like:
jonasen has joined #ocaml
<tekknolagi> type lobject = Fixnum of int | List of lobject list;;
<Algebr`> lostman: from source?
<Algebr`> or with opam?
<lostman> no, this is with opam
<tekknolagi> And I have this function that should only really be operating on List, because it deals with envs, how do I specify in the type signature that it only takes Lists?
<lostman> I think it's Mac OS specific problem. Tried with 4.03.0+32bit and the result is the same
<lostman> unfortunately there are some packages that still use camlp4...
<Algebr`> tekknolagi: can't. Lists is a constructor of type lobject
<Algebr`> lostman: will try now
<tekknolagi> Algebr`: So I have to pattern match on List and have a catch all for everything else? (in reality there are about 6 more constructors)
<Algebr`> yes
<tekknolagi> How would I catch that I am passing an invalid type to it at compile time?
<Algebr`> maybe rethink your api
<Algebr`> match item with List l -> ... | _ -> assert false or some exception
<tekknolagi> How do you mean?
<tekknolagi> Like yes, I could do that. That just seems gross.
<tekknolagi> I won't be improperly using it.
<Algebr`> again, then maybe rethink how you're structuring your program?
<tekknolagi> It's a Lisp type system. What would you recommend?
<tekknolagi> I know you've seen basically nothing of it, but perhaps you've seen something similar.
<Algebr`> someone might suggest gadt
<Algebr`> not sure if entirely appropriate here.
<tekknolagi> What is gadt?
<Algebr`> lostman: ha, look at that: amlp4_config.cmx camlp4/boot/Camlp4.cmx camlp4/boot/camlp4boot.cmx -o camlp4/boot/camlp4boot.native # File "_none_", line 1: # Error: Cannot find file dynlink.cmxa
<Algebr`> you're right, its busted.
<Algebr`> tekknolagi: a more advanced concept with which I hope not to burden you with
<lostman> Algebr`: is there an easy way to fix it? I don't know my way around OCaml that much. I only dabble sometimes :)
<tekknolagi> Algebr`: Burden me with because it is itself burdensome or because I don't know what I'm doing?
<Algebr`> tekknolagi: because it might confuse you more
<Algebr`> lostman: don't know, but def report it on github opam
<Algebr`> opam repository
<Algebr`> hmm, opam should have an easy, opam report option,
<Algebr`> liek brew does
<tekknolagi> Algebr`: see "symptom #1" of http://mads-hartmann.com/ocaml/2015/01/05/gadt-ocaml.html. Is that sort of what you're talking about?
<aantron> Drup: no, no such all-in-one example. we havent looked into the skeleton scripts, but you can use bisect_ppx's own travis script for reference
<aantron> im going offline for a while
aantron has quit [Quit: Enjoy!]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
tekknolagi has quit [Quit: leaving]
tekknolagi has joined #ocaml
jonasen has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
rgrinberg has quit [Ping timeout: 246 seconds]
tnguyen has joined #ocaml
tnguyen has left #ocaml [#ocaml]
MercurialAlchemi has joined #ocaml
jonasen has joined #ocaml
<tekknolagi> Okay, so I'm looking at GADTs. Say I have this signature:
<tekknolagi> let rec print_object obj : bool lobject -> () = function (* ... *)
<tekknolagi> ocamlc does not like that this function returns unit, and gives a syntax error on the parens... but doesn't say at all what sort of syntax error. Thoughts?
<Enjolras> tekknolagi: the type is called unit :)
<Enjolras> () is the value
nicoo has quit [Ping timeout: 244 seconds]
MercurialAlchemi has quit [Ping timeout: 276 seconds]
bruce_r has quit [Ping timeout: 250 seconds]
tekknolagi has quit [Ping timeout: 252 seconds]
nicoo has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
AlexDenisov has joined #ocaml
unbalancedparen has quit [Quit: WeeChat 1.5]
jonasen has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
MercurialAlchemi has joined #ocaml
Algebr` has quit [Ping timeout: 250 seconds]
jonasen has joined #ocaml
seangrove has joined #ocaml
sdothum has quit [Quit: ZNC - 1.6.0 - http://znc.in]
<apache2> Enjolras means: bool lobject -> unit =
A1977494 has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
basis has quit [Quit: basis]
basis has joined #ocaml
tekknolagi has joined #ocaml
<tekknolagi> Enjolras: oh, derp. thank you
<tekknolagi> One more question, if I may: is it possible to define a type in a type signature?
<tekknolagi> For example:
<tekknolagi> let print_object (obj: (int lobject | bool lobject)) = (* ... *)
<tekknolagi> If so, what would you call that?
<def`> not possible
<Enjolras> tekknolagi: if it is a GADT your only option is either a particular instance or forall quantifier
<tekknolagi> Enjolras: What is a forall quantifier? Also, if I want to have a particular instance, can I overload with tye type?
<tekknolagi> s/tye/the
basis has quit [Quit: basis]
<Enjolras> let print_object (tpe a) obj : a lobject -> ... = ...
<Enjolras> means "forall type a"
<Enjolras> actually you could have a disjunction like this with polymorphic variant (something like [`Int | ` Bool] lobject but mixing gadt and subtyping is not a good idea
<Enjolras> (and it requires a change in the definition of lobject of course, to map [`Int] to int=
<tekknolagi> hm
<tekknolagi> So I have my GADT. Am I now required to add types to all of my function signatures?
copy` has quit [Quit: Connection closed for inactivity]
<jun> when you use in a non trivial way, I would assume the answer is yes
<jun> *use it
<tekknolagi> Okay so I am clearly not understanding the type system at play here. I have a reasonable understanding of what a type constructor is (I think), but am unclear on what "|" vs "[> | ]
<tekknolagi> oops
<tekknolagi> "[> | ]" is, what the difference between what I am doing (what looks like a union of constructors...?) and GADTs, and a couple other things
<tekknolagi> Am I missing a couple of small things or is there a large knowledge gap here?
asdasd has joined #ocaml
asdasd has quit [Client Quit]
inr_ has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
<jun> do you what polymorphic variants are ?
<jun> *know
AlexDenisov has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<tekknolagi> jun: No, I don't think so. At least not in name.
<jun> well basically its "extendable" union types
<jun> that is ['Foo | 'Bar of string] is a polymorphic variant
<jun> value of this type have the form either "'Foo" or "'Bar s" where s is a string
martinkl_ has joined #ocaml
wolfcore has quit [Ping timeout: 258 seconds]
<jun> but you can then do things like let f (x : ['Foo | 'Baar of string]) : ['Foo | 'Bar of string | 'Other] = match x with 'Foo -> 'Other | _ -> x;;
<jun> ie the type ['A of a | 'B of b | 'C of c] is a subtype of ['A of a | 'B of c | 'C of c | 'D of d]
<jun> you can't do this with regular union type
<jun> moreove there are 'selectors' to tell the compiler you want at least a set of constructors (or at most )
<jun> ie [ > 'A of a | 'B of b] contains at least 'A and 'B but may have more constructors
<jun> ie [ < 'A of a | 'B of b] contains at most 'A and 'B but may have less constructors
<tekknolagi> If I were to change my current "type lobject = Fixnum of int | Boolean of bool | (* ... *)" to that, how much would I need to change in the rest of my program?
<tekknolagi> & is there decent reason to? As in, is what I am doing suboptimal?
wolfcore has joined #ocaml
<jun> suboptimal in what sense ?
<tekknolagi> Inflexible, nonstandard, etc
<jun> it depends on your use case
<jun> i think a good reason to use polymorphic variant is described here http://roscidus.com/blog/blog/2013/12/20/polymorphism-for-beginners/
sfri has quit [Remote host closed the connection]
<tekknolagi> alright, i'll take a look. thank you
<tekknolagi> time for sleep
tekknolagi has left #ocaml [#ocaml]
dexterph has joined #ocaml
xaimus has quit [Ping timeout: 276 seconds]
xaimus has joined #ocaml
nojb_ has joined #ocaml
ygrek has joined #ocaml
AlexDenisov has joined #ocaml
sfri has joined #ocaml
Simn has joined #ocaml
AltGr has joined #ocaml
lostman has quit [Quit: Connection closed for inactivity]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
sz0 has joined #ocaml
ygrek has quit [Ping timeout: 244 seconds]
al-maisan has joined #ocaml
martinkl_ has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
martinkl_ has joined #ocaml
octachron has joined #ocaml
FreeBird_ has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 260 seconds]
FreeBird_ has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
dave24 has joined #ocaml
jonasen has quit [Ping timeout: 264 seconds]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
sfri has quit [Remote host closed the connection]
freehck has joined #ocaml
sfri has joined #ocaml
toolslive has joined #ocaml
Kakadu has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
pyon has quit [Ping timeout: 258 seconds]
jonasen has joined #ocaml
pyon has joined #ocaml
<freehck> Hello. I suspect that integer part of float field Unix.LargeFile.stats.st_atime represents time in milliseconds. Do somebody know if I'm right?
<freehck> Hm... No. I'm not right.
melanargia1 has joined #ocaml
<flux> freehck, usually when times are float in OCaml they are in seconds
<adrien> man sta64 ?
<adrien> stat64*
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
kolko has quit [Ping timeout: 260 seconds]
kolko has joined #ocaml
zaquest has quit [Ping timeout: 260 seconds]
zaquest has joined #ocaml
martinkl_ has quit [Ping timeout: 272 seconds]
martinkl_ has joined #ocaml
hay207 has joined #ocaml
AlexRussia has quit [Ping timeout: 250 seconds]
tormen has quit [Read error: No route to host]
silver has joined #ocaml
hay207 has quit [Quit: Konversation terminated!]
<freehck> flux: btw, why a fractional part of a float time is always zero?
<mrvn> because your OS doesn't support subsecond timestamps
<mrvn> FS even
<freehck> Thank you, I'll check it up.
jonasen has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
jonasen has joined #ocaml
hay207 has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
AlexDenisov has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
AlexDenisov has joined #ocaml
AlexDenisov has quit [Client Quit]
AltGr has quit [Remote host closed the connection]
Kakadu has quit [Remote host closed the connection]
tane has joined #ocaml
Kakadu has joined #ocaml
Sorella has quit [Quit: Connection closed for inactivity]
jeffmo has joined #ocaml
AltGr has joined #ocaml
jeffmo has quit [Ping timeout: 246 seconds]
sdothum has joined #ocaml
jeffmo has joined #ocaml
fluter has quit [Ping timeout: 258 seconds]
FreeBirdLjj has quit [Remote host closed the connection]
StrykerKKD has joined #ocaml
FreeBirdLjj has joined #ocaml
dave24 has quit [Ping timeout: 240 seconds]
A19774941 has joined #ocaml
A1977494 has quit [Ping timeout: 250 seconds]
sdothum has quit [Quit: ZNC - 1.6.0 - http://znc.in]
sdothum has joined #ocaml
fluter has joined #ocaml
StrykerKKD has quit [Quit: Leaving]
hay207 has quit [Quit: Konversation terminated!]
martinkl_ has quit [Quit: Textual IRC Client: www.textualapp.com]
<cheater> hey guys
<cheater> i tried doing something like this:
FreeBirdLjj has quit [Remote host closed the connection]
<cheater> Pipe.read msgr >>= function
<cheater> | Pipe.Eof -> return "EOF"
FreeBirdLjj has joined #ocaml
<cheater> however, ocaml tells me: Error: Unbound constructor Pipe.Eof
<cheater> oh... i got it. instead of Pipe.Eof i wrote `Eof and it worked. Why does this work? what have i actually done here?
<companion_cube> `Eof is a "polymorphic variant"
<companion_cube> it's a constructor that doesn't have to be defined as part of a type
<cheater> ok so basically it's like a string promoted to type level?
<companion_cube> hmm, it can have parameters
<cheater> basically you write ` followed by any sort of string and then parameters and it'll be accepted as a valid constructor?
<companion_cube> more or less
<cheater> ok
<cheater> ocaml keeps track of the ones a function returns, right?
<companion_cube> and the resulting type is the union of all the cases
<companion_cube> yes
<cheater> OK
<cheater> great, thanks
rgrinberg has joined #ocaml
sdothum has quit [Quit: ZNC - 1.6.0 - http://znc.in]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
sdothum has joined #ocaml
dhil has joined #ocaml
AlexDenisov has joined #ocaml
rgrinberg has quit [Ping timeout: 240 seconds]
agarwal1975 has joined #ocaml
jonasen has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
FreeBird_ has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 252 seconds]
FreeBird_ has quit [Ping timeout: 240 seconds]
jonasen has joined #ocaml
kushal has joined #ocaml
kushal has quit [Changing host]
kushal has joined #ocaml
tane has quit [Ping timeout: 258 seconds]
tane has joined #ocaml
rand__ has joined #ocaml
thizanne has joined #ocaml
rgrinberg has joined #ocaml
AlexRussia has joined #ocaml
jonasen has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
A19774941 has quit [Remote host closed the connection]
inr_ is now known as inr
<cheater> my function foo is passed another function bar of a polymorphic type. inside the body of foo, bar is monomorphic. how can i prevent this?
freehck has quit [Remote host closed the connection]
jwatzman|work has joined #ocaml
<octachron> cheater, if you need to keep your function polymorphic, you need to encapsulate it within eitheir a record or an object with a universal type quantification
<cheater> eek
sz0 has quit [Quit: Connection closed for inactivity]
<octachron> e.g, type id = { f:'a . 'a -> 'a } let pair id (x,y) = id.f x, id.f y
shinnya has joined #ocaml
<cheater> hmm
<cheater> well this is my function currently:
<cheater> let rec long_poll_loop (rpc : ('a, 'b) Rpc.Rpc.t -> 'a -> 'b Deferred.t) = rpc long_poll_rpc () >>= fun resp -> print_endline @@ "Server says: " ^ resp; rpc client_received_rpc resp >>= fun _ -> long_poll_loop rpc
<cheater> oh well that's great, it got all put on one line, 1 sec
<cheater> octachron: i'm not sure how i would apply your idea here
kushal has quit [Quit: Leaving]
<octachron> if you need to apply rpc with different type value for 'a, 'b, you could define "type rpc = { f:'a 'b. ('a, 'b) Rpc.Rpc.t -> 'a -> 'b Deferred.t }" but there may be a simpler solution here.
hay207 has joined #ocaml
<sspi> would it be possible to use two different compiler-libs under one ocaml version? eg. run OCaml 4.02.3 but have access to the compiler libs of 4.03? (also apologies for not responding further to the question I asked a few days ago, I was a bit preoccupied)
basis has joined #ocaml
hcarty has joined #ocaml
<gasche> sspi: I think it's not a very good idea
<gasche> *technically* you could probably build the sources of 4.03.0 from your 4.02.3 compiler and then install the 4.03.0 compiler-libs and binaries somewhere
<gasche> but I would be worried that, given that it's not a supported usage mode, you'll get weird stuff happening
<Drup> sspi: could you explain your use case ?
<gasche> why don't you migrate to 4.03 instead if you want to use the 4.03 compiler from your programs?
<gasche> (if the answer is "because X does not work under 4.03", well, fix X)
<sspi> it's multicore... :P
<gasche> and what's the need for 4.03 compiler-libs?
basis has quit [Ping timeout: 272 seconds]
malc_ has joined #ocaml
<sspi> drup: the use case is generating code for either 4.03 or 4.02.3 + multicore - ideally we want to do this with the same parser
<sspi> but tbh. I'm not sure if it's worth the effort - might be wiser to wait for 4.04 (or whenever it lands) with multicore integrated
basis has joined #ocaml
<Drup> ah, so you don't want compiler libs, you want the parsetree
<Drup> that's much easier
<Drup> just use ppx_tools
<sspi> ppx_tools okay
<Drup> you should be able to write code that can compiles against both version
<gasche> (multicore probably won't be in 4.04; hopefully we will have an alpha release by that time)
<gasche> (probably => certainly)
dakk has quit [Quit: Leaving]
copy` has joined #ocaml
<Drup> for the rest of the pipeline, the functions changed a bit, but in the worse case, just dump the parsetree and call ocaml on it :)
<Drup> (or just code it for each version, it's less than 20 lines)
beginner_ has quit [Remote host closed the connection]
<sspi> Drup: interesting, I'll try this
<sspi> thanks!
MercurialAlchemi has quit [Ping timeout: 250 seconds]
jeffmo has quit [Ping timeout: 250 seconds]
jeffmo has joined #ocaml
basis has quit [Ping timeout: 272 seconds]
<toolslive> multicore is the new duke nukem forever
<Leonidas> gasche: ohno :-(
<Leonidas> toolslive: I thought modular implicits are the new duke nukem forever
<gasche> it's not a "duke nukem forever" problem
<gasche> it's just that (1) making it work well is a shit-ton of work and (2) merging it upstream properly will be a shit-half-ton of work
<gasche> (1) is not completely there yet, and even when (2) starts you shouldn't expect it to succeed in one OCaml release cycle
<gasche> (modular implicits have some of these qualities, but I would expect integration to be much easier once the work is stable)
<gasche> the expectation of the OCaml communities in terms of multicore availability are completely unreasonable, and Damien Doligez's silly 4.03 announcement did not help
<toolslive> what's the plan with the multicore fibers and lwt/async ?
<gasche> is there a plan?
<companion_cube> it's too early, I think
<toolslive> well, I'm perfectly fine with one core doing all the IO (or at least doing all the waiting for it) and the ability to push crunching to other cores.
<toolslive> (in a comfortable way)
jeffmo has quit [Read error: Connection reset by peer]
basis has joined #ocaml
jeffmo has joined #ocaml
jeffmo_ has joined #ocaml
jeffmo_ has quit [Client Quit]
<gasche> the problem is that most lwt/async-using code is designed (and all of it is tested) with sequential scheduling in mind, and thus little indication of intent for races between cooperative thread executions
<Leonidas> yes, that will have to be revisited, but that's fine.
* mrvn wants to do: let foo (x : 'a) (y : 'a) = type x of int -> foo_int x y | float -> foo_float x y | _ -> foo_generic x y
jeffmo has quit [Ping timeout: 244 seconds]
<gasche> mrvn: GADTs?
<mrvn> gasche: no
<gasche> foo : type a . a ty -> a -> a -> ...
SpiceGuid has joined #ocaml
<mrvn> I want to substitute optimized code for when the type is known at compile time.
<gasche> well using GADTs makes the type known at compile-time
<gasche> (and then when the ('a ty) value is a constant in caller code, it gets inlinined away)
<mrvn> gasche: not realy. makes it known at runtime with the potential to optimize that away
<gasche> meh
<gasche> ugly syntax, complex/unclear semantics, that's not very nice language design
<cheater> octachron: i wouldn't know what a simpler solution would be. hm.
<mrvn> gasche: I think implicits would allow this without adding overhead to the user.
<gasche> yep
<gasche> cheater: what about abstracting over (rpc long_poll) and (rpc client_...) instead of just (rpc)?
<mrvn> but I think in the generic case it would create overhead, actually construct the ty and match it at runtime.
<gasche> but some of this overhead is probably paid by the generic operation today, and maybe you could transfer costs instead of increasing them
<mrvn> I'm thinking something more like template specialization in c++
upbeatfx has joined #ocaml
<gasche> cheater: there's a general trick that instead of abstracting over a polymorphic f, you can abstract over all the results of calling f you actually need, because they have simpler types
<Drup> mrvn: this is a case where implicits could help.
<cheater> gasche: hmm.. right
wiredsister has joined #ocaml
<gasche> (and it often doesn't actually make code much more complicated, just less abstract)
<gasche> (but the polymorphic-record-field solution should also work and preserve the code structure you currently have in mind)
<mrvn> Drup: Can I somehow mark the implicit so that it is only matched at compile time and if the type is unknown it just always uses the _ case?
<cheater> gasche: gotcha. thanks.
<mrvn> Drup: garantee that the implicit is optimized away.
<cheater> :)
<Drup> with flambda, I wouldn't say garantee, but it's quite probable
<cheater> btw what do you call this issue that i ran into?
<cheater> "local monomorphism" perhaps?
<mrvn> Drup: not without some attribute. The generic case would not optimize the ty away.
tane has quit [Ping timeout: 276 seconds]
<upbeatfx> Hi everyone! I'm trying to learn OCaml and what to start with "How to think like a (functional) programmer" (a.k.a. "ThinkOcaml" http://www.greenteapress.com/thinkocaml/thinkocaml.pdf) because of how concise it is. However, when searching through the book it doesn't appear to cover cool features like functors that attracted me to OCaml in the first place. Is starting with ThinkOCaml and then moving onto Real Woarld Ocaml a good plan
<octachron> cheater: higher-rank polymorphism conundrums/limitations?
unbalancedparen has joined #ocaml
<hcarty> upbeatfx: RWO has good information on functors. So does the manual and courses.cms.caltech.edu/cs134/cs134b/book.pdf
<octachron> cheater: I have a draft/PR for a manual chapter on related problems, I will try to make it available online during the week
<Drup> upbeatfx: you could just go for RWO directly too. I don't have very good memory of thinkocaml
<cheater> yeah something like that
sfri has quit [Read error: Connection reset by peer]
<upbeatfx> @hcarty Thanks, I'll look into that book, @Drup & @hcarty Is there a recommended book for someone coming from procedural/imperative languages? I may start with RWO, it's longer but it covers far more than ThinkOCaml
lostman has joined #ocaml
<toolslive> has anybody tried to instruct travis to cache opam packages between builds ?
<upbeatfx> hcarty, Drup -- ah, forgot this works differently in irc
<hcarty> upbeatfx: I really like the caltech/Jason Hickey book as an introductory text
<hcarty> It doesn't cover all of the latest language features but the parts it does cover are described well
<gasche> (RWO in fact started from Jason Hickey's book)
tane has joined #ocaml
<upbeatfx> Gotcha, thank you, so, is there a recommended program, or do people who learn Ocaml look for good resources on each feature after learning the basics?
<upbeatfx> I don't have much experience with functional programming or ML's, I did a bit of lisp in college, but I'm not sure how much I need to learn to be productive and make things in a funcitonal language
<mrvn> 3 hours and 17 minutes.
<upbeatfx> That's kind of a hard question to answer though, I guess we never really stop learning
<Drup> upbeatfx: ocaml isn't too hard to pick up, given that you can start by writing imperative code.
<Drup> (and introduce the new functional fancy things slowly)
basis has quit [Quit: basis]
<upbeatfx> Hah, mrvn, is that the minimum? (were you talking to me?)
<mrvn> and if you've done some formal math it just flows.
sfri has joined #ocaml
<mrvn> upbeatfx: the quality of the answere is proportional to the quality of the question
Kakadu has quit [Quit: Konversation terminated!]
<gasche> mrvn: that's not a very nice way to answer beginner's questions
<gasche> I think being cold/snarky with people you know well is fine, but please help maintain a pleasing atmosphere for newcomers
<upbeatfx> Drup: Gotcha,
<Drup> upbeatfx: and it will give you the oportunity two years later to look at your old code and be like "omg, how could I wrote *that*" and then rewrite it with more functors and more GADTs. :>
<upbeatfx> Haha
<toolslive> yes. the incredible shrinking codebase(TM)
<gasche> (not too much GADTs please)
<upbeatfx> So if I work through Hickey's book and RWO, do you think I'd know enough to write interactive programs like games in a more pure-functional style in OCaml? Maybe using monad's for IO?
<upbeatfx> I guess I still don't understand what the pure-functional style is, will probably have to learn more OCaml before I can ask better questions about it
<upbeatfx> Oh, OCaml does have a signals library
<upbeatfx> alright, thanks everyone!
<upbeatfx> Off to work then
upbeatfx has quit [Quit: Page closed]
Kakadu has joined #ocaml
slash^ has joined #ocaml
sfri has quit [Remote host closed the connection]
Algebr` has joined #ocaml
buddyholly has quit [Ping timeout: 276 seconds]
dexterph has quit [Ping timeout: 258 seconds]
hongbo has joined #ocaml
sfri has joined #ocaml
pyon has quit [Quit: ... flowering silent scarlet piece of night.]
pyon has joined #ocaml
sfri has quit [Remote host closed the connection]
dave24 has joined #ocaml
ygrek has joined #ocaml
sfri has joined #ocaml
basis has joined #ocaml
basis has quit [Quit: basis]
sz0 has joined #ocaml
octachron has quit [Quit: Page closed]
A1977494 has joined #ocaml
AlexDenisov has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
basis has joined #ocaml
StrykerKKD has joined #ocaml
malc_` has joined #ocaml
malc_ has quit [Ping timeout: 276 seconds]
basis has quit [Ping timeout: 276 seconds]
ygrek has quit [Ping timeout: 240 seconds]
MercurialAlchemi has joined #ocaml
Sorella has joined #ocaml
seangrove has quit [Ping timeout: 246 seconds]
dave24 has quit [Quit: leaving]
ptolemarch has joined #ocaml
jonasen has joined #ocaml
jonasen has quit [Client Quit]
AlexDenisov has joined #ocaml
nojb_ has quit [Ping timeout: 276 seconds]
noplamodo has quit [Remote host closed the connection]
noplamodo has joined #ocaml
copy` has quit [Quit: Connection closed for inactivity]
pierpa has joined #ocaml
SpiceGuid has quit [Quit: ChatZilla 0.9.92 [SeaMonkey 2.40/20160120202951]]
jwatzman|work has quit [Quit: jwatzman|work]
ygrek has joined #ocaml
wiredsister has left #ocaml ["ERC (IRC client for Emacs 24.5.1)"]
M-jimt has quit [Remote host closed the connection]
M-pesterhazy has quit [Read error: Connection reset by peer]
regnat[m] has quit [Remote host closed the connection]
M-martinklepsch has quit [Write error: Connection reset by peer]
M-Illandan has quit [Write error: Connection reset by peer]
jonasen has joined #ocaml
StrykerKKD has quit [Quit: Leaving]
darkf has quit [Quit: Leaving]
pipirka has joined #ocaml
<pipirka> I have a question.
<pipirka> Why in the following code I cannot reve any of the semicolons?
<pipirka> let a = 1
<pipirka> let b = 2
<pipirka> let sum = a + b;;
<pipirka> print_int sum;
<pipirka> print_endline "Hi"
<pipirka> Do they have any special meaning?
<pipirka> remove*
<Algebr`> the ;; is for the top level
<Algebr`> you don't need to use it in ml files
<pipirka> Algebr`: It is not. I save the code below in a ml file and compiled it with ocamlc test.ml
<pipirka> If I remove any of the semicolons in the file, it shows me errors.
regnat[m] has joined #ocaml
<Algebr`> probably because you add the print_int sum;
shinnya has quit [Ping timeout: 272 seconds]
<Algebr`> you should probably do let () = print_int sum; print_endline "Hi"
<pipirka> It goes pretty well. Could you tell me though about the semicolons? I`ve seen a listing with them.
<pipirka> I guess,a double semicolon in a .ml file tells me that an expereesion result has to be discarded, a single semicolon ends a function appliction.
<Algebr`> the double semicolon is just to separate expressions
<gasche> phrases
<Algebr`> the ; is short hand for let () = print_endline "Hello"
<Algebr`> phrases
<Algebr`> sorry
<hongbo> pipirka: I like this syntax `;; a_side_toplevel_expresssion`
<hongbo> otherwiese you don't need `;;'
<gasche> if you write
<gasche> let sum = a + b print_sum; print_endline "Hi"
<gasche> it means
<gasche> let sum = ((a + b print_sum); print_endline "Hi")
<Algebr`> (it is nice that reason gets ride of this ;; business all together)
<Algebr`> rid
<pipirka> >let sum = ((a + b print_sum); print_endline "Hi")
<pipirka> So, there`s no such a thing as a "let without in". Just a let on one line does not mean that it ends on that line. Sure.
<pipirka> May I see a kind of a written explanation to this? Just haven`t seen a thing like this in books, sorry, need to read about that.
<pipirka> Thanks for the explanation, however.
<mrvn> pipirka: A ;; tells the interactive toplevel to start evaluating the input. There is never a reason to put a ;; in a file.
<mrvn> pipirka: top level "let" don't have an in
<mrvn> # let x = 1;;
<mrvn> val x : int = 1
<pipirka> mrvn: I can`t put a simple let x = 1 in a .ml file?
<mrvn> yes you can
<pipirka> mrvn: I`ve seen semicolons in code examples. Single semicolons though.
<gasche> ( plus http://caml.inria.fr/pub/docs/manual-ocaml/compunit.html for why the link above discusses what can be put in sig..end: that's the same as what you put in .ml files )
<mrvn> pipirka: yes. ; is used a lot
<mrvn> pipirka: ;; is a different token to ; or ; ;
<pipirka> gasche: Thanks a lot!
<gasche> you also need to know that OCaml is whitespace-isensitive, which is pointed out in the very beginning of http://caml.inria.fr/pub/docs/manual-ocaml/lex.html
<gasche> asking where stuff is pointed out in writing is a good question, because it can help us locate missing bits in the documentation
<mrvn> gasche: except for e.g. (* vs ( *, or ;; vs ; ; and so on.
<mrvn> or does whitespace-isensitive include the need for whitespaces between tokens?
<Drup> mrvn: white space insensitive usually means "any number of whitespace can be transformed into one whitespace"
<mrvn> ok, nm then
<Drup> (otherwise, "x y" is different than "xy", yeah, thanks.
<gasche> this is explained in the link I gave
<mrvn> 123xyz used to be the same as 123 xyz
<gasche> "Blanks are ignored, but they separate adjacent identifiers, literals and keywords that would otherwise be confused as one single identifier, literal or keyword."
lostman has quit [Quit: Connection closed for inactivity]
<pipirka> gasche: That example of yours greatly pointed it out. Just got it :)
<gasche> you're welcome
<pipirka> Thanks !
M-martinklepsch has joined #ocaml
M-jimt has joined #ocaml
M-pesterhazy has joined #ocaml
M-Illandan has joined #ocaml
<mrvn> weren't there cases where a ;; in a .ml file where harmfull?
<hongbo> whenever I got a syntax error, I would start adding `;;` somewhere
<mrvn> that makes no sense
<hongbo> it helps you localize the syntax error, when you are unclear about what's going on
<mrvn> still makes no sense unless you are looking for a missing expression after a "let ... = ... in"
octachron has joined #ocaml
pipirka has left #ocaml [#ocaml]
jonasen has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
SpiceGuid has joined #ocaml
Kakadu has quit [Quit: Page closed]
hay207_ has joined #ocaml
hay207 has quit [Ping timeout: 252 seconds]
shinnya has joined #ocaml
jonasen has joined #ocaml
sz0 has quit [Quit: Connection closed for inactivity]
octachron has quit [Read error: Connection reset by peer]
nicoo has quit [Remote host closed the connection]
nicoo has joined #ocaml
octachron has joined #ocaml
octachron has quit [Quit: Leaving]
ptolemarch has quit [Ping timeout: 260 seconds]
slash^ has quit [Read error: Connection reset by peer]
ptolemarch has joined #ocaml
SpiceGuid has quit [Quit: ChatZilla 0.9.92 [SeaMonkey 2.40/20160120202951]]
dmj` has joined #ocaml
Kakadu has joined #ocaml
SpiceGuid has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 250 seconds]
copy` has joined #ocaml
tane has quit [Quit: Leaving]
dmj` has left #ocaml ["ERC (IRC client for Emacs 24.5.1)"]
SpiceGuid has quit [Quit: ChatZilla 0.9.92 [SeaMonkey 2.40/20160120202951]]
SpiceGuid has joined #ocaml
AlexDenisov has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
jonasen has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
loocash has joined #ocaml
loocash has quit [Client Quit]
rgrinberg has quit [Ping timeout: 246 seconds]
_2can_ is now known as _2can
mfp_ has quit [Read error: Connection reset by peer]
Higgs has joined #ocaml
Higgs has quit [Read error: Connection reset by peer]
Higgs has joined #ocaml
AltGr has left #ocaml [#ocaml]
AlexRussia has quit [Ping timeout: 264 seconds]
hcarty has quit [Ping timeout: 246 seconds]
mfp has joined #ocaml
dhil has quit [Ping timeout: 276 seconds]
rgrinberg has joined #ocaml
malc_` has quit [Remote host closed the connection]
thizanne has quit [Ping timeout: 272 seconds]
rgrinberg has quit [Ping timeout: 272 seconds]
AlexRussia has joined #ocaml
silver has quit [Quit: rakede]
A1977494 has quit [Remote host closed the connection]
Kakadu has quit [Remote host closed the connection]
marsam has quit [Ping timeout: 260 seconds]
rand__ has quit [Quit: leaving]
Higgs has quit [Remote host closed the connection]
SpiceGuid has quit [Quit: ChatZilla 0.9.92 [SeaMonkey 2.40/20160120202951]]
sh0t has joined #ocaml
madroach has quit [Ping timeout: 244 seconds]
madroach has joined #ocaml
agarwal1975 has quit [Quit: agarwal1975]
ptolemarch has quit [Quit: Leaving]
Algebr` has quit [Ping timeout: 250 seconds]
fluter has quit [Ping timeout: 258 seconds]