<dark>
type t = ('a. 'a list) -> int isn't possible too o.O
<lewis1711>
bit of a noob here; let rec factorial n =
<lewis1711>
if n < 2 then n else n*factorial n-1;;
<lewis1711>
"Stack overflow during evaluation (looping recursion?)." not quite sure what is meant by looping recursion. they don't make much sense together
iago has quit [Quit: Leaving]
<tautologico>
looping recursion means that you're using a recursive function as a loop
<tautologico>
stack overflow because your program is using all the memory space available for the stack
<tautologico>
and that happens because n * factorial n-1 is actually parsed as n*(factorial n)-1
<tautologico>
so this function keeps calling itself with the same argument and never terminates... eventually the stack is exhausted
<lewis1711>
AHHH
<lewis1711>
let rec factorial n =
<lewis1711>
if n < 2 then n else n * (factorial (n-1));;
<lewis1711>
thanks tautologico:)
<tautologico>
np :)
philtor has joined #ocaml
Amorphous has quit [Ping timeout: 255 seconds]
joewilliams is now known as joewilliams_away
<gnuvince>
Is it possible to split a sig and struct into .mli and .ml files? I'm toying with phantom types, and when I have a single .ml file with module Foo : sig (* something *) end = struct (* something *) end, the compiler properly whines when my types don't match.
<gnuvince>
But if I do split them into two separate files, the compiler compiles happily and the code doesn't do what it's supposed to.
Amorphous has joined #ocaml
<tautologico>
separating sig/struct into mli/ml is quite standard
<tautologico>
maybe the types you're exposing in the sig don't enforce the constraints you want?
<tautologico>
because I named the file safe.ml, the module ended as Safe.SafeString and so you have it, the compiler error you wanted :)
<gnuvince>
ok
<gnuvince>
thanks
<tautologico>
np
tautologico has quit [Quit: tautologico]
<lewis1711>
if ocaml allows explicit type conversion but not implicit, then why is there a print for every data type? wouldn't it make more sense to have a print that converted all its arguments to strings?:/
ccasin has quit [Quit: Leaving]
joewilliams is now known as joewilliams_away
<thelema>
lewis1711: print can't implicitly convert its arguments to strings
<thelema>
so you have to either explicitly stringify your arguments and use string print or you can print with a more specific printer
philtor has joined #ocaml
xcthulhu has quit [Ping timeout: 250 seconds]
seafood has joined #ocaml
lewis1711 has quit [Quit: Leaving.]
lewis1711 has joined #ocaml
mjonsson has quit [Quit: Leaving]
lewis1711 has left #ocaml []
seafood has quit [Quit: seafood]
<flux>
dark, correct, it's not possible. but you can always use a record for the same purpose.
<flux>
dark, so: type t' = { x : 'a.'a list } and t = t' -> int
<flux>
dark, however, you cannot populate t' so it's pretty useless..
<flux>
dark, best to put the function directly inside the record
<flux>
dark, so: type t = { x : 'a. 'a list -> int }
philtor has quit [Ping timeout: 240 seconds]
DimitryKakadu has joined #ocaml
dark has quit [Ping timeout: 245 seconds]
dark has joined #ocaml
ygrek has joined #ocaml
ski has quit [Read error: Connection reset by peer]
ski has joined #ocaml
ulfdoz has joined #ocaml
init1 has joined #ocaml
kerneis has joined #ocaml
DimitryKakadu has quit [Ping timeout: 255 seconds]
hcarty has quit [Read error: Operation timed out]
Yoric has joined #ocaml
hcarty has joined #ocaml
<flux>
hmph.. am I supposed to use nl_params instead of hidden fields?
<flux>
[in ocsigen]
<flux>
I guess best read more documentation :)
ztfw has joined #ocaml
ygrek has quit [Ping timeout: 245 seconds]
boscop_ has joined #ocaml
boscop has quit [Ping timeout: 264 seconds]
ikaros has joined #ocaml
ygrek has joined #ocaml
iago has joined #ocaml
Tobu has quit [Ping timeout: 276 seconds]
Tobu has joined #ocaml
<dark>
flux, does this limitation makes sense? (also, this kind of limitation tells me this must be relatively recent.. it is not, say, inherited from caml)
ygrek has quit [Ping timeout: 245 seconds]
ikaros has quit [Quit: Leave the magic to Houdini]
ygrek has joined #ocaml
<ulfdoz>
top
pikachuyann has joined #ocaml
ikaros has joined #ocaml
asmanur_ has joined #ocaml
asmanur has quit [Read error: Operation timed out]
dark has quit [Ping timeout: 265 seconds]
dark has joined #ocaml
hcarty has quit [Read error: Operation timed out]
iago has quit [Quit: Leaving]
dark has quit [Ping timeout: 255 seconds]
hcarty has joined #ocaml
<adrien>
bottom
dark has joined #ocaml
pikachuyann has quit [Ping timeout: 240 seconds]
pikachuyann has joined #ocaml
Snark has joined #ocaml
ikaros has quit [Quit: Leave the magic to Houdini]
ikaros has joined #ocaml
ikaros has quit [Quit: Leave the magic to Houdini]
pikachuyann has quit [Read error: Connection reset by peer]
ccasin has joined #ocaml
oriba has joined #ocaml
ccasin has quit [Quit: Leaving]
DimitryKakadu has joined #ocaml
xcthulhu has joined #ocaml
kaustuv has joined #ocaml
ztfw has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
joewilliams_away is now known as joewilliams
<gildor>
anyone knows a good template system for ocaml
<adrien>
it has a nasty bug/limitation which prevents you from using "file" in your code however (this looks live a left-over from past versions)
philtor has joined #ocaml
init1 has quit [Quit: Quitte]
ulfdoz has quit [Quit: deprecated]
<flux>
dark, well, I guess it makes sense in that the forall quantification is limited to records instead of all constructs, possibly leading into higher maintenance costs
ztfw has joined #ocaml
<flux>
(hmh, I mean that if everything supported it, it would be code in lots of places)
<flux>
dark, recently ocaml gained the capability to have the forall quantifier in function definitiopns as well
<dark>
I can't make a function with forall..
ftrvxmtrx has quit [Quit: Leaving]
<thelema>
the forall quantification is only supported where types can be explicitly defined (and it matters)
<thelema>
hmm, except for variants...
ftrvxmtrx has joined #ocaml
nejimban has quit [Ping timeout: 250 seconds]
nejimban has joined #ocaml
dcolish has quit [Quit: Coyote finally caught me]
dcolish has joined #ocaml
ulfdoz has joined #ocaml
mjonsson has joined #ocaml
<flux>
dark, I was under the impresion ocaml 3.12 supported this: let a : 'a.'a -> 'a = fun a -> a or something..
<dark>
and it actually supports. o.o'
<dark>
but this is a parse error: let a (x : 'a. 'a) = x;;
<dark>
not a type error, but a parse error
<dark>
Error: Parse error: [fun_binding] expected after [ipatt] (in [let_binding]), with a underlined
<flux>
again, you are annotating a value, not a function..
kaustuv has quit [Quit: Page closed]
metasyntax has joined #ocaml
Snark has quit [Quit: Ex-Chat]
<dark>
ok, trying again:
<dark>
# let (a : 'a. 'a -> 'a) x = x;;
<dark>
Error: Parse error: ident_of_ctyp: this type is not an identifier
<dark>
but:
<dark>
# let (a : int -> int) x = x;;
<dark>
value a : int -> int = <fun>
<dark>
so to use this feature, one has to give up the sugar?
<flux>
let a : 'a.'a -> 'a = fun x -> x
<dark>
= fun x -> x is somewhat inconvenient
<flux>
I've found it convenient in the form that it's much easier to copy/paste to mli-file ;)
Smerdyakov has quit [Quit: Leaving]
<xl0>
Guys, what's your opinion on ATS?
<flux>
xl0, it's very cool, but it's even more verbose/annotation-heavy than c
<dark>
ats?
<flux>
a high-performance functional programming language
<flux>
hmph, would I be wrong in my perception that ocaml-orm-sqlite isn't quite usable yet?
<orbitz>
ats is really cool I just wish the uathor would A) Make imperative programming less ugly in it B) Slim the language down a bit
<dark>
it has some foreign concepts..
<flux>
I guess I'll switch to pg'ocaml for now. Too bad, an almost-functional special-purpose inventory-app for me was only 100 lines or so ;).
DimitryKakadu has quit [Ping timeout: 240 seconds]
<dark>
my plan with pg'ocaml was a bit like: i will write an prototype on it, then switch to hdbc (or other haskell library). but it is working well.. (modulo this thing of not having $var.field)
<dark>
it should have $(expression) as well..
<flux>
I'm mostly missing building queries out of fragments
<dark>
(I was trying to write in haskell, but I have a poor undestanding of haskell basics....)
<flux>
I think it should be possible with a macro system
<flux>
(so the actual query would still be available at compile time)
<dark>
I am writting some backend in ocaml and a frontend in ruby, with sinatra and sequel. sequel is really more mature, but.. also less reliable. and the "safe" api for building fragments is just weird (like something(...).group_by(..), and what I'm actually learning is sql, so I want to actually write sql..)
<dark>
isn't macaque supposed to give composability on top of pg'ocaml?
<dark>
at price of giving up the prepared statement stuff
<flux>
well, it's still IMO a bit more effort to write queries the macaque way if you already know sql..
<dark>
I think what I actually miss is a printf-like hack.. like PGSQL(db) "insert into a values (%s)" c
<flux>
actually it could work even more nicely, you could use ?1 ?2 etc
<flux>
because the types are inferred from sql
<flux>
basically PGSQL(db) "insert into a values (?1, ?2, ?1 + ?2)" would return a two-parameter function
<dark>
hmm.. then you are supposing one can write some arbitrary expression there
<flux>
where?
<dark>
at the fields of (?1, ?2, ?1 + ?2)
<flux>
well, you can in the sql
<dark>
ah, this + is actually an sql +
<flux>
yes
<dark>
I thought about printf because one could reuse the sprintf machinery
<flux>
no pg'ocaml releases this year :(
<flux>
iirc it could use some support for handling sequences more easily..
<flux>
but I'm off to sleep
<dark>
in general haskell community seems more alive u.u
<dark>
bye
hcarty has quit [Ping timeout: 240 seconds]
monra has joined #ocaml
<monra>
Hello. I have the following problem. In a file, let's say "foo.ml" I have this declaration "exception Type_error", in another file I do "open Foo" and then try to catch Type_error exception but I got the following message: Error: Unbound constructor Type_error
<monra>
Any ideas on how to fix this ?
<flux>
compile foo.ml before anotherfile.ml
<flux>
hm, actually, open Foo shouldn't work then either
<flux>
testcase?
<flux>
(I didn't actually go to sleep just yet, but rather linger around 8-))
<monra>
flux: hmm... I found it ... I hadn't declared the exception in the mli file :S
<flux>
monra, well, it sure helped to ask it on irc anyway?-)
<orbitz>
I have a namespace of Foo and I want things like Foo.Bar, is the common style for this to have foo_bar.ml and foo.ml and do mudule Bar = Foo_bar?
hcarty has joined #ocaml
<monra>
flux: Well... I was looking for it 15 minutes before asking(and it seemed "easy" to fix). Anyway. Thank you for your time :)
<dark>
module Bar = Foo.Bar
<dark>
I would like to have haskell's qualified imports. :(
<dark>
like module U = ExtUnix.Specifics
<dark>
then U.realpath "."
<dark>
Specific actually
monra has quit [Quit: leaving]
ikaros has joined #ocaml
ztfw has quit [Remote host closed the connection]
pikachuyann has joined #ocaml
<orbitz>
dark: you can do just that...
<ulfdoz>
Aber gab es nichtmal lisp-maschinen?
<ulfdoz>
ewin, sry.
<dark>
just that = ?
<dark>
like open ExtUnix.Specifics (realpath)
<dark>
or open ExtUnix.Specific hiding (a, b)
jonafan_ has joined #ocaml
jonafan has quit [Ping timeout: 276 seconds]
<orbitz>
let realpath = ExtUnix.Specifics.realpath
<orbitz>
more verbose clearly
<orbitz>
could probably make a camlp4 to do it
<pikachuyann>
bonne nuit / good night
<julm>
bonne nuit pikachuyann (ter)
<pikachuyann>
:p
pikachuyann has quit [Quit: nenuit]
ygrek has quit [Ping timeout: 245 seconds]
ulfdoz has quit [Read error: Operation timed out]
Yoric has quit [Quit: Yoric]
Fullma has quit [Ping timeout: 252 seconds]
ikaros has quit [Quit: Leave the magic to Houdini]
Edward_ has joined #ocaml
<dark>
orbitz, yeah. but I don't see an idiom for writing something like "hiding"
<orbitz>
dark: same, I'm not convinced it's a particularly useful feature though
<orbitz>
Hrm, omake doesn't seem to build with 3.12