flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | 3.11.0 out now! Get yours from http://caml.inria.fr/ocaml/release.html
Kerris7 has quit []
slash_ has quit [Read error: 60 (Operation timed out)]
slash_ has joined #ocaml
willb has joined #ocaml
seafood has quit []
asabil has quit [Remote closed the connection]
ozzloy has quit [Read error: 60 (Operation timed out)]
ozzloy_ has joined #ocaml
love-pingoo has quit ["Connection reset by pear"]
pumpkin_ has joined #ocaml
pumpkin_ has left #ocaml []
seafood has joined #ocaml
sbok has quit [Remote closed the connection]
sbok has joined #ocaml
Kopophex has quit ["Leaving"]
middayc_ has quit [Read error: 110 (Connection timed out)]
seafood has quit []
seafood has joined #ocaml
seafood has quit [Client Quit]
seafood has joined #ocaml
mishok13 has quit [Read error: 60 (Operation timed out)]
jeddhaberstro has quit []
shortc|desk has joined #ocaml
Amorphous has quit [Read error: 110 (Connection timed out)]
Amorphous has joined #ocaml
ozzloy_ is now known as ozzloy
mwhitney has joined #ocaml
ygrek_ has joined #ocaml
ygrek_ has quit [Remote closed the connection]
sporkmonger has quit []
pango_ has joined #ocaml
seafood has quit []
pumpkin_ has joined #ocaml
pango has quit [Remote closed the connection]
olgen has joined #ocaml
Camarade_Tux has quit [Remote closed the connection]
Camarade_Tux has joined #ocaml
ygrek_ has joined #ocaml
apples` has quit ["Leaving"]
Gionne has joined #ocaml
_zack has joined #ocaml
petchema has joined #ocaml
dabd has joined #ocaml
_zack has quit ["Leaving."]
itewsh has joined #ocaml
foo_ has joined #ocaml
<foo_> I have some problems with using or understanding modules system
<foo_> I wrote simple module
<foo_> which is Vertex of a graph
<foo_> and I don't know how to create and instance of it
<foo_> could you guys help me?
<foo_> when I type Vertex.create 5;;
<foo_> it tells me that 5 is not type of Vertex.label
sebbu has quit [Read error: 54 (Connection reset by peer)]
foo_ has quit ["Ex-Chat"]
Snark has joined #ocaml
Yoric[DT] has joined #ocaml
<Yoric[DT]> hi
slash_ has quit [Client Quit]
dank0 has joined #ocaml
love-pingoo has joined #ocaml
<flux> hm, how should this stuff work? type 'a number = [> `I of int | `R of float] as 'a;; doesn't, but fails with "Unbound type parameter .."
<flux> the manual is a bit thin on the subject
<flux> infact, I didn't even find the relevant syntax description
<flux> ah, right, I need to use the constraint syntax?
<flux> yes.. but still, hickey's book has that example
MelanomaSky has joined #ocaml
<MelanomaSky> How can I define a type in one file, that I plan on using across multiple OCaml source files?
<flux> melanomasky, foo.ml: type a = int bar.ml: type b = Foo.a
<flux> melanomasky, note that foo.ml (or foo.mli) must be compiled before bar.ml
<MelanomaSky> flux: Hrm, I am playing with that..
<MelanomaSky> flux: Arg, only when I get frustrated enough to come to IRC do I find my problem.
<MelanomaSky> flux: Is there some requirement about naming types with lower-case letters?
<flux> yes
ygrek_ has quit [Remote closed the connection]
<flux> modules and type constructors start with capital letters, everything else with lowercase
<MelanomaSky> Ack... I see... hrm... I see this now spelled out in section 6.3 of the manual.
<MelanomaSky> Frustrating that I get "syntax error"..
<flux> well, it is :)
ygrek has joined #ocaml
<MelanomaSky> Follow up question... let's say I have an arbitrary list of some arbitrary type.
<flux> yes..
<MelanomaSky> Is there some way to print out something along the lines of a "toString()" type representation of them?
<MelanomaSky> (of the elements?)
<flux> you would need to define a to_string for each of the element; you might find certain type extensions helpful in doing that (such as sexplib)
<MelanomaSky> I guess I'm wanting something in a library or whatever eg foo: 'a -> string that will work for any types I might define.
<MelanomaSky> Hrm I see..
<flux> well, there is a dumping library that does that, but it is more an estimate than an exact representation
<MelanomaSky> Yeah I think an estimate would work for my use case
<flux> for example I don't think it can differentiate between integers and characters
<flux> here's one of the dumping libs: http://www.geocities.com/tmp_456/dump/index.html
<flux> seems relatively sophisticated
<flux> extlib (or now Batteries) has a simpler version, simple val dump : 'a -> string
<MelanomaSky> thanks for the pointers, i'll check those out
<flux> what does type [< `R | `W >`R] mean?
<mfp> flux: [`R] or [`R | `W] ("one of `R or `W might be missing" + "at least `R")
<Yoric[DT]> "at most `R or `W and at least `R"
<mfp> (inclusive or)
<flux> so it's useful because it's compatible with [`R | `W] but it's more narrow than [>`R] ?
<flux> (in the context of Batteries' Data.String.Cap)
<mfp> the < `R | `W part seems more restrictive than usually needed when using phantom types to represent capabilities
<Yoric[DT]> flux: In that context, the [< `R | `W] part is a sanity check.
<Yoric[DT]> The important part is [> `R], i.e. "you need reading rights".
<mfp> Yoric[DT]: so you're using constraint 'a = [< `Read | `Write] to prevent typos in extString.ml, right?
<Yoric[DT]> Essentially, yes.
<mfp> hmm
<Yoric[DT]> Polymorphic variants are typo-prone.
<mfp> one you have the 'a t type, I'd be useful to lift that constraint
<mfp> so ppl can add their own capabilities
<flux> yoric[dt], well, you could type ro_string = .. rw_string = .. ?
<flux> to remove the need to repeat the constraints all the time?
<Yoric[DT]> flux: things that work on [ro_string] also work on [rw_string].
<Yoric[DT]> So I'd need something like [#r_string] and [#w_string].
<Yoric[DT]> I'm not sure that would be more convenient.
<Yoric[DT]> mfp: mmmhhh...
<mfp> module Tainted_string = struct include String.Cap let untainted_ro x : [`Untainted | `Read ] = of_string x end
<mfp> then you can use [> `Untainted] t and so on
hjpark has quit [Remote closed the connection]
<Yoric[DT]> mfp: fair enough
jlouis has quit [Remote closed the connection]
<mfp> Yoric[DT]: I'm trying to find a find to keep the compile-time checks by using a dummy (hidden) module that adds the [< `Read | `Write] constraint
<mfp> first attempts failed
<Yoric[DT]> Added to the tasklist.
<mfp> trying things like module Y(X : sig type 'a t end with type 'a t = 'a t constraint 'a = [< `R | `W]) = X;;
_zack has joined #ocaml
<mfp> I think I got it
Kerris7 has joined #ocaml
<mfp> failure
<Yoric[DT]> :/
Kerris7 has quit [Read error: 54 (Connection reset by peer)]
Kerris7 has joined #ocaml
<mfp> keep bumping against Type declarations do not match type 'a t = 'a X.t constraint 'a = [< `A | `B ] is not included in type 'a t no matter where I place the constraint
<mfp> either that or Multiple definition of the type name t. :-(
<mfp> I was placing my hopes on : S with type 'a t = 'a X.t constraint 'a = [<`A | `B] = struct include X type 'a t = 'a X.t constraint 'a = [< `A | `B] end;;
<Yoric[DT]> What exactly are you trying to do?
<mfp> find a way to keep the protection against typos in extString.ml
<mfp> while lifting the type constraint
<mfp> by adding it to a dummy module (which won't be exposed in the mli) derived from Cap
<mfp> it's rather academic, as you'd need to have the same typo in the .ml and the .mli
<mfp> and the fact that the current code compiles with the constraint in place means there's no such bug
<mfp> so it could be uncommented momentarily if new functions are added to make sure there are indeed no typos
<Yoric[DT]> Sure.
tux2 has joined #ocaml
<flux> still, putting the repetition into a type definition is sound functional design practive, no?-)
<Yoric[DT]> flux: you mean the [ro_string] and [rw_string]?
<tux2> I had never tried camlirc (in lablgtk distribution) :)
<flux> albeit perhaps it would just obscure the matter, it's easy to see what's happening the way it currently is
<flux> yoric[dt], yeah. for the record, I don't think it's worth changing :)
<Yoric[DT]> tux2: I wasn't even aware that existed.
<Yoric[DT]> flux: noted :)
<flux> but the one about being pervasive throughout the library _would_ be cool. I wonder how it could be done..
<Camarade_Tux> Yoric[DT], I wasn't either ;)
<Yoric[DT]> flux: what do you mean?
<flux> yoric[dt], so 'string' would really be [`Read | `Write] Data.String.Cap.t, and the type alias would be reflected to other non-batteries modules too..
<flux> because if the latter wouldn't happen, it would be too big a pain to use
<flux> but, off to shower ->
tux2 has left #ocaml []
<mfp> I sometimes wished all basic data types were phantom types
Gionne has quit ["Leaving"]
Kerris7_ has joined #ocaml
Kerris7 has quit [Read error: 54 (Connection reset by peer)]
ocamleg has joined #ocaml
<ocamleg> /names
<olegfink> whoops.
<olegfink> heh, ocamlirc isn't much fun.
ocamleg has quit [Remote closed the connection]
<Camarade_Tux> yeah, it's quite limited
<Camarade_Tux> I wonder if the optimizing back-end will somehow make it to the official ocaml compiler
<Camarade_Tux> (see the caml-list)
<Yoric[DT]> interesting
jlouis has joined #ocaml
dank0 has quit [Read error: 113 (No route to host)]
vixey has joined #ocaml
<flux> btw, is that [< `A >`A] documented somewhere?
<Yoric[DT]> ?
<flux> where did you guys learn about it?-)
<Yoric[DT]> Ah, ok :)
<flux> or, from the mailing list and sources?
<Yoric[DT]> Mmmmhhh....
<Yoric[DT]> I think I learnt about it from the documentation of Camlp4 :)
<flux> I'd like to say ocaml documentation is good, but at times it seems a bit lacking..
<Yoric[DT]> Yeah.
<TaXules> yo
<Yoric[DT]> Yes?
_zack has quit ["Leaving."]
_zack has joined #ocaml
itewsh has quit [Read error: 60 (Operation timed out)]
_zack has quit ["Leaving."]
zerny has joined #ocaml
asabil has joined #ocaml
itewsh has joined #ocaml
jeddhaberstro has joined #ocaml
zerny has quit [Remote closed the connection]
delian has joined #ocaml
delian has left #ocaml []
Camarade_Tux_ has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
olgen has quit [kornbluth.freenode.net irc.freenode.net]
rwmjones has quit [kornbluth.freenode.net irc.freenode.net]
struktured_ has quit [kornbluth.freenode.net irc.freenode.net]
bohanlon has quit [kornbluth.freenode.net irc.freenode.net]
svenl has quit [kornbluth.freenode.net irc.freenode.net]
flux has quit [Read error: 104 (Connection reset by peer)]
flux has joined #ocaml
dank0 has joined #ocaml
olgen has joined #ocaml
rwmjones has joined #ocaml
struktured_ has joined #ocaml
bohanlon has joined #ocaml
svenl has joined #ocaml
Camarade_Tux has quit [Read error: 110 (Connection timed out)]
olgen has quit [kornbluth.freenode.net irc.freenode.net]
svenl has quit [kornbluth.freenode.net irc.freenode.net]
rwmjones has quit [kornbluth.freenode.net irc.freenode.net]
struktured_ has quit [kornbluth.freenode.net irc.freenode.net]
bohanlon has quit [kornbluth.freenode.net irc.freenode.net]
olgen has joined #ocaml
rwmjones has joined #ocaml
struktured_ has joined #ocaml
bohanlon has joined #ocaml
svenl has joined #ocaml
jeddhaberstro has quit []
<Camarade_Tux_> =)
<Camarade_Tux_> my (old) webkit-gtk bindings now compile without warnings
Kerris7_ has quit [Read error: 54 (Connection reset by peer)]
Kerris7 has joined #ocaml
<Camarade_Tux_> it's quite easy to make new bindings to *gtk libs but there could be a bit more documentation on that topic
Camarade_Tux_ is now known as Camarade_Tux
rwmjones has quit ["Leaving"]
<vixey> does anyone know how to get rid of Uncaught exception: DynLoader.Error ("pa_ifdef.cmo", "file not found in path") ?
<vixey> I think I have to just install pa_ifdef, but I don't find anything called that anywhere
<mfp> vixey: there's a pa_ifdef.ml in camlp4/unmaintained/etc
<mfp> it's been deprecated by Camlp4MacroParser.cmo
<vixey> thank you
* mfp thinking of extending pa_monad to accept let! x = ... in and try! x with stuff -> y (<=> catch (fun () -> x) (fun stuff -> y) )
<mfp> rather fun <stuff> -> y | e -> fail e unless the pattern in irrefutable
Lockless has joined #ocaml
Galaxor has joined #ocaml
<Galaxor> let addthree num = Int num -> num+3 | Float num -> num+.3.0 ;; doesn't work for me. Unbound constructor Int.
<Galaxor> I practically copied that out of the documentation that came with my interpreter.
<Galaxor> I mean, let addthree num = match num with Int num -> num+3 | Float num -> num+.3.0 ;;
<mfp> Galaxor: look for the explanation of sum types which should precede that function in the documentation
<mfp> (you have to define a type with those constructors)
Camarade_Tux_ has joined #ocaml
<Galaxor> Those constructors aren't built in?
<mfp> Galaxor: you can find the list of built-in types and exceptions here > http://caml.inria.fr/pub/docs/manual-ocaml/manual033.html
<mfp> (they aren't)
<thelema> Galaxor: and your return type will have to be tagged: Int num -> Int(num + 3)
<mfp> thelema: sssh that's the next step :)
<Galaxor> It lists int as a predefined type. That doesn't mean that Int is defined?
<thelema> no, Int != int
<mfp> int is a type, Int is a constructor
<thelema> Int doesn't construct a value of type int.
<Galaxor> How do I do that type matching in a function like addthree? Or do I have to explain what Int and Float are and then it'll work?
<mfp> Galaxor: are you by chance reading the OCaml doc & user manual, Part I, Chapter 1?
<thelema> make a type with Int and Float constructors: type number = Int of int | Float of float
<Galaxor> Oh.
sporkmonger has joined #ocaml
<Galaxor> Oh man, I didn't notice that because it didn't use the word "number" in the definition of add_num.
<Galaxor> But I guess it did in the interpreter's response.
<Smerdyakov> Call it the "toplevel," not the "interpreter." Every bit of code is compiled before evaluation.
* thelema wonders if batteries included should have a numeric type that moves between int, float, and ... big_int? as appropriate
<mfp> between int and float? doesn't seem to make sense
<thelema> Int / Int -> Float
<Galaxor> Okay. Shoot, man. This is like learning computers all over again.
<Smerdyakov> thelema, it seems scary to lose precision silently.
<Smerdyakov> thelema, [int] is generally contained within [float], and [big_int] would likely be useful in few cases.
Camarade_Tux__ has joined #ocaml
<thelema> Smerdyakov: auto-promotion to big_int seems appropriate sometimes, and as for int -> float promotion, of course it'd only happen with non-even division... jumping to rational types seems overkill for most projects.
Camarade_Tux has quit [Read error: 110 (Connection timed out)]
Camarade_Tux__ is now known as Camarade_Tux
<Smerdyakov> thelema, do you agree that, without [big_int] promotion, it makes more sense just to use [float] from the start?
pango_ has quit [Remote closed the connection]
<thelema> some languages' numeric types generally DWIM (Do what I Mean) more than others.
<thelema> I think that it's better to stay with ints unless you need a float.
<Galaxor> thelema: floating point division takes a lot longer than integer division. Sometimes I want integer division.
<thelema> We can have a different operator for that, but the default should be that 3 / 2 = 1.5, not 1
Lockless- has joined #ocaml
Lockless has quit [Read error: 145 (Connection timed out)]
* thelema realizes this project will require camlp4
<thelema> but also that we could have two 'modes' - one using floats and the other using rationals
Lockless- has quit [Client Quit]
<thelema> i.e. exact and fast
pango_ has joined #ocaml
<vixey> this was all solved in the 60s by ALGOL
flo_ml has joined #ocaml
<olegfink> thelema: I think I fail to think of any statically typed language that would do what you want
<flo_ml> what is wrong in http://nopaste.info/2a15b6096d.html ? I want to change nachname & vorname with the function benenne: the second printf should show the values, setted by benenne
<thelema> exactly - this moule would bring the... ease of use... of many dyamically typed languages into ocaml.
<Smerdyakov> olegfink, why is this a language issue? You just define the proper module.
<vixey> flo_ml, why didn't you declare them mutable then?
<thelema> flo_ml: declare your record fields as mutable and use <- to change them
<flo_ml> thanks.
<olegfink> this is as much a language issue as a properly defined standard library, I've had enough fun with C++ operator overloading to have / behaving differently depending on some 'open' somewhere in the code, I suppose.
Camarade_Tux_ has quit [Read error: 110 (Connection timed out)]
<thelema> olegfink: it'd be more than just an open, as camlp4 would be needed to take literals and make them into the appropriate type
<thelema> and / wouldn't behave *that* differently.
<olegfink> I thought you were talking about (/) : int -> int -> float, which doesn't seem to need any preprocessing
<olegfink> I agree that pa_float is somewhat better solution, especially if the code in question would be explicitly marked with Float [...]
<olegfink> (I think I don't remember pa_float's syntax)
<thelema> (/) : number -> number -> number, where number is Int / Float / Big_int / Rat
<mfp> <thelema> olegfink: it'd be more than just an open, as camlp4 would be needed to take literals and make them into the appropriate type -> so you want a global pa_do ?
<thelema> step 1: tag all numeric types needed, step 2: write functions to operate on the tagged types and DWIM lots of operations.
<olegfink> mfp, I just misunderstood thelema
<flo_ml> something like http://nopaste.info/45dfb38b19.html ? => unbound instance variable x.
<thelema> global pa_do? no, more general than that - a replacement math subsystem that avoids all the float vs. int issues.
<thelema> x.vorname <- "flo"
seafood has joined #ocaml
<mfp> thelema: a pa_do enabled by default with an accompaining Number module
<flo_ml> ohhh thanks ;)
<mfp> so everything is processed as if surrounded by Number.( ... )
<olegfink> I can't think of many issue that would require changing the default behaviour
<olegfink> s/issue/&s/
<mfp> but I don't see how that would improve on the current situation
<thelema> mostly allowing users to mix float / int without thinking about types - a number is a number
<mfp> because I do mean integer division when I do 10 / 3
<thelema> "global pa_do" == "open"
<mfp> you also need to rewrite literals
<thelema> mfp: that'd be one exception where we'd have to introduce a symbol to mean integer division.
<thelema> yes, the camlp4 would be needed to rewrite literals.
<thelema> I assume that "normal" division is more normal than integer division.
<mfp> am I the only one who likes having separate (+) and (+.) with distinct types?
* thelema would like a 'pragma' keyword for language-bending features like this.
<thelema> mfp: I think so.
<thelema> The designers of C let ints auto-cast to floats on purpose, I think.
<olegfink> mfp, no, you aren't.
<thelema> heh, I happen to show up in #ocaml when the majority of voices like + vs. +.
<olegfink> mfp, haskell has a complete sublanguage in {-LANGUAGE ...} for such things. but I can't say I want this level of complexity for ocaml
<mfp> I'm all for pa_do and being able to do Float.( 1 + 2.0 ), but I wouldn't want that to become global
<olegfink> s/mfp/thelema/
<thelema> as opposed to ocaml, where our sublanguages are defined in the build system
<vixey> mfp, looks like Coq (1 + 2.0)%float
<mfp> huh
<Smerdyakov> Coq has a very general notion of notation scopes.
seafood_ has joined #ocaml
seafood has quit [Read error: 110 (Connection timed out)]
<hcarty> mfp: I'm a fan of the ( + ) vs ( +. ) operators as well... they catch a lot of bugs which would otherwise be a royal pain to track down. pa_do provides a very nice alternative to a global generic ( + )
<thelema> really? I can understand mixing up a string and a number, but a float and an int meeting usually is time for a cast
itewsh has quit ["KTHXBYE"]
seafood_ has quit []
CoryDambach has quit [Read error: 104 (Connection reset by peer)]
JokerDoom has joined #ocaml
<hcarty> thelema: If the cast is implicit, which way should the cast go?
<hcarty> It has bitten me before in C, and while the ( + ) vs ( +. ) thing annoyed me at first in OCaml, I've been quite happy with it in larger projects
alexyk has joined #ocaml
smimram has joined #ocaml
<hcarty> The only time I find it a major annoyance now is when I'm using the toplevel and want to do a quick calculation. In that case, something like you have proposed would likely be nice
vixey has quit ["There exists an infinite set!"]
<Smerdyakov> hcarty, it sounds like type classes would do just as well for you.
vixey has joined #ocaml
smimou has quit [Read error: 110 (Connection timed out)]
<thelema> hcarty: the cast would go whichever way the user would expect - I'm sure a general rule can be established.
<thelema> hcarty: I agree the extension wouldn't be as appropriate for larger projects, but there are times it'd be useful.
<hcarty> Smerdyakov: That is probably true, though they won't do me much good until I'm in a situation where I want to and am reasonably able to switch to a language with type classes
<hcarty> thelema: I think the extension would be quite useful as well. I'd just prefer it to not be the OCaml-default case :-)
* thelema thinks it'd be good to have as a batteries default - the people who know better are the ones who want to turn it off.
<thelema> If you don't know better, you probably want it on.
<hcarty> I guess that may be a matter of folks new to OCaml vs folks new to Batteries
<thelema> defaults should be conducive to newcomers or experts?
<hcarty> It would change the learning curve for Batteries of one group or the other
<thelema> the learning curve of ocaml experts?
<hcarty> If it were enabled by default
<hcarty> Not many libraries change ( + ) and friends globally
Optikal__ has joined #ocaml
<hcarty> It may be useful for most projects. But it is a pretty big change from the default OCaml way of working.
<thelema> in ocaml that's not common practice. I've been doing a bunch of perl lately, and it works for them.
<thelema> you're making the "backwards compatibility" argument, no?
<hcarty> Not so much backwards compatibility
threeve has joined #ocaml
<hcarty> I'm just worried about losing a compile time check that makes OCaml very useful in a larger project
<hcarty> Or, to be more accurate, in my larger projects
<hcarty> s/accurate/specific/
<thelema> If there were an option to turn off the numerical tower, that'd suffice?
<hcarty> thelema: Probably so, yes
<thelema> that's where I'm headed. A default include of batteries would use the tower, but you could use batteries without the tower too.
<hcarty> thelema: What would the underlying mechanism be? Classes or records? (curiosity)
<hcarty> Or something else?
<thelema> Variant type. all the dispatch logic would go in the functions.
bfrog has joined #ocaml
bfrog has left #ocaml []
<hcarty> Is there a significant performance difference between using variant types vs classes or records?
Kerris7 has quit []
<thelema> yes, for classes, and you'd pretty much need to use a variant inside your record anyway.
<hcarty> Ok. I wasn't sure how much of a difference caching would make on the class side
<thelema> hmm, maybe needs benchmarking.
<hcarty> And I imagine the specifics would depend on how the code is used
flo_ml has quit [Remote closed the connection]
<thelema> definitely more space for objects, probably not worth having one level of dispatching implemented by the compiler.
<Camarade_Tux> iirc objects are about six times slower than an equivalent code using records or variants (simple micro-benchmarks)
<thelema> Camarade_Tux: except the caching of records may beat manual dispatching in a function.
<hcarty> (also microbenchmarks) I've found objects to be similarly performant to records when used as simple records
<hcarty> But given that there is compiler magic involved, it's all but certainly application-specific
* thelema doesn't see any need for code to be attached to numeric values - it'll have to be multiple dispatch anyway.
<hcarty> Is code shared between objects of the same class, or is it duplicated for each object?
<thelema> of course it's shared - iirc, there's a pointer to the dispatch structure
love-pingoo has quit ["Connection reset by pear"]
<Camarade_Tux> thelema, I think that was one of the issues raised about the benchmark but I'd need to find a link to the thread (and read it again myself)
<Camarade_Tux> (only for dispatch btw)
<hcarty> thelema: I'm off for now, but I am looking foward to see what comes of this library + extension
<thelema> just an idea - lots to work on.
Snark has quit ["Ex-Chat"]
* thelema is trying to figure out why this one commit in ocaml's CVS breaks my compile but hasn't affected anyone else's...
Stefan_vK has joined #ocaml
thelema has quit [Read error: 60 (Operation timed out)]
Galaxor has quit [Read error: 110 (Connection timed out)]
alexyk has quit []
dank0 has quit ["Ex-Chat"]
<Optikal__> draw_prim (1., 1., 1.) `line_strip (Array.iter vertex) [|vec2 0. 1.; vec2 0. 0.; vec2 1. 0.; vec2 1. 1.|] is giving me this error on compile: This expression has type Vec2.t array -> unit but is here used with type (Vec2.t -> unit) -> 'a -> 'b
Stefan_vK1 has quit [Read error: 110 (Connection timed out)]
<Optikal__> ah I tink i found it
<Optikal__> newp hmm
pumpkin_ has quit []
pumpkin_ has joined #ocaml
pumpkin_ has left #ocaml []
alexyk has joined #ocaml
<alexyk> is there a shorter way to get every 3rd element of a list than
<alexyk> List.fold_left2 (fun acc a i -> if i mod 3 == 0 then a::acc else acc) [] ['a';'b';'c';'d';'e';'f'] [1;2;3;4;5;6];;
<Camarade_Tux> List.nth ?
<hcarty> alexyk: You likely also want to use ( = ) rather than ( == )
Palace_Chan has joined #ocaml
<Palace_Chan> i keep getting a syntax error on this line what is wrong ?
<Palace_Chan> try let b = blocks.(!i) in with Invalid_argument -> Printf.printf "exception frontier %d" (!i); failwith "fail"
<Camarade_Tux> 'in with'
<Palace_Chan> i still get the syntax error if i just get rid of the in word
<olegfink> alexyk: well, not really different way, but I'd use combine/split
alexyk has left #ocaml []
<Camarade_Tux> Palace_Chan, 'in ()' I guess
alexyk has joined #ocaml
Galaxor has joined #ocaml
<olegfink> alexyk: well, not really different way, but I'd use combine/split (if you missed it the first time)
Galaxor has left #ocaml []
<alexyk> oops, my colloquy osscilatted
<alexyk> oscillated
<alexyk> so List.nth returns only one nth, right?
<olegfink> Palace_Chan: or the other way around, let b = try ... with ... in ...
<alexyk> Camarade_Tux: is there a shorter way with nth than fold_left2 ... mod ... range?
<Palace_Chan> ill try that
<alexyk> olegfink: I don't want to create intermediate objects
<olegfink> you create [1..n] anyway
<olegfink> alexyk, let rec third = function a::_::_::xs -> a::(third xs) | _ -> [] probably does what you want
<olegfink> with the downside of being an explicit (and non-tail) recursion
<alexyk> olegfink: true
<alexyk> olegfink: I'm also not sure about the edge cases
Kerris7 has joined #ocaml
<olegfink> alexyk: you mean cases like lists with length not evenly divisable by 3?
<olegfink> _ -> [] says 'just discard the remainder'
<vixey> why don't you make a new kind of list
<olegfink> because there's apparent need in a new language
itewsh has joined #ocaml
<vixey> huh
<alexyk> olegfink: ah, ok
<Palace_Chan> how can i, after a List.find operation on a list...obtain a list without the found item ? if i use filter ill remove all copies of the removed item as well and not just the one found by the find
<vixey> Palace_Chan, a good function is select : ('a -> bool) -> 'a list -> ('a * 'a list) option
<Palace_Chan> what module may i find that in ?
<Camarade_Tux> or implement your own list_first_filter
<vixey> Palace_Chan, you have to write it
<Camarade_Tux> s/first_filter/filter_first
<Palace_Chan> i guess so, only way i can think of of writing something like that is to turn my input list into an assoc list with index as key
alexyk has quit []
<Camarade_Tux> I hate having to implement my own read_file for every *small* program I write
alexyk has joined #ocaml
alexyk has quit [Client Quit]
<Smerdyakov> Camarade_Tux, gosh, too bad it
<Smerdyakov> Camarade_Tux, gosh, too bad it's not possible to build your own libraries!
<Camarade_Tux> Smerdyakov, I don't want to add another requirement for a five-liner in such a small program
<Smerdyakov> Camarade_Tux, why not?
<Camarade_Tux> because I prefer to keep things independant
<Camarade_Tux> I think I'll write it somewhere and copy-paste it whenever I need it
Smerdyakov has quit ["Leaving"]
Smerdyakov has joined #ocaml
Smerdyakov has quit [Read error: 104 (Connection reset by peer)]
Smerdyakov has joined #ocaml
<olegfink> well, from what I've seen, Batteries provide many of the things that were traditionally in the haskell's real, including pretty tasty IO
<mbac> solid? what's solid?
<vixey> people are nuts
<Camarade_Tux> I'm not in favor of making gallium's lib a huge beast but I think a read_file function : string -> string (not sure about string as a parameter) would really be helpful
<mbac> some people over at #lisp said something about solid -> ocaml what slime -> lisp
Palace_Chan has quit [Client Quit]
ygrek has quit [Remote closed the connection]
<det> Camarade_Tux, batteries included has a read_file type function (works on any kind of type input, not just files)
<det> I am also annoyed to implement that in everything I write
thelema has joined #ocaml
<Camarade_Tux> but why is not in Pervasives or List ? ='(
sporkmonger has quit []
<det> why would it be in List ?
<Camarade_Tux> right, not in List. I was not really paying attention and had written a read_file returning a string list ;)
<det> btw, I dont think a function read_file: string -> string is a good idea, I prefer batteries: input -> string
* Camarade_Tux is actually watching V
<det> ahh, I think batteries also provides a read_lines
<det> which returns an enum
<det> which is better than list, IMO
<det> System.IO.lines_of
<Camarade_Tux> yeah, string -> string feels a bit hackish ;)
<det> also has things like chunks_of
<Camarade_Tux> s/hackish/perlish ;)
<Camarade_Tux> need to sleep
jeddhaberstro has joined #ocaml
<Camarade_Tux> and I now only need to implement signals/callbacks in my webkit-gtk bindings :)
olgen has quit []
Palace_Chan has joined #ocaml
pumpkin_ has joined #ocaml
pumpkin_ has left #ocaml []
petchema has quit [Read error: 113 (No route to host)]
petchema has joined #ocaml
Yoric[DT] has joined #ocaml
seafood has joined #ocaml
itewsh has quit ["KTHXBYE"]
rwmjones has joined #ocaml
vixey has quit ["There exists an infinite set!"]