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
caligula_ has quit [Connection timed out]
jeddhaberstro has joined #ocaml
<mrvn> I sometimes do refine functions like let make x y = make 1 x y
<mrvn> If let where always recursive then you would have to use a temporary name to get around it.
<mrvn> Any idea how to unify the if and else paths in this? http://paste.debian.net/32919/
<mrvn> nm.
rhar has quit [Read error: 60 (Operation timed out)]
ched_ has joined #ocaml
Ched has quit [Read error: 101 (Network is unreachable)]
<thelema> mrvn: that seems really straightforward to unify in ocaml - there's only two tokens that differ between the two branches, create the function that takes those as arguments and ...
<mrvn> thelema: yeah, already done.
rhar has joined #ocaml
rhar has quit ["Leaving"]
hsuh has joined #ocaml
seafood has joined #ocaml
hkBst has quit [Read error: 104 (Connection reset by peer)]
jeddhaberstro has quit []
<grirgz> mrvn: rec is not just to optimise the compiler ?
<mrvn> ifat all I would think it makes things worse.
<grirgz> why N?
<grirgz> s/N//
<hsuh> grirgz: if you don't add rec, when you make the recursive call the function will be unknown... is that what you're asking ?
seafood has quit []
seafood has joined #ocaml
<grirgz> hsuh: i know, but why add such keyword ? why not make all functions recursive ?
<hsuh> oh, i see your point now :)
<mrvn> because you often have things like let foo = foo x in
<kaustuv_> Unintended recursion is hard to debug, so it's better to make the programmer be explicit about it.
<grirgz> kaustuv_: it's the only reason ?
<mrvn> probably simplifies the compiler and type inference too
<mrvn> and I really want to be using let foo = foo x in constructs.
AxleLonghorn has joined #ocaml
<kaustuv_> grirgz: I agree with mrvn
<grirgz> mrvn: i have some moral code which forbid me to use similar or same name for differents things
<grirgz> maybe it comes from imperative languages
<kaustuv_> you'd rather use different names for the same thing?
<grirgz> :p
<grirgz> each identifier should be unique, unless it point to the same thing
<kaustuv_> ah, so you are a devotee of static single assignment at the source level
seafood has quit []
<mrvn> grirgz: When I have a function that takes multiple arguments of which the first is fixed during a recursion I usualy apply it outside the recursion and use the same name, as in let into_buffer = into_buffer buffer in List.iter list into_buffer
<mrvn> Or when I convert from one type to another let x = 17 in let x = Int64.of_int x in ...
<mrvn> It is still the same thing so I use the same name.
<grirgz> it seem correct =)
<grirgz> i will do that now
kaustuv_ has left #ocaml []
<mrvn> or let (foo, pos) = parse_foo s pos in let (bar, pos) = parse_bar s pos in let (baz, pos) = parse_baz s pos in ...
<mrvn> On that note, does Batteries have a Buffer module that allows removing stuff from the front?
<thelema> mrvn: you want to remove from the front of a Buffer? like a FIFO queue for text?
<mrvn> like a stream
<mrvn> read in 64k of data and use it up bit by bit.
<grirgz> i think buffers is meant to be used with an index
<grirgz> s/is/are
<mrvn> But often you could use a FIFO.
<thelema> mrvn: the right way to do this is with a string and an index, using the string as a circular buffer...
<mrvn> thelema: sure. that is what I want the buffer module to do. :)
<thelema> Batteries doesn't provide this at the moment, and you'd have to think of a new name, as "Buffer" is already taken
orbitz has left #ocaml []
hsuh has quit [Read error: 110 (Connection timed out)]
<det> How can I allocate/return an int32 from C code ?
jeff__ has joined #ocaml
Camarade_Tux has quit [Read error: 110 (Connection timed out)]
Camarade_Tux has joined #ocaml
wsmith84 has joined #ocaml
AxleLonghorn has quit [Read error: 110 (Connection timed out)]
<sOpen> mrvn, I don't understand "let into_buffer = into_buffer buffer in List.iter list into_buffer". Why not "List.iter list (into_buffer buffer)"? It seems shorter and less confusing.
<mrvn> sOpen: Assume the "into_buffer buffer" is used many times in the following function
<mrvn> det: # caml_copy_int32(i), copy_int64(i) and caml_copy_nativeint(i) return a value of Caml type int32, int64 and nativeint, respectively, initialized with the integer i.
<sOpen> mrvn, doh! i see.
<det> mrvn, thanks, I decided to just use a length 4 string, works for my purposes.
<mrvn> In the general case "into_buffer buffer" could also do some computations in preparation for the remaining args. By applying it once outside the recursion that calculation is done only once.
<sOpen> mrvn, yes... i wasn't thinking big enough for the let-block and i got confused. for big stuff and loop hoisting it's nice
<mrvn> det: Verry bad style. Do you actually need an int32? Aren't 31 bits enough?
<det> I need 32 bits
wsmith84 has quit [Read error: 60 (Operation timed out)]
<det> I am returning crc32 from C :-)
<det> and in the end I just convert it to hex for output, I have hex routine in Ocaml
<mrvn> det: why bother? Use a proper checksum like sha1
<sOpen> mrvn, although, if the expression were referentially transparent and pure...
<det> I have to use crc32 for this
<det> inter-operating with another piece of software
<mrvn> det: maybe keep thetype abstract and provide an "to_hex" that returns a string of length 8?
<det> I already have hex routine in Ocaml, and I am also using md5 that returns a 16 byte digest, so it is also nice to keep the same interface
<det> same interface for crc32 and md5, that is
<det> even if 1 will technically fit into a word
<mrvn> det: Same as Digest?
<det> I dont use Digest module the interface is really terrible
<det> To use digest module, I either need to keep my input all in memory at the same time or write it to a file first
<det> my md5 is just create/update/final
<det> I just wrapped md5 from APR (Apache Portable Runtime) since I am using it in this code anyways.
<mrvn> I know the problem. There is also no of_hex : string -> t and no to_binary/of_binary.
<det> problem with Digest is there is no updating
<det> hex isnt a problem, I have my own hex routines
<det> You can get the digest of a string, you can get the digest of a file, but you cant incrementally update the digest.
<det> let md5 = Md5.create();md5.update("Hello\n");md5.update("There!");let digest = md5.final(md5)
<det> is the same thing as
<det> let digest = Digest.string "Hello\nThere!"
<det> But in my program I can't have the whole file in memory at once because of Ocaml string limit size on 32 bit. It would be bad style to anyways.
<det> My only solution would be to create a temporary file and write the whole file to that and use Digest.file
<det> But that is a really awful solution
pierre_m has joined #ocaml
<det> let md5 = Md5.create(); Md5.update "Hello\n"; Md5.update"There!"; let digest = Md5.final md5
<det> I mean that, I was just doing C and my head was warped :-)
AxleLonghorn has joined #ocaml
cads has joined #ocaml
seafood has joined #ocaml
<mrvn> 2500 lines of code and all it does so far is say "Hello World."
<mrvn> Building a project bottom up is hard.
m3ga has quit ["disappearing into the sunset"]
<sOpen> mrvn, 2500 lines of ocaml? what does this project do?
<mrvn> sOpen: A filesystem using FUSE
<sOpen> cool
<sOpen> features?
<mrvn> Written in userspace and a type safe, functional language. DOH. :)
th5 has joined #ocaml
<mrvn> Verry simple design using a single BTree to organize all metadata.
th5 has quit [Client Quit]
<mrvn> Raid 0/1/5/6/... striping support on a per file basis and one setting for all metadata.
<mrvn> All operations are Copy-On-Write with atomic commits of the BTree root to enact any change. The filesystem is always in a consistent state so no fsck and no journal replay needed.
<mrvn> Online defrag that also does grabage collection to free blocks that are no longer used.
<sOpen> mrvn, nice... is it going into production?
<mrvn> So far it only manages to say "Hello World." :)
<flux> mrvn, does it have an interface one could use without using FUSE?
<flux> (or s/does/will/)
<flux> for example implementing other filesystems above that kind of (very complete) layer
<mrvn> flux: like some shell like thing where you could cat/cp/rm/ln/touch/...?
<flux> mrvn, I was thinking more like a library you could link in
<mrvn> The thing is a full filesystem so there isn't really a layer.
<flux> so everything is integrated with the FUSE component?
<flux> instead of FUSE just using a set of well-defined services?
<mrvn> One part is the BTree, the other part is libfuse and between them there is code that translates the fuse callbacks into function calls of the btree.
<mrvn> So the read callback does BTree.find root (Key.File.key inode offset) and gives the result back to fuse.
<flux> how about things like metadata, moving files?
verte_ has joined #ocaml
<mrvn> flux: The Btree has an entry ((Key.Dir.key parent hash), (inode, name)) for files. So a rename would add a new entry with the new parent/hash and then remove the old one.
verte has quit [Nick collision from services.]
verte_ is now known as verte
<mrvn> flux: A touch alters the ((Key.Inode.key inode), Fuse.stats) infos. and so on.
<flux> mrvn, is it easy to add custom metadata to the fs?
<mrvn> fuse has support for extended attributes if you mean that.
<mrvn> You would have to add a Key.MyMetadata module that has a key and a value part and interface it with the setxattr/getxattr/listxattr calls. Haven't planed that yet.
seafood has quit [Read error: 104 (Connection reset by peer)]
seafood has joined #ocaml
<mrvn> Another thing I've skipped for now is support for snapshots.
seafood has quit [Read error: 104 (Connection reset by peer)]
<flux> if everyhing is CoW, wouldn't that be simple?
seafood has joined #ocaml
_zack has joined #ocaml
<mrvn> flux: Just keep the old root of the btree around, yes.
<mrvn> I could add a ((Key.Snapshot.key id), (name, tree stripe)) to the main tree. But then snapshots would be slower than the main tree and always alter the main tree. You could get really long chains with multiple snapshots. A better design is to add an extra layer on top that manages snapshots in a seperate small BTree and have the main FS just as one of the snapshots.
seafood has quit [Connection reset by peer]
jeff__ has quit []
seafood has joined #ocaml
cads has quit [Read error: 113 (No route to host)]
_zack1 has joined #ocaml
_zack has quit [Read error: 113 (No route to host)]
Alpounet has joined #ocaml
<Alpounet> hi
pierre_m has left #ocaml []
Proteus has joined #ocaml
slash_ has quit [Client Quit]
AxleLonghorn has left #ocaml []
AxleLonghorn has joined #ocaml
komar__ has quit [Remote closed the connection]
cads has joined #ocaml
s4tan has joined #ocaml
jamii__ has joined #ocaml
AxleLonghorn has left #ocaml []
sgnb has quit [Read error: 104 (Connection reset by peer)]
sgnb has joined #ocaml
zerny has joined #ocaml
cads has quit [Read error: 113 (No route to host)]
OChameau has joined #ocaml
seafood has quit []
jeanbon has joined #ocaml
<mrvn> Juhey, my mkfs now writes the filesystem signature to the disks.
_zack1 has quit ["Leaving."]
hkBst has joined #ocaml
Yoric[DT] has joined #ocaml
komar_ has joined #ocaml
Proteus has quit ["Leaving"]
babalu has joined #ocaml
<babalu> hi, i've installed lablgtk as a library in a directory /.../lablgtk/lib but now how can i compile an ocaml file with it ? i can launch the executable lablgtk and that launches OCaml and i can write gtk commands ; but if i try to write a file and compile with 'ocamlc -I +lablgtk lablgtk.cma main.ml' it says 'Unbound value [...]'
<gildor> babalu: give use the full "Unbound value ..." error
<babalu> File "main.ml", line 7, characters 17-32:
<babalu> Unbound value GMain.Main.quit
<babalu> it's the first command i use in main.ml that belongs to gtk
<gildor> babalu: replace +lablgtk by the /.../lablgtk/lib (if there is lablgtk.cma in this directory)
<babalu> gildor: but if lablgtk.cma was not found, it would have said it, wouldn't it ?
<babalu> ocamlc -I ~/.../lablgtk lablgtk.cma main.ml
<babalu> hm that worked
<babalu> thanks
<babalu> acutally, that does not work really fine since when i try to launch the executable i get :
<babalu> i have the same big errors if main.ml contains only this line 'let w = GWindow.window ~show:true () ;;'
jeanbon has quit [Read error: 113 (No route to host)]
<babalu> does someone have an idea ?
<babalu> my mistake the compilation also needs gtkInit.cmo
th5 has joined #ocaml
<kaustuv> I have a proposal for an alternative to Batteries' dump function that can produce http://www.msr-inria.inria.fr/~kaustuv/misc/n4.svg by running [dump "n4.svg" (List.init 10 Std.identity)]. Would anyone find something like this useful?
<mrvn> kaustuv: Maybe int values should be unique and not share the same circle.
<kaustuv> Possibly, but because the runtime does not distinguish between 0 and [] and None, etc. it is unclear which ones should be separate and which ones not.
<mrvn> I would keep [] and None seperate too.
<kaustuv> But would you keep None separate from None?
<mrvn> Just causes too much overlap if you have multiple lists or option types.
grirgz has quit [Remote closed the connection]
<flux> mrvn, btw, I suppose online growing of your fs is simple. but have you thought of online shrinking?
<kaustuv> online shrinking seems like a complete non use case for any real situation
<flux> when you are reorganizing storage it's convenient
<mrvn> flux: A simple case of marking a region as out-of-bounds and running defrag. I'm more focused on removing a disk completly rather than shrinking a partition though.
<mrvn> Oh and one feature I haven't mentioned yet. Every block is checksummed so data corruption will be detected and with raid1/5/6 stripes can be repaired automatically.
ulfdoz has quit [calvino.freenode.net irc.freenode.net]
zerny has quit [calvino.freenode.net irc.freenode.net]
jamii__ has quit [calvino.freenode.net irc.freenode.net]
Camarade_Tux has quit [calvino.freenode.net irc.freenode.net]
gildor has quit [calvino.freenode.net irc.freenode.net]
Fullma` has quit [calvino.freenode.net irc.freenode.net]
sbok has quit [calvino.freenode.net irc.freenode.net]
Demitar has quit [calvino.freenode.net irc.freenode.net]
prigaux has quit [calvino.freenode.net irc.freenode.net]
zerny has joined #ocaml
jamii__ has joined #ocaml
Camarade_Tux has joined #ocaml
gildor has joined #ocaml
Fullma` has joined #ocaml
ulfdoz has joined #ocaml
sbok has joined #ocaml
Demitar has joined #ocaml
prigaux has joined #ocaml
LeCamarade has joined #ocaml
Ariens_Hyperion has joined #ocaml
komar_ has quit [Read error: 110 (Connection timed out)]
mishok13 has quit [Read error: 104 (Connection reset by peer)]
s4tan has quit [Read error: 60 (Operation timed out)]
s4tan has joined #ocaml
pierre_m has joined #ocaml
LeCamarade has quit ["Reboot."]
mishok13 has joined #ocaml
<Alpounet> Reference to undefined global `Thread'
<mrvn> -thread
<Alpounet> when linking threads.cma and with option -thread
<Alpounet> "-thread threads.cma"
dejj has joined #ocaml
mrvn has quit [Remote closed the connection]
mrvn has joined #ocaml
holgr has quit [Remote closed the connection]
holgr has joined #ocaml
willb has joined #ocaml
Ariens_Hyperion has quit []
Ariens_Hyperion has joined #ocaml
sgnb has quit [Read error: 104 (Connection reset by peer)]
sgnb has joined #ocaml
th5 has quit []
ched_ has quit [Remote closed the connection]
th5 has joined #ocaml
slash_ has joined #ocaml
thelema has quit [Read error: 54 (Connection reset by peer)]
Ched has joined #ocaml
<petchema_> Alpounet: -thread -I +threads unix.cmxa threads.cmxa
<petchema_> (mmmh s/cmxa/cma/ for bytecode I suppose)
maskd has quit [Remote closed the connection]
th5 has quit []
slash_ has quit [Client Quit]
mrchebas has joined #ocaml
_andre has joined #ocaml
ccasin has joined #ocaml
mishok13 has quit ["Stopping IRC chat... [OK]"]
Amorphous has quit [Read error: 110 (Connection timed out)]
Amorphous has joined #ocaml
<Alpounet> petchema_, if I link against threads.cma, it tells me the module "Thread" is unknown...
slash_ has joined #ocaml
s4tan has quit []
<palomer> hrmph
jeanbon has joined #ocaml
Spiwack has joined #ocaml
komar_ has joined #ocaml
<babalu> how can i use a "method virtual f : 'a -> 'b" in my class ? (when i try i get "f unbound value")
mrchebas has quit ["Leaving"]
<babalu> no one ?
<palomer> babalu, paste some code
<Alpounet> self#f ?
Ariens_Hyperion has quit []
<babalu> oh
<babalu> thanks
<babalu> that was just it
<Alpounet> it's like for any other method
<Alpounet> brb, switching OS.
Alpounet has quit ["Ex-Chat"]
thelema has joined #ocaml
flux has quit [Remote closed the connection]
maskd has joined #ocaml
Alpounet has joined #ocaml
<Alpounet> hi back.
Ariens_Hyperion has joined #ocaml
babalu has quit [Remote closed the connection]
vuln has joined #ocaml
<Alpounet> Wouldn't a Monad.Make functor be useful ?
<Ariens_Hyperion> was the -dtype flg removed from ocamlc?
bouzu has joined #ocaml
acatout_ has joined #ocaml
<Yoric[DT]> Alpounet: what would it do?
<bouzu> jiz
acatout has quit ["leaving"]
<Ariens_Hyperion> ups its dtypes
<bouzu> i have a problem
acatout_ is now known as acatout
<bouzu> int_of_string "1234567890532345" => is not working
<bouzu> maybe int is in 32 bits?
<Yoric[DT]> On 32 bit platforms, int is 31 bit.
<Yoric[DT]> # Int64.of_string "1234567890532345";;
<Yoric[DT]> - : int64 = 1234567890532345L
<bouzu> i need int of string for somting big
<bouzu> any uper of int64 ?
<Yoric[DT]> Well, if that something doesn't fit in an int, you'll have to find another way.
<bouzu> i have a text of int
<Yoric[DT]> Bigger?
<Yoric[DT]> Sure, you have Big_int.
<bouzu> length i dont know 10 line
<Yoric[DT]> # Big_int.of_string "1234567890532345";;
<Yoric[DT]> - : Batteries.Big_int.big_int = <big_int 1234567890532345>
<Yoric[DT]> big integers are theoretically unlimited
<Yoric[DT]> (although they do have limits in practice)
<bouzu> Big_int.of_string dosnt exist
<Yoric[DT]> Well, that's in Batteries.
<Yoric[DT]> In standard OCaml, it may have a slightly different name.
willb1 has joined #ocaml
<Yoric[DT]> Big_int.big_int_of_string
<bouzu> lol
<Yoric[DT]> And you need to be using nums.cma / nums.cmxa .
<bouzu> batteries dosnt exist
<Yoric[DT]> Yes, it does :)
<Yoric[DT]> You just need to install it.
<bouzu> i wana somthing.ml
<Yoric[DT]> To use Big_int, follow the instructions in the OCaml manual (search for "The num library")
<Alpounet> (I should really consider finishing mlbot ASAP, heh)
<Yoric[DT]> Alpounet: :)
<Yoric[DT]> bouzu: or install Batteries :)
<Alpounet> bouzu, are you running Debian ?
* Yoric[DT] will take his leave.
<bouzu> debian ?
<bouzu> im crypting big intiger
acatout has quit ["leaving"]
<Yoric[DT]> bouzu: Alpounet was asking what operating system you're using.
acatout has joined #ocaml
<Yoric[DT]> bouzu: he was planning to help you install Batteries, I'm sure :)
<bouzu> my prblem is "12123213244546765745634543.....999" somthing big int
<bouzu> xo
<bouzu> xp
* Yoric[DT] hasn't dared test Batteries in XP.
<bouzu> Big_int.mli exist
<bouzu> not .ml
<bouzu> i cant import this module
<Yoric[DT]> bouzu: you don't need the .ml
<Yoric[DT]> Have you looked at the documentation, as I've instructed you?
<bouzu> Error: Unbound value Big_int.of_string
<Yoric[DT]> Have you looked at the documentation, as I've instructed you?
<Yoric[DT]> I'll repeat once and then go: To use Big_int, follow the instructions in the OCaml manual (search for "The num library") .
* Yoric[DT] is gone.
<bouzu> The num library" ?
<bouzu> i cant do FILE OPEN big_int.mli or cmi
<Alpounet> calm down, bouzu.
* Yoric[DT] is back, by accident.
<Yoric[DT]> Have you opened the OCaml manual?
<Yoric[DT]> Do you need help finding the manual?
<bouzu> manual for what
<Alpounet> (damned, again the need for mlbot !)
<bouzu> lol
<Yoric[DT]> OCaml
<Yoric[DT]> You are using OCaml, are you not?
<bouzu> yes
<Yoric[DT]> There is a manual for OCaml.
<Yoric[DT]> The manual is here
<Yoric[DT]> Now, in this manual, search for "The num library", it's in part IV.
<Yoric[DT]> It explains the necessary steps to use Big_int.
* Yoric[DT] is going again.
<Alpounet> And, after having read the Num Library section, if you have problems/questions, ask. But not until you have read it.
<bouzu> i will
<bouzu> thnks
<bouzu> but i dont have any permision to import <> .ml
<Alpounet> Yoric[DT], I think it would be the same thing than the module given as argument to Monad.Make, but adding definitions of >>= etc automatically, with respect to the given module.
BiDOrD has joined #ocaml
willb has quit [Read error: 113 (No route to host)]
<Alpounet> And maybe defining a monadic functor fmap, etc.
zerny has quit [Remote closed the connection]
<bouzu> open Big_int.mli;;
<bouzu> not working
<hcarty> bouzu: You really need to read the OCaml manual
<bouzu> i'm not pro in ocaml
<hcarty> And/or a tutorial or two
<bouzu> i just need to use this option
<bouzu> lik usine hd in List
<bouzu> open List.ml
<bouzu> then hd([blalb lalba])
tar_ has joined #ocaml
<bouzu> but big int i cant do this way
<Alpounet> you have to write : open List;; or open Big_int ;;
<Alpounet> without file extension
<bouzu> done
<bouzu> Error: Reference to undefined global `Big_int'
<bouzu> i have this eror
sgnb has quit [calvino.freenode.net irc.freenode.net]
verte has quit [calvino.freenode.net irc.freenode.net]
kg4qxk has quit [calvino.freenode.net irc.freenode.net]
<Alpounet> #load "num.cma" ;;
<Alpounet> (not sure, though)
<Alpounet> (of the name)
<bouzu> num ?
<Alpounet> Big_int is part of the "num" module
prime2 has joined #ocaml
<bouzu> Cannot find file num.cma.
<bouzu> :(
tar_ has quit []
<bouzu> i resing
<bouzu> thnks anyway
<bouzu> bybye
bouzu has quit []
<Ariens_Hyperion> has anyone managed to install ocsigen in leopard?
<prime2> Ariens_Hyperion: The easiest way to do it is with godi
<_andre> anyone using ocsigen.opt?
<Ariens_Hyperion> prime2: I just have ocaml 3.11 installed do I need 3.10?
<prime2> Ariens_Hyperion: No I used it with 3.11 also installed via godi
<Ariens_Hyperion> thanks for the tip prime2. I never heard of godi before :\
<_andre> oh, just found my problem in the ocsigen wiki...
verte has joined #ocaml
oriba has joined #ocaml
<Ariens_Hyperion> prime2: godi says 3.10 is selected
<prime2> Ariens_Hyperion: That will show you how to bootstrap godi with 3.11
<Ariens_Hyperion> cool
<Ariens_Hyperion> prime2: it says its missing pcre. But which one the library or the caml-pcre?
<prime2> Ariens_Hyperion: That is refering to the base pcre libraries of which caml-pcre wraps
<prime2> Ariens_Hyperion: Do you happen to use macports?
<Ariens_Hyperion> I added the suggest flag to the cong file and it seems to be compilling
<Ariens_Hyperion> prime2: yes
<Ariens_Hyperion> ... compilling the pcre lib
sgnb has joined #ocaml
kg4qxk has joined #ocaml
jeanb-- has joined #ocaml
jeanbon has quit [Nick collision from services.]
Spiwack has quit [Remote closed the connection]
jeanb-- is now known as jeanbon
dejj has quit ["Leaving..."]
OChameau has quit ["Leaving"]
flux has joined #ocaml
flux has quit [Remote closed the connection]
<Ariens_Hyperion> prime2: its working! you rule man!
<prime2> Ariens_Hyperion: Not a problem
flux has joined #ocaml
kg4qxk has quit [Connection reset by peer]
verte_ has joined #ocaml
verte has quit [Nick collision from services.]
verte_ is now known as verte
Ariens_Hyperion has quit []
Ariens_Hyperion has joined #ocaml
verte has quit [":("]
Fullma has joined #ocaml
pierre_m has quit [Read error: 110 (Connection timed out)]
Fullma` has quit [Connection timed out]
Mr_Awesome has quit ["aunt jemima is the devil!"]
Ariens_Hyperion has quit []
_andre has quit ["Lost terminal"]
Ariens_Hyperion has joined #ocaml
<vuln> I'm having some troubles about using 'when' in pattern-matching. May anyone help me?
<vuln> My code has a function, and I would like to, using pattern-matching, says something depending to what that function retrieves
<vuln> The key-word 'when' is not helping me with that :)
<Ariens_Hyperion> try "math function argument with | result0 -> foo | result1-> bar ....
<vuln> I think it worked now
<vuln> lemme see
<Ariens_Hyperion> s/math/match
<vuln> Ariens_Hyperion: it doesn't work here
<Ariens_Hyperion> can you paste the code?
<vuln> it is working now :)
<vuln> Of course.
<vuln> Give me one sec
<vuln> It's working.
Smerdyakov has joined #ocaml
<Ariens_Hyperion> vuln: you should probably add an extra let in to compute the average just once
<vuln> humm
<vuln> lemme see
<vuln> Ariens_Hyperion: any suggestion how to do it?
<Ariens_Hyperion> vuln is the f(notas) the average?]
<vuln> yes.
<Ariens_Hyperion> the thing is you could have an invalid grade and the average would still be positive
<vuln> I didn't get the point ;o
<Ariens_Hyperion> for example nota1 = 10, nota2 = 10, nota3 = -1
<Ariens_Hyperion> the average is positive but one grade is invalid
<vuln> It can be possible :)
jeanb-- has joined #ocaml
<vuln> Once, in class, a friend of mine had 0 in an exam. He was almost fighting with the teacher haha, so the teacher said he lost one point
<vuln> -1 :P
<Ariens_Hyperion> ok :p
<Ariens_Hyperion> then i sugest you use a let in in "funcao", for example " let stat_value = f notas in"
<Ariens_Hyperion> and the use if elses
<Ariens_Hyperion> then*
<vuln> The original one use if/else/then
<vuln> but at my last class, the teacher taught pattern-matching
<vuln> So I'm trying to pratice :D
<vuln> practice*
jeanbon has quit [Nick collision from services.]
jeanb-- is now known as jeanbon
jeanbon is now known as chickenzilla
<vuln> Ariens_Hyperion: look now, if it's better to you (with the let in)
oriba has left #ocaml []
<vuln> :)
chickenzilla is now known as jeanbon
<Ariens_Hyperion> in this case I think the if elses are simpler
<vuln> Ariens_Hyperion: True, but as I said I'm trying to learn more of pm :)
<Ariens_Hyperion> ok :)
<vuln> :)
oof has quit [Read error: 104 (Connection reset by peer)]
thelema has quit [Read error: 60 (Operation timed out)]
ccasin has quit ["BitchX-1.1-final -- just do it."]
olegfink has joined #ocaml
<olegfink> that's magic, I don't understand the typing here:
<olegfink> # let rec c n f x = if n>0 then f (c (n-1) f x) else x ;;
<olegfink> val c : int -> ('a -> 'a) -> 'a -> 'a = <fun>
<olegfink> # let e a b = b a ;;
<olegfink> val e : 'a -> ('a -> 'b) -> 'b = <fun>
<olegfink> # e (c 2) (c 3) ;;
<olegfink> - : ('_a -> '_a) -> '_a -> '_a = <fun>
<olegfink> it even computes correctly:
<olegfink> # e (c 2) (c 3) ((+)1) 0 ;;
<olegfink> - : int = 8
<Ariens_Hyperion> what does this function compute?
<olegfink> it's exponentiation on church numerals.
<olegfink> but from the type of e, 'a -> ('a -> 'b) -> 'b, 'a should be equal to ('a -> 'b) which should be equal to 'b. strange.
komar_ has quit [Remote closed the connection]
<Ariens_Hyperion> I can't understant why does it compile either
<aij> olegfink: why would the 'e' function care what the type of 'a' is ?
<aij> it sounds like you're just getting a more general type than you're expecting
<olegfink> no, at least that late into night, my brain can't unify 'a, 'a -> 'b and 'b
<olegfink> I can't see how this is possible even for the most general type (which this one clearly is)
<olegfink> and they should unify so that I can get the right type for application.
<olegfink> aij: hm, I'm starting to remember something about '_underscored type variables. could you remind me what's special about them?
<aij> oh, those mean the type isn't polymorphic but hasn't been bound yet
<olegfink> hrm, how come it's not polymorphic.
<aij> because ocaml doesn't allow you to return a polymorphic function
<olegfink> I have a feeling that I'm being tricked here.
<olegfink> ah
<aij> ocaml doesn't have the full value restriction of SML, but I sometimes wish it wasn't as strict as it is :P
<olegfink> but still I don't understand e's type.
<olegfink> I've started all that just because I was too lazy to figure if exponentiation was lambda-definable a la Curry.
<olegfink> and now I have an answer I can't interpret :-(
<aij> ok, so e takes an argument of any type, 'a, then another argument from that to any type 'b, and returns you value of type 'b
<olegfink> indeed, but all three arguments should be specialized to the same in the application
<olegfink> and I can't understand how that happens
<flux> olegfink, perhaps writing a unification algorithm will help?-)
<flux> (not like I would have done that exercise, though)
Associat0r has joined #ocaml
Associat0r has quit [Read error: 104 (Connection reset by peer)]
<olegfink> i was supposed to write one, but probably I didn't understand what I wrote. anyway, here I'm just trying to check if e has a type in Curry-typed lambda calculus, and ocaml's answer doesn't convince me.
<Ariens_Hyperion> I need to study weak types :\
<Smerdyakov> Ariens_Hyperion, what do you mean by "weak types"?
<Ariens_Hyperion> the '_a
<Smerdyakov> Ariens_Hyperion, they're just unification variables. The only interesting bit is why they would appear.
<olegfink> I believe in HM as described by Cardelly they should either go away or proclaim the expression untypable
<mattam> # e (c 2);;
<mattam> That should make it obvious I think.
Alpounet has quit ["Quitte"]
<olegfink> hm, let rec c n f x = if n>0 then f (c (n-1) f x) else x; exp a b = b a in exp (c 2) (c 3) types in http://www.cidee.de/ca/type/07/index.html
<olegfink> mattam: this has a strange type, while it should be something unifiable to int -> int, where int is ('a -> 'a) -> 'a -> 'a
<mattam> Weel, it has to be an instance of (int -> int).
<olegfink> well, yes, but it doesn't seem to be (or I can't count parens properly)
bzzbzz has joined #ocaml
<mrvn> wasn't exp untypeable?
<olegfink> mrvn: I think that's the case, but trying to use modern technology(tm) to check.
<mfp> found on reddit "type inference only proceeds left to right" -> ??
<mattam> exp a b = b a;; wouldn't be typable?
Ariens_Hyperion has quit []
<mfp> this guy says that c |> b |> a sometimes requires fewer type annotations than a (b c) " since type inference only proceeds left to right, this lets you put things in the right order to avoid needing type annotations in some places"
<mfp> [let (|>) x f = x f]
<mfp> oops = f x
jeanbon has quit ["EOF"]
<mattam> let e : (('a -> 'a) -> 'a -> 'a) -> ('a -> 'a) -> 'a -> 'a = e (c 2);;
<mattam> That's [int -> int].
<mattam> Oops. Messed with the top-level :)
<mrvn> define type Int = ('a -> 'a) -> 'a -> 'a so one can read that
jamii__ has quit [Read error: 110 (Connection timed out)]
seafood has joined #ocaml
<mattam> type 'a cint = ('a -> 'a) -> 'a -> 'a;;
<mattam> let e : ('a -> 'a) cint -> 'a cint = exp (c 2);;
<mattam> val e : ('_a -> '_a) cint -> '_a cint = <fun>
<olegfink> hmm, why ('a -> 'a) cint and not 'a cint -> 'a cint?
<mrvn> let e : 'a. ('_a -> '_a) cint -> '_a cint = exp (c 2);;?
<mattam> Because that's how 'a get's instantiated by the (c 2) argument's type.
<mrvn> I think the problem is that one would want (('_a -> '_a) as '_a) cint -> '_a cint
Mr_Awesome has joined #ocaml
vuln has quit ["leaving"]
seafood has quit []
thelema has joined #ocaml
Yoric[DT] has quit ["Ex-Chat"]
prime2 has quit ["leaving"]
tonasinanton has joined #ocaml
seafood has joined #ocaml
seafood has quit []
jeddhaberstro has joined #ocaml
seafood has joined #ocaml
seafood has quit []