<palomer>
if i copy/paste the output of camlp4o, it runs fine
jeanbon has quit ["EOF"]
<palomer>
if I use camlp4, I get the error "Unbound constructor lv1"
<palomer>
presumably on this line of code: method load = function | { foo = lv1 } -> v1#load lv1
<julm>
palomer: and if you use camlp4 -printer o ?
jeddhaberstro has joined #ocaml
<palomer>
right now I'm using ocamlfind -syntax camlp4o
<palomer>
ocamlfind ocamlopt -syntax camlp4o -package 'unix' -warn-error A -I . -c test.ml <--this is the full line, what do you want me to change it to?
<julm>
I remember a bug in camlp4 present when output was textual and not present when the output was binary
<julm>
this "Unbound constructor lv1" is strange, because lv1 is not a constructor, it does not even begin with a cap
<julm>
what gives: ocamlfind ocamlopt -syntax 'camlp4o -printer o' -package 'unix' -warn-error A -I . -c test.ml
<palomer>
one sec...
<palomer>
same...
<julm>
:/
<palomer>
I think it's because of my pattern
<palomer>
here's the code:
<palomer>
<:patt< $lid:a$ = $uid:"l"^b$
<palomer>
oh my
<palomer>
uid is uppercase!!
<julm>
you got it ?
<palomer>
well, it would explain it
<julm>
and you can fix your problem now ?
<travisbrady>
is 'type' equivalent to 'data' in Haskell?
<palomer>
it works!
<palomer>
yeah
<palomer>
travisbrady, basically
<palomer>
travisbrady, so ocaml's type embodies both haskell's type and haskell's data
<travisbrady>
ahh, so i can say 'type blah = Int'?
<travisbrady>
and what about newtype?
<palomer>
travisbrady, types are lowercase
<julm>
palomer: great ;)
<palomer>
travisbrady, there's no newtype
<palomer>
julm, so I was using uid: , which tells camlp4 that it's an uppercase identifier
<palomer>
travisbrady, there's no newtype because ocaml doesn't have typeclasses
<travisbrady>
palomer: is there some similarish mechanism?
<palomer>
classes, I guess
<palomer>
you can also do something similar with existential types, which are encoded with universal types, which is rather complicated
<travisbrady>
oh the OO stuff? i've heard that's rarely used
<palomer>
I use it pervasively
<palomer>
though the people on this channel are constantly discouraging me
<julm>
I rarely need to use the OO stuff that much but it's an interesting technology
<mbishop>
nice to have options
maxote has quit [Read error: 110 (Connection timed out)]
travisbrady has quit []
<palomer>
is it possible to ask camlp4 to tell me where my syntax error is?
<palomer>
right now it just says "syntax error"
<julm>
don't you have something like : File "/tmp/src/test.ml", line 1, characters 0-4:
<julm>
generally camlp4 is quite accurate in reporting syntax error
<palomer>
I have:
<palomer>
File "test.ml", line 1, characters 6-8:
<palomer>
Syntax error
<julm>
isn't it accurate enough?
<julm>
you mean you want to have the syntax error in the processed output ?
<julm>
well, for that I personnally use -printer o
<julm>
and two files
<julm>
test.ml4 (the source) and test.ml (the output of camlp4 on test.ml4)
Ched has quit [Read error: 110 (Connection timed out)]
ched_ has joined #ocaml
<palomer>
gotcha
alexyk has joined #ocaml
mishok13 has joined #ocaml
Raynes has joined #ocaml
jeff_s_ has joined #ocaml
mishok13 has quit [Read error: 60 (Operation timed out)]
palomer has quit ["Leaving"]
jeddhaberstro has quit []
sfmatt has joined #ocaml
<sfmatt>
Hi, trying to create a type to represent a n-ary hierarchy and could use some help
<sfmatt>
Why is this fine: type test = Genre of (string * test list);; when this is not: type test = (string * test list);;
ulfdoz_ has joined #ocaml
<jli>
sfmatt: interesting!
sporkmonger has quit []
ulfdoz has quit [Read error: 101 (Network is unreachable)]
ulfdoz_ is now known as ulfdoz
palomer has joined #ocaml
<palomer>
how do I print a ctyp?
<palomer>
nevermind
* palomer
wonders if ever type-conv will ever be able to harness the power of .cmi files to automatically generate stuff
<sfmatt>
ok it seems that "you need atleast one constructor in order to declare a recursive type
<sfmatt>
but then I have another hopefully simpler question, how do you declare a list type for non-trivial types?
travisbrady has joined #ocaml
<sfmatt>
Example: type x = (float option) list;; compiles but type x = (A of string | B of float) list;; does not...
<jli>
sfmatt: what's the intent of that? a list of something that's either an A or a B?
<sfmatt>
yes
<jli>
type a_or_b = | A of string | B of float;;
<jli>
type x = a_or_b list;;
<jli>
I don't think you can stick it all in one declaration
<sfmatt>
Thanks, what's strange is that I'm under the impression it's Ok when I look at the ocaml manual (the typexpr BNF).
<jli>
oh, hum. maybe it's a bug.
<sfmatt>
I certainly cannot assess if it's one given my expertise ;-)
<jli>
what part matches what you're trying to do?
<jli>
" ( typexpr { , typexpr } ) typeconstr " ?
<jli>
the | A of .. | B of ... is a variant-type. not sure what "'a list" is
<jli>
it's a poly-typexpr, I think
<jli>
okay, nevermind. enough bad guesses from me for tonight :)
<sfmatt>
Back to my original problem, building a type for a n-ary category hierarchy...
<sfmatt>
My best attept so far is let test = Genre of string | SubGenre of (string * test list);;
mishok13 has joined #ocaml
<jli>
sfmatt: could you explain what a category hierarchy is?
<sfmatt>
for example the categorization of Amazon content
<sfmatt>
the top level is music, movies, home & garden etc...
<sfmatt>
then you can dig one level and you get the genres for music
<sfmatt>
etc
<sfmatt>
it's like a tree, n-ary instead of binary
<sfmatt>
A bibary tree would look like let tree = Leaf of string | Node of tree * tree;;
<sfmatt>
sorry binary
<sfmatt>
so n-ary would be: type tree = Leaf of string | Node of (string list);; which again does not compile...
<jli>
works for me
<sfmatt>
sorry I meant for the n-ary tree: type tree = Leaf of String | Node of (tree list);;
<jli>
that works for me too
<sfmatt>
sorry it works for me too
<jli>
so, does anything not work? :)
<julm>
sfmatt: if you ever come to need recursive types it can be done by passing -rectypes to ocaml, that said I've personally never had to.
<sfmatt>
It does, in the end I am just being lazy. I was hoping for a concrete syntax that would be simple enough that I could define my hierarchy "manually" in a human readable form.
<julm>
type x = (A of string | B of float) list < you cannot do that because then there would be no type for: A "toto", howaver you can use do type x = [`A of string | `B of float] list
<julm>
-do
<sfmatt>
Instead of having to use Leaf and Node to contsruct a hierarchy,again I'm just lazy
<sfmatt>
Thanks a lot julm it makes sense now.
hto_ has joined #ocaml
hto has quit [Read error: 104 (Connection reset by peer)]
mishok13 has quit [Read error: 110 (Connection timed out)]
mishok13 has joined #ocaml
alexyk has quit []
nickname` has quit ["Sto andando via"]
alexyk has joined #ocaml
mishok13 has quit [Read error: 110 (Connection timed out)]
julm has quit [Read error: 113 (No route to host)]
alexyk has quit []
kaustuv_ has joined #ocaml
hkBst has joined #ocaml
seafood has joined #ocaml
kaustuv has quit [Read error: 104 (Connection reset by peer)]
alexyk has joined #ocaml
Associat0r has quit []
BiD0rD has joined #ocaml
m3ga has quit ["disappearing into the sunset"]
BiDOrD has quit [Read error: 110 (Connection timed out)]
Jedai has quit [Read error: 110 (Connection timed out)]
hto_ has quit ["Lost terminal"]
rwmjones_ has joined #ocaml
alexyk has quit []
vithos has quit [Read error: 60 (Operation timed out)]
vithos has joined #ocaml
alexyk has joined #ocaml
alexyk has quit []
travisbrady has quit []
hkBst has quit [Remote closed the connection]
seafood_ has joined #ocaml
seafood has quit [Read error: 110 (Connection timed out)]
<mfp>
robocop: wrap try ... with begin/end or parentheses
slash_ has quit [Client Quit]
<mfp>
robocop: otherwise, the following patterns are associated to try ... with ..., not to function
<robocop>
mfp: this works : try (if 3 = 2 then List.tl [4] else List.hd []) with _ -> failwith "pas ok";;
<mfp>
mfp: the problem is that you have | Leaf(a, err) -> after with
<mfp>
so it becomes try .... with _ -> .... | Leaf (...) -> ...
<robocop>
Ha, yes !
<robocop>
thanks.
<mfp>
np
Camarade_Tux has joined #ocaml
seafood_ has quit []
jli has quit [Nick collision from services.]
jli has joined #ocaml
angerman has joined #ocaml
seafood has joined #ocaml
seafood has quit [Client Quit]
vithos has quit []
alexp__ has joined #ocaml
ikaros has joined #ocaml
verte has joined #ocaml
Yoric[DT] has joined #ocaml
rjack has joined #ocaml
_zack has joined #ocaml
vpalle has joined #ocaml
kaustuv_ is now known as kaustuv
LeCamarade has joined #ocaml
ched__ has joined #ocaml
ched_ has quit [Read error: 110 (Connection timed out)]
schme has joined #ocaml
ched__ has quit [Remote closed the connection]
komar_ has quit [Remote closed the connection]
komar_ has joined #ocaml
rjack has quit ["leaving"]
ulfdoz has quit [Read error: 110 (Connection timed out)]
ulfdoz has joined #ocaml
Associat0r has joined #ocaml
maxote has joined #ocaml
ulfdoz has quit [Success]
ulfdoz has joined #ocaml
Camarade_Tux has quit ["Quitte"]
Camarade_Tux has joined #ocaml
fschwidom has joined #ocaml
<flux>
ocamlnet sure covers pretty much everything, but at times it can be daunting: apply_relative_url (remove_from_url ~path:true u) (make_url ~path:["bar";] (partial_url_syntax (Hashtbl.find common_url_syntax "http")))
<kaustuv>
generally to write expressions f(g(h(i(j(k))))) it is better to use a series of lets
<Camarade_Tux>
is there no simplified interface to it, with default "ok" values ?
<Camarade_Tux>
or was it pxp ?
<flux>
well, that's the result of me finding my way through in the toplevel
<flux>
I'm just trying to follow relative redirections from an url
Jedai has joined #ocaml
<mrvn>
I also always put a space before the (
schme has quit [Remote closed the connection]
<Camarade_Tux>
I'm sure pxp and netclient would benefit from some faq/code snippets
Snark has joined #ocaml
seafood has joined #ocaml
schme has joined #ocaml
_andre has joined #ocaml
love-pingoo has joined #ocaml
love-pingoo has quit [Client Quit]
kaustuv has quit ["ERC Version 5.3 (IRC client for Emacs)"]
pants1 has joined #ocaml
komar_ has quit [Read error: 113 (No route to host)]
pants2 has quit [Read error: 60 (Operation timed out)]
Ched has joined #ocaml
ikaros has quit [Read error: 110 (Connection timed out)]
seafood has quit [Read error: 110 (Connection timed out)]
Yoric[DT] has quit [Read error: 60 (Operation timed out)]
Raynes has left #ocaml []
rjack has joined #ocaml
jeff_s_ has quit ["Leaving."]
seafood has joined #ocaml
ched_ has joined #ocaml
Ched has quit [Read error: 110 (Connection timed out)]
sporkmonger has joined #ocaml
<Camarade_Tux>
everytime I think I'm done with ocaml-gir, a new thing to implement appears =/
<flux>
that's what happens with software :)
<Camarade_Tux>
especially undocumented software =/
<Camarade_Tux>
right now, it feels like retro-engineering functors written in C/GTK ><
feydr_ has quit ["leaving"]
ched__ has joined #ocaml
ikaros has joined #ocaml
ched_ has quit [Read error: 110 (Connection timed out)]
hkBst has joined #ocaml
Associat0r has quit []
robocop has left #ocaml []
ched__ has quit [Read error: 60 (Operation timed out)]
<Camarade_Tux>
gar, I added basic broken support for a few xml nodes and hard coded some types and now it can ends the processing, many things are broken however
julm has joined #ocaml
kig has joined #ocaml
alexyk has joined #ocaml
alexyk has quit [Client Quit]
Ched has joined #ocaml
verte has quit ["~~~ Crash in JIT!"]
<gildor>
Is it me or the OCaml doc describing howto to interface C with OCaml is not clear about variant type ?
<gildor>
e.g. for 'a option
<flux>
when you dig the specification for option, it's None | Some of 'a, isn't that covered?
<gildor>
reading the documentation, I was believing that I will get a block of size 2
Ched has quit [Read error: 110 (Connection timed out)]
<gildor>
but I get a block of size 1
<gildor>
with Field(v, 0) containing 'a
<thelema__>
gil: not necessariy. you'll get a value, that value could be a block of size 1 (header + pointer to 'a value) or a single value
<gildor>
thelema__: I must agree, since it is true
<gildor>
thelema__: but after reading the doc ( 18.3.6 Variants )
<thelema__>
okay, the size of the block is # of words past header (excepting packed float blocks)
Ched has joined #ocaml
<thelema__>
variants either have arguments or don't.
<gildor>
The variant value `VConstr(v) is represented by a block of size 2 and tag 0, with field number 0 containing hash_variant("VConstr") and field number 1 containing v.
<thelema__>
each variant with arguments gets tagged 0..n, and has a the appropriate size block for its arguments
<thelema__>
that's a polymorphic variant.
<gildor>
yep
<gildor>
In my case, I get a block of size 1 with tag 0
<gildor>
for (Some 'a)
<thelema__>
variants without arguments are represented as ocaml ints 0..n
<gildor>
'a = custom block
<thelema__>
yup, Some is the 0th variant with a constructor, and it only has one argument
<gildor>
thelema__: did you read it in the doc ?
<thelema__>
it's probably in there somewhere...
<gildor>
I know, you are true, but it doesn't seems documented in the doc
<gildor>
thelema__: if it is not, I will fill a bug against OCaml about this; it is not clear and is quite important
<gildor>
thelema__: can you tell me where you learn this ?
<julm>
gildor: "Non-constant constructors declared with a n-tuple as argument are represented by a block of size n, tagged with the constructor number;"
<thelema__>
or maybe we need an example with multiple constructors of each type
<thelema__>
gildor: I agree with you in terms of a minor fix to the official docs, but in the longer term, a notation for in-memory values will be really useful for talking about representations
<gildor>
yes
seafood has quit [Read error: 110 (Connection timed out)]
<flux>
that's the signature of the module you need to provide
<robocop>
ha, okey.
<flux>
so, have something like: module P = struct let server = "localhost" .. etc.. end
<flux>
the type of that module patches that signature, which is sufficient
<flux>
or, you can be explicit: module P : Irc.Client_params = struct .. end
alexp__ has quit [Read error: 110 (Connection timed out)]
<travisbrady_>
What do people here find compelling/interesting/novel/mindblowing about OCaml? specifically coming from a Haskell background? I'm thinking of playing with Ocaml some but can't decide on a starter project
palomer has quit [Remote closed the connection]
<flux>
I wouldn't say I have Haskell background, but in my personal experience O'Caml is a lot faster to get into than Haskell
<flux>
(that is, I've studied some Haskell and written small programs)
<flux>
also, the compiler is tons faster and the interactive toplevel actually lets you enter programs (with types) in :)
<travisbrady_>
ahh, that last part is nice, that's a persistent annoyance of mine
<travisbrady_>
faster executables are nice, though haskell can be fast, but it often takes some doing
<flux>
fast has been sufficient for me
<flux>
s/fast/speed/
<flux>
the integration with emacs is nice. compile with -annot and you can move your cursor over an expression and retrieve its type with C-c C-t.
<flux>
also if you have installed OcamlSpotter you can find the definition of symbol with a keystroke (more accurate than a simple tags-based approach)
<travisbrady_>
oh neat, I'm a vim person, but still cool to hear
<flux>
I think there's something for vim too
<flux>
-annot just produces an auxiliary file that tools can be make use of
<travisbrady_>
is there some equivalent in the interactive toplevel to ":t" in ghci?
<flux>
I imagine monadic code in ocaml would perform worse than in haskell, but if you want to use them, you can. I've used monads for database and CPS-based message passing abstractions.
julm has left #ocaml []
<flux>
travisbrady_, well, if you enter a value the toplevel will tell its type in addition to its value
julm has joined #ocaml
<flux>
there is an enhtop that adds certain features to the toplevel, but I haven't tried it
<flux>
s/an enhtop/a project called enhtop/
<travisbrady_>
cool to hear it's easier to get into, i initially chose Haskell because I found it more readable, so if OCaml's easier maybe I can bang out my starter project in a weekend or something
<schme>
travisbrady_: ocaml is not such a pain in the arse about being functional.
<mfp>
travisbrady_: btw, vim ships with annot support -> <LocalLeader>t to get the type of the expr under the cursor
<flux>
mfp, does it have something for sending expressions to ocaml?
<flux>
those two basically cover all the emacs ocaml support I make use of
<mrvn>
Ocaml is much more "fun" than haskell
Yoric[DT] has joined #ocaml
<mfp>
flux: not in the std distro; there might be something out there for that, though (doesn't sound too hard to implement)
<flux>
travisbrady_, one interesting thing ocaml has going on is the preprocessor. I understand haskell has template haskell, but it seems even higher order magic than camlp4..
<travisbrady_>
flux: i'll have a look at camlp4
<flux>
travisbrady_, the syntax extensions can for example make writing monadic code simpler, create datatypes for you, create pretty printers for you (think 'deriving'), etc
<travisbrady_>
well, i think Haskell is pretty fun, but glad to know OCaml is too
<mrvn>
# let the = fun _ -> begin end;;
<mrvn>
val the : 'a -> unit = <fun>
<mfp>
travisbrady_: is it possible to define arbitrary syntaxes in TH, or do you always have to use Oxford brackets?
<Camarade_Tux>
the module is not automatically loaded
<Camarade_Tux>
or start ocaml with 'ocaml str.cma'
<travisbrady_>
Camarade_Tux: ahh, thank you
* palomer
wonders why str is not automatically loaded
<Camarade_Tux>
unix is not automatically loaded either, that's maybe because they use side-effects (and nicely fail if you load them several times [at least for unix])
<aij>
palomer: because it's not in stdlib?
<palomer>
but...why isn't it in stdlib?
<thelema__>
it was developed separately, and never needed integration.
<aij>
palomer: possibly because it depends on str.a
vpalle has quit [Connection timed out]
vpalle has joined #ocaml
gdmfsob has quit [Read error: 131 (Connection reset by peer)]
gdmfsob has joined #ocaml
<thelema__>
aij: that's just a packaging issue - all that code could be in the stdlib.a
julm has quit [Read error: 110 (Connection timed out)]
julm has joined #ocaml
_andre has quit ["leaving"]
<travisbrady_>
why do I get a non-exhaustive pattern warning here? val a : int list = [1; 2; 3]
<travisbrady_>
# let (x::y::z::[]) = a;;
<kig>
because a might be a longer list or a shorter list, probably
<palomer>
yeah, the compiler does not store the size of lists in its type
<mrvn>
We have tuples for that.
<palomer>
the problem with tuples is that they are a set of types
<palomer>
you can use GADTs to encode lists of determined size
<monadic_kid>
travisbrady: as someone has just said you're pattern match may failure and your code is ocaml
<monadic_kid>
travisbrady: failure because you may have an empty list, a list with less than 3 elements
<mrvn>
or more
<monadic_kid>
yeah
<palomer>
let [x;y;z] = a is nicer syntax
<monadic_kid>
or more
<monadic_kid>
erhh i'm getting confused what channel i'm in
<flux>
you could use bluestorm's pa_refutable.ml? to hide the warning, where it would be something like: let refutable [x; y; z] = [1; 2; 3]
<monadic_kid>
*getting confused with which channel i'm in
<palomer>
that's a nice extension
<monadic_kid>
i thought i was in haskell thinking someone was asking about ocaml code in haskell
<palomer>
so...who here has 3.11.1rc0 ?
<hcarty>
There is fixed-size array code floating around somewhere, with the size encoded in the type. I imagine something similar could be done with a list.
<monadic_kid>
hcarty: with dependant types yes
<mrvn>
I wish one could declare a int '3 list for this
<flux>
monadic_kid, I don't think you even need dependant types for some effect..
<monadic_kid>
hcarty: you want to know the size of list at compile-time?
<flux>
but obviously there are limits on what you can reach :)
<palomer>
but then what would be the return type of fun x -> if foo then [] else [1] ?
<hcarty>
monadic_kid: I don't have a particular need for that
<hcarty>
monadic_kid: Just saying that a similar technique could probably be adapted for lists
<monadic_kid>
hcarty:but was that what you was talking about?
<mrvn>
palomer: [< '0 list, '1 list ]
<hcarty>
monadic_kid: I'll try to find the mailing list posting
<palomer>
ok, what about fun x -> make (g ()) 1 where make n i makes a list of length n containing all is
<mrvn>
palomer: that lacks the info that 'b is a '<int> type.
<hcarty>
monadic_kid: That provides type-checked array dimensions
<mrvn>
hcarty: one can do that?
<travisbrady_>
is there an ocaml equivalent to Maybe in haskell?
<hcarty>
mrvn: It's rather ugly, but the that posting has code to do it
<flux>
travisbrady_, the option-type: type 'a option = None | Some of 'a
<travisbrady_>
flux: awesome, thank you
<travisbrady_>
and is there something like Data.Maybe.catMaybes?
fschwidom has quit [Read error: 104 (Connection reset by peer)]
<monadic_kid>
hcarty: i know what phantom types. You can do the same thing bit more nicer with type classes and functional dependencies (and better with associated types). This is just basically emulating dependant type system, kind of like expression templates
itewsh has joined #ocaml
<mrvn>
hcarty: that example is limited to arrays of size 10
<hcarty>
mrvn: I don't think so. It is stackable
<hcarty>
monadic_kid: I'm just the messenger :-)
<mrvn>
type 'a d0 and 'a d1 and 'a d2 and 'a d3 and 'a d4
<mrvn>
type 'a d5 and 'a d6 and 'a d7 and 'a d8 and 'a d9
<hcarty>
mrvn: I haven't toyed with it in a while, but according to the message and from what I remember testing it, you can stack them
<hcarty>
let d1230 = dec d1 d2 d3 d0 dim;; for example
<mrvn>
hcarty: that is 4 dimensions, each one size 10 except the last.
<mrvn>
or am I reading this wrong?
<hcarty>
mrvn: No, that's an array with 1230 elements as I understand it
<mrvn>
ahh, my mistake. I see.
<mrvn>
makes sense.
<mrvn>
crafty to encode the decimal digits into a string of types.
<hcarty>
mrvn: Indeed
<hcarty>
Some camlp4 magic could probably clean it up as well.
ulfdoz has quit [Read error: 110 (Connection timed out)]
<travisbrady_>
is there an easy way to print values of any type? not in the toplevel, I mean in actual source code
bombshelter13_ has quit []
angerman has quit []
<hcarty>
travisbrady_: OCaml doesn't not keep type information around after compilation, so without extra code you are restricted to printing the data representation
willb has quit [Connection timed out]
<hcarty>
travisbrady_: I think Batteries has a function called "dump" or similar which does this
schme has quit [Read error: 113 (No route to host)]
<hcarty>
travisbrady_: Batteries also has a module Print which provides user-defined printf augmentations. There are other libraries and syntax extensions which can generate automatic printers.
gdmfsob has quit ["Leaving"]
gdmfsob has joined #ocaml
moncef has joined #ocaml
moncef has left #ocaml []
<travisbrady_>
why is this a type error? # let nint x = truncate (x + 0.5);; "This expression has type float but is here used with type int"
<Camarade_Tux>
replace + with +.
<travisbrady_>
oh right
komar__ has quit [Remote closed the connection]
<travisbrady_>
Camarade_Tux: thank you
<Camarade_Tux>
:)
itewsh has quit ["There are only 10 kinds of people: those who understand binary and those who don't"]
<travisbrady_>
sorry to keep asking questions, but what is the list subscript operator in ocaml?
OChameau-bis has quit [Read error: 110 (Connection timed out)]
<thelema__>
travis: no operator - only List.nth
<thelema__>
the only list operator is :: to prepend (or deconstruct)
<monadic_kid>
i think he/she is getting confused with a list and array
Ched has joined #ocaml
<Camarade_Tux>
(* and (@) :D *)
<Camarade_Tux>
I'm wondering if anyone would miss @
kaustuv has joined #ocaml
<thelema__>
Camarade_Tux: I wouldn't miss (@) - if people want to do that they should be penalized by having to type List.append
<Camarade_Tux>
thelema__, that's exactly what I had in mind ;)
<thelema__>
travisbrady_: array subscripting is arr.(i), string suibscripting is str.[i]
* palomer
loves @
<Camarade_Tux>
I sometimes use @ actually, but only when I'm sure the list is has less than 40 elements
* thelema__
bonks palomer
<travisbrady_>
thelema__: cool, thank you
* thelema__
wonders if ocamlers look on stack overflow for these kinds of questions.
ikaros_ has joined #ocaml
<Camarade_Tux>
my biggest concern is not stack overflow, it's just appending to a list, it makes me wanna cry ='(
<travisbrady_>
mrvn: and what is the 'val' bit? a type annotation?
<mrvn>
travisbrady_: output from the toplevel
<travisbrady_>
is it common to declare your types in source files in Ocaml?
<mrvn>
quite the reverse
<travisbrady_>
your version still throws "This expression has type (int option * 'a option * int option) list but is here used with type 'b option list"
<mrvn>
00:20 < mrvn> second problem: lists elements are seperated by ; and not ,
<travisbrady_>
ahh, my mistake
<travisbrady_>
so what is the type of "[1,2,3]"?
<rwmjones_>
(int * int * int) list
<mrvn>
(int*int*int) list
* rwmjones_
wonders where is xavierbot?
<mrvn>
travisbrady_: , creates tuples.
<travisbrady_>
ahh, ok, like [(1,2,3)] in haskell or python
<mrvn>
travisbrady_: the () are not neccessary
<Camarade_Tux>
but that's the idea
<rwmjones_>
one can write: [1, 2, 3; 4, 5, 6]
<mrvn>
In ocaml () truely only declares precedence. Nothing more.
<mrvn>
I always write (a, b, c) for readability though.
<mrvn>
tomaw: Funktioniert das dann auch auf der console?
<mrvn>
ups
ikaros_ is now known as ikaros
monadic_kid has quit ["Leaving"]
slash_ has quit [Client Quit]
mishok13 has joined #ocaml
hcarty_ has joined #ocaml
mishok13 has quit [Read error: 60 (Operation timed out)]
maxote has quit [Client Quit]
maxote has joined #ocaml
hcarty has quit [Read error: 104 (Connection reset by peer)]
m3ga has joined #ocaml
mishok13 has joined #ocaml
jeanbon has quit ["foo"]
<palomer>
mrvn, () can also be unit!
jmou has joined #ocaml
vpalle has quit [Read error: 110 (Connection timed out)]
vpalle has joined #ocaml
julm has quit [Read error: 110 (Connection timed out)]
maxote has quit [Connection timed out]
jmou is now known as julm
Yoric[DT] has quit ["Ex-Chat"]
ikaros has quit [Read error: 110 (Connection timed out)]