<alexyk>
when I access Str from toplevel, I do #load "str.cma";; -- but if I try to compile a file with it I get a syntax error on that line, why?
<thelema>
alexyk: because you can't do # declarations outside the toplevel.
<qwr>
alexyk: becouse those #directives are not part of ocaml language
<thelema>
alexyk: the way to use str.cma from a compiled program is to link with them
<thelema>
ocamlc str.cmxa myprog.ml
evn_ has joined #ocaml
<alexyk>
right -- so I guess the way to develop is to issue # directives manually in tuareg's toplevel, leaving them off the files, right? I also saw them in Markus's shell scripts, but I guess that's because they start with #!...ocaml
szell has quit [Read error: 110 (Connection timed out)]
<qwr>
is your problem
<qwr>
and no, it don't work
<alexyk>
qwr: of course
<alexyk>
()
<alexyk>
we just talked about
<qwr>
that print_newline just sits there emitting it's function value into outer space or something ;)
szell has joined #ocaml
<alexyk>
works without () :)
<thelema>
alexyk: I don't believe you on that.
kopophex has quit [Connection timed out]
<alexyk>
thelema: wanna bet? It prints numbers on my Mac OSX with 3.10.1
<qwr>
alexyk: of course. but not the newline
<alexyk>
works without the newline :)
<alexyk>
ok, with () works fine as expected
<qwr>
those parts that don't give warning work ;)
<alexyk>
so I join print statements with ; and it works here without begin...end wrap -- when woudl I need to use begin...end? found I need it in if/else, what's the justification for the difference?
<qwr>
alexyk: put some print_endline "line done" after try with ;)
<ikatz>
alexyk: it has to do with precedence i believe
vincenz_ is now known as vincenz
<qwr>
alexyk: basically yes, ()/begin end allow grouping a part of expression
<qwr>
alexyk: differently than it would be grouped by default rules
<qwr>
alexyk: (in the grammar)
<ikatz>
since you can create an if/else without the else, the compiler looks for an else after the statement that follows the if
<ikatz>
if you have a semicolon and another statement, it assumes that the else is implicit
<ikatz>
and (hopefully) gives you an error before you get into trouble at runtime
<alexyk>
ikatz: ok
<qwr>
match Some x -> (match x with 33 -> "a" | _ -> "z") | None -> "..."
<qwr>
this would be incorrect without parenthesis
<thelema>
qwr: match Some 33 -> "a" | Some _ -> "z" | None -> "..."
<Ramzi181>
Can you explain the error? Where is the type unit?
<qwr>
thelema: yes, this can be simplified so ;)
<thelema>
Ramzi181: comingfrom t shouldn't have a ; after it.
<thelema>
or you should do "match l with [] -> ()" to return unit
<Ramzi181>
I don't understand.
<thelema>
comingfrom returns [], the empty list.
<thelema>
you probably want it to return (), unit.
<Ramzi181>
Why does the semicolon there hurt? Also, I don't care what the return type is.
<thelema>
because you have "comingfrom t;" ocaml expects a unit return type.
<qwr>
Ramzi181: btw I suggest you avoid the list @ [ element ] pattern
<qwr>
Ramzi181: it's terribly ineffective
<Ramzi181>
why does ocaml expect a unit return type?
<Ramzi181>
qwr: Yes, I understand.
<thelema>
Ramzi181: because that's what functions that don't return anything return.
<qwr>
Ramzi181: as it copies whole list each time and gives you so O(n^2)
<Ramzi181>
thelema: But my function returns []
<Ramzi181>
thelema: I could have had it return 5 if I so chose, right?
<thelema>
Ramzi181: which has type 'a list, not unit. If you want to avoid the warning, return ()
<qwr>
Ramzi181: and x = false is usually written as not x
<thelema>
the warning is so that you don't do things like "print_string; print_int 4; print_newline;
yangsx has joined #ocaml
<qwr>
Ramzi181: ah. unit comes actually from line 18
<thelema>
qwr: = false seems reasonable to me.
<thelema>
there is a problem on line 18 as well.
<qwr>
Ramzi181: first if unifies with ()
<Ramzi181>
i don't know what that means.
<thelema>
no, there's no problem other than because comingfrom's return type is 'a list, paths_helper also has return type []
<qwr>
Ramzi181: so the comingFrom result type gets unified also with unit
<qwr>
Ramzi181: but it really wants to be list
<thelema>
qwr: no, it is a list, and warnings get emitted when you try to use it in a ; context.
<qwr>
Ramzi181: as one of the paths_helper return values is comingFrom application
<thelema>
Ramzi181: change line 2 from [] to (), and this warning will go away
<qwr>
yes
<thelema>
maybe even error, as you're not allowed to have if foo then 5; (you have to have an else case if your then case returns a value (other than unit))
* qwr
just started to think, wtf that comingfrom needs to return [] ;)
<qwr>
and yes, if without else really has implicit else () ;)
psnively has quit []
<Ramzi181>
Thank you guys again so much.
<Ramzi181>
I'm going to take a break. I might be (probably am) done for tonight.
seafood_ has quit []
<alexyk>
if I have a list [1;2;3], what's the fastest way to assign the three members to a,b,c?
<alexyk>
I'll read millions of lines with three fields and split them with Str.split to get a list each time
<qwr>
let [a;b;c] = l
<alexyk>
so I want to avoid memory churn
<alexyk>
would using scanf instead of Str.split be more efficient?
<alexyk>
qwr: thx! I guess it's a short list so it won't be too inefficient over scanf
<qwr>
alexyk: although you may use match l with [] -> wtf; [a;b;c] -> ... to avoid partial-match warnings
<qwr>
damn. match l with [a;b;c] -> ... | _ -> wtf
<alexyk>
qwr: yep, cool
<alexyk>
qwr: but that screws up the code layout, everything gets stuck into ->, prolly better scanf then
AxleLonghorn has joined #ocaml
AxleLonghorn has quit [Client Quit]
AxleLonghorn has joined #ocaml
AxleLonghorn has quit [Client Quit]
evn_ has quit [Read error: 104 (Connection reset by peer)]
evn_ has joined #ocaml
<thelema>
alexyk: the minor heap collector is *very* efficient at collecting ephemeral objects -- don't worry about them.
seafood_ has joined #ocaml
<alexyk>
a bit more fp question -- I'm scanning lots of integers, and print them back N on a line. FP style is to pass the counter along as another argument, do modulo N and print if 0. Now I have 3 such parameters telling me when to print what. In python an easy global would do. What alternatives do we have in FP but tacking on accumulator arguments one after another?
<alexyk>
It also complicates branching as I have to repeat most of the arguments save for a few which change in each particular branch
<Smerdyakov>
You can probably use a higher-order function, where all these parameters will live in a closure passed to that function.
<Smerdyakov>
I'm not sure if that actually makes any sense, but it's hard to provide suggestions without a concrete problem you're trying to solve. :-)
<thelema>
it means that it'll throw away the return value of paths_helper on L23
<Ramzi181>
why?
<thelema>
because you're not telling it what to do with it, you're just saying do paths_helper, and then if m>1 do paths_helper again (and return that result)
<Ramzi181>
Notice here: http://codepad.org/FSFoLbnS If I take out the parens on line 28 it says wrong number of arguments
<Ramzi181>
I don't understand. paths_helper will return an int list. And the else will return an int list.
<thelema>
you're trying to apply sum to 5 arguments, when it only takes one.
<thelema>
you mean sum (paths_helper ...)
<Ramzi181>
yes, but paths_helper takes the 3 arguments. i think ocaml should be able to deduce that
<thelema>
If you think a little bit, you can create a case that's ambiguous.
<thelema>
(I think)
<Ramzi181>
can you overload functions?
<thelema>
in any case, ocaml works kinda like lisp - the first value is the function, the rest are arguments.
<thelema>
probably not in the way you're thinking - how would type inference work?
schme has quit [Remote closed the connection]
<Ramzi181>
well, if you can't overload, then I cannot think of an ambiguous case
<Ramzi181>
i'm not sure if that's important, now, though. i'm more concerned with understanding the nature of this warning.
<Ramzi181>
On what line am I returning type unit?
<thelema>
on line 23, you should return type unit so it can be safely ignored.
<qwr>
Ramzi181: you can't overload. but every function really has only 1 argument ocaml.
<Ramzi181>
lol. I thought we just agreed that the return type of a function has to be consistent. I'm returning an int list in other places. It would be inconsistent to return a unit.
<qwr>
Ramzi181: and the type system don't allow direct union types
<thelema>
Ramzi181: yup. so you need to do something with the returned value, and not just ignore it.
<qwr>
Ramzi181: and multiple arguments are really a curring magic
<thelema>
maybe you want to concatenate the two returned lists?
<Ramzi181>
i'm not ignoring it. it gets returned. i'm only returning 1 list.
coucou747 has quit ["bye ca veut dire tchao en anglais"]
<qwr>
Ramzi181: without parens, as you wrote it will parse as ((((sum paths_helper) m) n) [(m,n)])
<thelema>
qwr: thank you, but you're not helping.
<thelema>
Ramzi181: line 23 calls path_helper, right?
<Ramzi181>
agreed
<thelema>
and path_helper returns a list
<Ramzi181>
agreed
<thelema>
so what do you do with that list?
<Ramzi181>
return it
* qwr
is sleepy and tried to explain why ocaml requires parens there :)
<thelema>
no, you return the lst generated by path_helper on L24
yminsky_ has quit []
<thelema>
*list
<Ramzi181>
okay, so the list created by line 23 goes no where
<thelema>
yup. and that's what the compiler warns you about.
<thelema>
let's talk about count for a second.
<Ramzi181>
Line 20 doesn't ever get returned. Why isn't there a warning on that?
<Ramzi181>
That is, what's wrong with created a list that "goes to waste."
<thelema>
comingFrom returns unit
<qwr>
Ramzi181: unit can be wasted ;)
<Ramzi181>
hmm, so if I through in 5 somewhere in the code, that would get a warning also.
<Ramzi181>
unit can be wasted...
<thelema>
and if you want to ignore the result of something without a warning, do "ignore(code returning something)"
<qwr>
if n > 1 then ignore (paths_helper m (n-1) (path @ [(m,(n-1))]));
<thelema>
but I don't think that's what you want to do. lets talk about count.
<Ramzi181>
Okay.
<thelema>
you're trying to accumulate a 1 for each time m=1 and n=1?
<Ramzi181>
yes
<thelema>
you want to push a 1 onto count?
<Ramzi181>
yes
<thelema>
then you want let count = ref []
<thelema>
so it's mutable.
<Ramzi181>
is that a variable?
<thelema>
and then count := 1::!count
<Ramzi181>
I have instructions to not use variables.
<thelema>
it's changable like variables in other languages
<thelema>
ah, then you can't do that with count.
<Ramzi181>
yes. a mutable type makes a lot of sense here, really it does.
<Ramzi181>
but craziness should still compile anyway. :-P
<Ramzi181>
qwr: your use of ignore didn't quite work.
<thelema>
and then return the final list at the end.
<qwr>
but yes, both if's have 2 branches
<thelema>
quit it with the ignore, that won't get you where you want.
<Ramzi181>
thelema: i'm not opposed to discussing the logic or implementaion, but I'm interesting in learning why syntactically what i have is wrong.
<thelema>
you have to use the return value from paths_helper each time.
<thelema>
sorry, I'm pushing you towards what I now classify as "completing an assignment"
<Ramzi181>
between lines 23 and 24 there are 4 "branches," then. and the "branches" on line 23 can never be the return value, because line 24 will always get executed.
<qwr>
Ramzi181: thelema is right in that ignore probably gives incorrect end result for your intent. but you still cant hide else into parenthesis like you did there. it belongs to the if ;)
<Ramzi181>
I still have time. There is no imperative, yet.
<thelema>
the value of paths_helper comes from the top-level if statement.
Mr_Awesome has joined #ocaml
<qwr>
Ramzi181: you could just omit it wholly meaning the if has else ()
<thelema>
(if m=n&&n=1 ...)
<thelema>
err, s/statement/expression/
<thelema>
it either evaluates the 'then' branch or the 'else' branch.
<thelema>
to evaluate the else branch it has to evaluate another if statement
<Ramzi181>
you'll probably hate this, but.
<thelema>
(the if f m n = false) statement
<Ramzi181>
when I removed the else [], knowing full well there is an implicity else (), and just applied the ignore to the if, it worked.
<thelema>
yes, right now L23 returns unit.
thermoplyae has left #ocaml []
<qwr>
Ramzi181: ignore after the else? it's exactly what i suggested first ;)
<qwr>
damn. ignore after then
<thelema>
qwr: no, he has if n>1 then ignore (blah);
<qwr>
thelema: yes. that's what i meant.
<thelema>
if n>1 then ignore (blah else []); doesn't work because (blah else []) doesn't have meaning.
<Ramzi181>
so ignore can only be applied to one statement at a time?
<Ramzi181>
i mean, when i had else [], why couldn't I throw that in the ignore also?
<qwr>
Ramzi181: ignore can be applied only to value
<thelema>
one expression.
<Ramzi181>
what do you mean value?
<thelema>
and you can't just put "else []" in an arbitrary expression
<qwr>
Ramzi181: and else is nothing meaningful without if
<Ramzi181>
if x = true 2 else 2.0
<qwr>
Ramzi181: (if ... then ... else ...) is single syntactic construct, where the last else part is optional (defaulting to else ())
<thelema>
if x = true then 2 else 2.0 ?? can't do -- has to return a single type
<Ramzi181>
let's say my return type of a function was a list, or something.
<Ramzi181>
so i want to ignore the whole thing
<thelema>
s/return/evaluate to/
<Ramzi181>
can't i do ignore(if x = true 2 else 2.0)
<thelema>
no, the inside doesn't typecheck. 2 isn't the same type as 2.0
<thelema>
treat ignore as a function (fun x -> ())
<Ramzi181>
i don't think the else [] is arbitrary. i didn't have it there before, but i wanted uniformity in returning a list always. but then i went and learned that I get warnings for wasted values. that is, the only thing you can waste is a unit.
<qwr>
Ramzi181: both branches must have same type
<Ramzi181>
okay, I had if "a list" else []. why was ignore(if "a list" else []) bad?
<thelema>
L23 isn't involved in returning a value in paths_helper (because of the ; at its end)
<qwr>
Ramzi181: because if-then-else as expression as single type
<thelema>
Ramzi181: if true then [2;3;4] else [] -- this is ok.
<qwr>
Ramzi181: ignore (if condition then list1 else []) is ok
<qwr>
Ramzi181: its just more code than if condition then ignore list
<Ramzi181>
I had ignore(if condition then list1 else [])
<Ramzi181>
and it didn't work
<thelema>
Ramzi181: I saw: if condition then ignore(list1 else [])
<Ramzi181>
oh.....
<qwr>
... where the thing in parens is just not a valid expression (it won't parse)
<Ramzi181>
the return type isn't list1, the return comes from the if.
<Ramzi181>
wait, wahh. then why does if condition then ignore(list1) work?
<Ramzi181>
oh, let me explain
<qwr>
Ramzi181: because it's short for if condition then ignore(list1) else ()
<Ramzi181>
ignore(list1) turns that into a unit, so the if returns a unit. but if the else was inside of the ignore, then the else would return a unit and... shouldn't the if return a unit also?
<qwr>
it will
<Ramzi181>
if n > 1 then ignore (paths_helper m (n-1) (path @ [(m,(n-1))]) else []);
<Ramzi181>
what does the if return?
<Ramzi181>
or, in our new shorthand..
<qwr>
type error ;)
<thelema>
Ramzi181: type error - the first branch (), the second []
<Ramzi181>
if condition then ignore (list 1 else [])
<Ramzi181>
how does the second branch return []? it's in the ignore
<thelema>
oops, no, can't do that. syntax error
goalieca has joined #ocaml
<thelema>
(sorry, there's lots of parens, we thought the ignore ended before the else.
<Ramzi181>
okay
<Ramzi181>
so where does the syntax error come from?
<thelema>
the bit inside the ignore: foo else []
<qwr>
Ramzi181: what should (list 1 else []) mean as a standalone expression?
<Ramzi181>
doesn't that mean, "turn foo into a unit, and then turn else [] into a unit"
<qwr>
what else?
<thelema>
nope.
<Ramzi181>
hmm
<Ramzi181>
i see your point, qwr. the else is meaningless without the if.
<Ramzi181>
so you can only pass whole statements into ignore
<qwr>
yes
<thelema>
expressions
<Ramzi181>
lol
<Ramzi181>
so you can only pass whole expressions into ignore
<Ramzi181>
and i was passing this incomplete expression.
<qwr>
Ramzi181: ignore is just a function
<qwr>
# ignore;;
<qwr>
- : 'a -> unit = <fun>
<thelema>
qwr: actually it's builtin magic, but it's nearly identical to (fun _ -> ())
<Ramzi181>
I think I understand it now. And there are many ways I could have done it.
<thelema>
the compiler optimizes it specially.
<qwr>
thelema: imho the magic can be considered to be optimisation ;)
<Ramzi181>
I could have put the entire expression in the ignore, or I could just put list1 in the ignore, and let the implicit else return a unit
<thelema>
Ramzi181: exactly.
<Ramzi181>
I really like you guys as teachers.
<thelema>
you don't always get teaching on #ocaml - sometimes you get Smerdyakov.
<mbishop>
heh
<Ramzi181>
the atmosphere in here is much better than other rooms, I think.
<thelema>
(Not that he's bad - he knows tons more about code correctness than I, he just doesn't teach much.)
<Ramzi181>
My experience in C and Ruby rooms is, you have to know so many little details, and no one will explain nuances without telling you to switch majors.
<thelema>
there's advantages to a quieter room
<Ramzi181>
I think it's the nature of the language.
<thelema>
OCaml - the programming language for teachers?
Traveler has joined #ocaml
Traveler is now known as Ramzi
<Ramzi>
Was I kicked or disconnected?
<qwr>
neither
<Ramzi>
oh look, I'm still in.
Ramzi181 has quit [brown.freenode.net irc.freenode.net]
ertai has quit [brown.freenode.net irc.freenode.net]
<Ramzi>
I'm sorry, did anyone reply to my generalizations?
<thelema>
OCaml - the programming language for teachers?
ertai has joined #ocaml
Ramzi181 has joined #ocaml
<Ramzi>
haha what's going on.
<dobblego>
netsplit
<Ramzi>
thelema: yes, I think people who use OCaml have been in the classroom for longer...
ertai_ has joined #ocaml
ertai has quit [Read error: 104 (Connection reset by peer)]
<Ramzi>
that's my impression anyway.
* thelema
learned OCaml outside the classroom.
<Ramzi>
did you do post grad?
* qwr
certainly isn't. but i'm just interested in functional programming
* thelema
just has Bachelor's degree
<Ramzi>
hmm, maybe it's the nature of functional programming that attracts a certain kind of croud, then.
<Ramzi>
since i entered college I've heard CS majors complaining about OCaml.
<Ramzi>
But I'm having a very positive experience with it.
<Ramzi>
Some of my functions work correctly on the first run. That happens so rarely in other languages.
<thelema>
Ramzi181: strong typing does that - if you ever program in Ada, similar things happen - once it compiles, it probably works.
<thelema>
I think it's more so in OCaml because it has better types
<Ramzi>
i'm not familiar with Ada, so I won't comment.
<palomer>
and errors are easy to catch!
<Ramzi>
but i clearly prefer strong type to loose type.
<palomer>
(they rarely stump me for more than 10 minutes)
<thelema>
and the earlier one catches errors, the less one pays for them.
Ramzi181 has quit [brown.freenode.net irc.freenode.net]
<Ramzi>
thelema: it appears that my function is returning 0. do you think my sum function is wrong, or am I not adding ones to count correctly?
<Ramzi>
it's funny to see myself keep quitting irc
<thelema>
Ramzi: you're not adding ones.
<palomer>
I met a ruby programmer the other day, he told me he does 4 levels of unit testing
Ramzi181 has joined #ocaml
<Ramzi>
i mean, pushing ones
<palomer>
he actually told the whole party, but I'm the only one who understood
<Ramzi>
hahaha
<thelema>
you're not pushing ones correctly.
* qwr
has lovely memories about C daemons with slightly misdirected pointers... that was something to debug for hours ;)
<thelema>
the else [] resets the count of ones you've accumulated.
<thelema>
why accumulate a list, only to sum it? why not just accumulate the sum? (count + 1)
<Ramzi>
i don't understand. what gets set to count+1?
<Ramzi>
i just realized I must have said "I don't understand" like 400 times in this chat.
<thelema>
your goal is to count the paths, no?
<Ramzi>
yes.
<thelema>
so why do you make a huge list, and then count how many elements are in it?
<Ramzi>
because i can't use variables.
<thelema>
why not count +1 each time you would add a list element?
<Ramzi>
and store it where?
<thelema>
same place your partial sums get stored in sum
<qwr>
looking at the current code... why is this count = [] constant useful?
<Ramzi>
hmm, so I would have to add a parameter
__suri_ has quit []
<Ramzi>
no, i'm not seeing it
<Ramzi>
i only want to increment the part sum in the top if
<Ramzi>
that is, when m and n = 1
<Ramzi>
i can't keep a partial sum as a parameter, because i never pass that around afterward
<thelema>
you'll need to pass it around.
* palomer
remembers the good old days of getting brainfudged by this stuff
<thelema>
qwr: it's not -- beginner code
<Ramzi>
does the function need to be completely rewritten?
<thelema>
palomer: it's quite an experience going through this. I remember hitting the ocaml manual over and over to pick out pearls of wisdom from it.
<thelema>
Ramzi181: not completely.
<palomer>
it's like a completely different way of thinking, and you can never go back!
<thelema>
palomer: you can go back - you're just adding another tool onto your toolbelt.
<palomer>
haskell programming is similar, they just combine combinators ad absurdum
<palomer>
every time I go back I'm like "where are my datatypes???!"
<thelema>
haskell and absurdum seem to go together well.
<thelema>
as far as I can tell.
<Ramzi>
is the highest number of elements in a list i can ever return is 1?
<flux>
I liked it. also the tehcnique how a large comic was brought to web was nice..
evn_ has quit [Read error: 104 (Connection reset by peer)]
evn_ has joined #ocaml
bla has quit [Read error: 110 (Connection timed out)]
bla has joined #ocaml
kopophex has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
evn_ has quit []
pango_ has quit [Remote closed the connection]
bluestorm has joined #ocaml
pango_ has joined #ocaml
thelema has quit [Read error: 110 (Connection timed out)]
^authentic has joined #ocaml
evn has joined #ocaml
authentic has quit [Read error: 110 (Connection timed out)]
^authentic is now known as authentic
evn has left #ocaml []
munga has joined #ocaml
sporkmonger has quit []
munga has quit [Client Quit]
Linktim has joined #ocaml
Yoric[DT] has joined #ocaml
Linktim_ has joined #ocaml
kopophex has quit [Remote closed the connection]
Linktim has quit [Read error: 110 (Connection timed out)]
Linktim_ has quit [Read error: 110 (Connection timed out)]
thelema has joined #ocaml
bongy has joined #ocaml
Linktim has joined #ocaml
Linktim has quit [Remote closed the connection]
ita has joined #ocaml
jlouis has joined #ocaml
delamarche has joined #ocaml
OChameau has quit ["Leaving"]
olleolleolle has joined #ocaml
evn has joined #ocaml
<thelema>
POLL: how fundamental is the concept of a string slice? Would you like a string library that does efficient slicing, but all operations are performed on slices?
<Yoric[DT]>
What do you mean "all operations are performed on slices" ?
<thelema>
for example, to get the index of a character, you need to give that function a slice
<thelema>
(of course there'd be a simple function to convert a string to a substring)
<thelema>
(substring = slice)
Snark has joined #ocaml
<thelema>
This is in the context of immutable strings
<RobertFischer>
thelema: Not very fundamental to me. If I was doing some kind of flat file parsing or something (basically, trying to make Ocaml do Perl's job), the story would be different.
<thelema>
RobertFischer: should/could ocaml start encroaching on that part of the problem space?
<RobertFischer>
The biggest part being a kind syntax around regular expressions.
Demitar has joined #ocaml
* thelema
is tackling the Unicode part of the problem
<RobertFischer>
And I'm not sure concepts like the global "$1", "$2", etc. variables are really ideas Ocaml should be picking up...but they're exactly what make Perl such a category killer language.
<thelema>
(right now)
<thelema>
RobertFischer: I think ocaml can do well with returning a tuple of matched substrings
<thelema>
(when I program in perl, I try to avoid $1,$2 and use ($var1,var2...) = $str ~= /regex(part1)line-noise(part2)/
<Yoric[DT]>
Have you looked at Martin Jambon's micmatch ?
<Yoric[DT]>
It allows pattern-matching with regular-expressions, which is basically what we want.
<Yoric[DT]>
Except we should extend that to streams.
* thelema
is wary of any non-trivial camlp4
<RobertFischer>
You can't return a tuple, because you don't know how many there will be.
<RobertFischer>
You could return a list, but that's kinda noisy to decompose.
<thelema>
well, I wouldn't want to implement perl5's regexes, perl6's rule/grammar constructs seem more useful
* RobertFischer
is a recovering Perlhead (CHIA@CPAN, to be exact), and so has a lot of rants in this area, mostly cached on his blog.
* thelema
made the (odd) transition from perl to ocaml, and still finds use for perl from time to time
alexyk has joined #ocaml
<RobertFischer>
For quasiportable sysadmin stuff and string munging, it can't be beat. :)
<RobertFischer>
I'd be interested to see what you come up with, though, if you decide to take it on.
<thelema>
one thing at a time. Unicode is a nasty beast
<RobertFischer>
Yeah, it is
<RobertFischer>
Have fun with that.
olleolleolle has quit []
kelaouchi has joined #ocaml
palomer has quit [Read error: 110 (Connection timed out)]
authentic has quit [Read error: 110 (Connection timed out)]
^authentic is now known as authentic
ita has quit [Remote closed the connection]
psnively has joined #ocaml
alexyk has quit []
ikaros has quit ["segfault"]
bongy has quit ["Leaving"]
gene9 has joined #ocaml
RobertFischer has left #ocaml []
gene9 has quit [Client Quit]
Axioplase has joined #ocaml
alexyk has joined #ocaml
alexyk has quit [Client Quit]
Axioplase has quit [Client Quit]
alexyk has joined #ocaml
|Catch22| has joined #ocaml
ikaros has joined #ocaml
Axioplase has joined #ocaml
alexyk has quit [Read error: 110 (Connection timed out)]
ttamttam has joined #ocaml
ita has joined #ocaml
ygrek has quit [Remote closed the connection]
Ramzi has joined #ocaml
ygrek has joined #ocaml
ttamttam has left #ocaml []
<thelema>
okay, I'm a beginner at large projects - I want to put some source files in my project into a subdir, I try to use -I to include that dir, but I still get Unbound value on values inside a file in that dir
mwc has joined #ocaml
ygrek has quit [Remote closed the connection]
coucou747 has quit ["bye ca veut dire tchao en anglais"]
psnively has quit []
Snark has quit ["Ex-Chat"]
coucou747 has joined #ocaml
psnively has joined #ocaml
delamarche has quit []
middayc has joined #ocaml
<ertai_>
use ocamlbuild (ocamlbuild -I subdir1 -I subdir2 my_main.byte)
Morphous_ has quit [Read error: 110 (Connection timed out)]
Morphous_ has joined #ocaml
<thelema>
I'm not able to change the build system of this project - it's pretty standard makefiles
<psnively>
OCamlMakefile?
<thelema>
psnively: no, Makefile.
<psnively>
I meant, could you benefit from OCamlMakefile?
<psnively>
Perhaps by inclusion into your Makefile?
<thelema>
no, as I said, it's a large project with its own custom, complex build system. I'm messing with one part of it and want to put some code in a subdir.
<thelema>
but still use that code in my changes to the project.
<thelema>
maybe I could read an OCamlMakefile and see how they handle subdirs, but I imagine there's an easy answer that I'm just missing.
<psnively>
OK. Good luck!
<ita>
makefiles for a large project is a sign of fail
<psnively>
== Try not to get saddled with make.
<thelema>
heh. There's some progress in converting parts of this project to ocamlbuild, but I think this part will be stuck with make.
ikaros has quit ["segfault"]
marmottine has quit ["Quitte"]
bluestorm has quit ["Konversation terminated!"]
<Ramzi>
I'm getting a char from a function called get_char which reads the next one from stdin.
<Ramzi>
But I want to analyze it and do stuff with it.
<Ramzi>
If I always just put get_char it'll return a different char. But if I save it, then I'm using a variable.
|Catch22| has quit [Read error: 104 (Connection reset by peer)]
<Ramzi>
hmm, maybe i should read all of stdin into a string, and that way i can functionally refer to a letter by its unchanging position in the string.
<Smerdyakov>
Ramzi, what's wrong with variables?
<Ramzi>
The lesson is to learn functional programming by avoiding the use of imperative style.
<Smerdyakov>
OCaml variables have nothing imperative about them.