gildor changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | OCaml 3.12.0 http://bit.ly/aNZBUp
lamawithonel has joined #ocaml
lamawithonel has quit [Remote host closed the connection]
tauntaun has joined #ocaml
boscop has quit [Ping timeout: 240 seconds]
arubin has joined #ocaml
duper has quit [Ping timeout: 240 seconds]
ccasin has joined #ocaml
joewilliams_away is now known as joewilliams
udzinari has quit [Remote host closed the connection]
lopex has quit []
joewilliams is now known as joewilliams_away
joewilliams_away is now known as joewilliams
myu2 has quit [Remote host closed the connection]
ccasin has quit [Quit: Leaving]
npouillard has quit [Read error: Operation timed out]
tauntaun has quit [Ping timeout: 240 seconds]
npouillard has joined #ocaml
enthymeme has quit [Quit: rcirc on GNU Emacs 23.1.1]
lamawithonel has joined #ocaml
lamawithonel has quit [Read error: Connection reset by peer]
arubin has quit [Quit: arubin]
lamawithonel has joined #ocaml
joewilliams is now known as joewilliams_away
lamawithonel has quit [Remote host closed the connection]
myu2 has joined #ocaml
willb1 has quit [Ping timeout: 240 seconds]
joewilliams_away is now known as joewilliams
willb1 has joined #ocaml
infbliss has joined #ocaml
<infbliss> is there a yum package for ocaml?
<infbliss> to install on redhat systems
<Asmadeus> probably, why not check yourself? :P
<infbliss> i did a yum install ocaml
<infbliss> on my system
<infbliss> but did'nt work
<infbliss> found it. apparently it is ocaml-lcaml
ulfdoz has joined #ocaml
infbliss has quit [Remote host closed the connection]
joewilliams is now known as joewilliams_away
myu2 has quit [Remote host closed the connection]
sepp2k has joined #ocaml
kaustuv_ has left #ocaml []
cyanure has joined #ocaml
myu2 has joined #ocaml
boscop has joined #ocaml
cyanure has quit [Quit: Quitte]
boscop has quit [Ping timeout: 240 seconds]
ikaros has joined #ocaml
philtor has quit [Ping timeout: 240 seconds]
thelema has quit [Remote host closed the connection]
thelema_ has joined #ocaml
BiDOrD_ has joined #ocaml
BiDOrD__ has joined #ocaml
BiDOrD has quit [Read error: Connection reset by peer]
Yoric has joined #ocaml
BiDOrD_ has quit [Ping timeout: 255 seconds]
ulfdoz has quit [Ping timeout: 255 seconds]
Modius has joined #ocaml
Inazad has joined #ocaml
<Inazad> hi there, i need help for a coding function
<Inazad> someone is here ?
myu2 has quit [Remote host closed the connection]
<Inazad> its a program who decodes a huffman string
<Inazad> does my code looks good ?
<mrvn> wrong locale
<Inazad> what ?
bobzhang` has joined #ocaml
<mrvn> you are using french, right?
<Inazad> yes
<mrvn> Line 6 could read |Feuille(_),[] -> ""
<Inazad> but it doesn't matters
<mrvn> and line 8 | _ ->
<Inazad> the function should decode a binary list and a huffman tree to returns a string
<Inazad> the code works with one leaf but not with a complete tree
<Inazad> I get "" as result
<Inazad> function extraireFeuille should returns the caracter of the path (like 1;1;0)
<mrvn> line 11 makes no sense
<Inazad> why
<mrvn> should give you a compiler warning too
<mrvn> (s' ^ Char.escaped(extraireFeuille a' (t'@[c]))) is computed and thrown away
<Inazad> if I get a U
<Inazad> I add it to my table until I get a Z
<Inazad> when I get a Z, i get the char for the path
<Inazad> clear my table and continue in the list
<Inazad> I could have the following structure
<mrvn> and you throw it away
<Inazad> what do u mean ?
<mrvn> you are not doing anything with it.
<Inazad> I want that s' get all the chars
<Inazad> then when the list is empty, returns the string s'
ygrek has joined #ocaml
<Inazad> how I can fix this ?
<mrvn> but s' is not getting anything
<Inazad> why ?
<mrvn> because 1+2 does not make 1 be 3.
<Inazad> how to get 1+2 -> 3 ?
<Inazad> do I have to do
<Inazad> s' ^ (s^ ....) ?
<mrvn> s' ^ whatever does not change s'
<Inazad> how to change it and keep the values
<mrvn> you can't. you can only create a new string
<Inazad> yeah but could I keep the same string and pass it each time to the function ?
<Inazad> I was thinking that if I keep s' as var, I could concat it and return the result...
<mrvn> That is what you are currently doing so it always is ""
<mrvn> There are simply no vars in functional languages
<Inazad> how to not get "" ?
<mrvn> make a new string and pass that along
<Inazad> let s'' = ..... and passing s''
<mrvn> yes. or call is s' again.
<Inazad> what would be the correct syntax for the line ?
<mrvn> or give it an actually meaningfull name so one can understand what it is.
<mrvn> let s'' = ..... in ...
<Inazad> s' = the returning string
<Inazad> let decodage a l_bin = match a,l_bin with
<Inazad> |Vide,_ -> failwith "ERREUR : Arbre vide avec liste pleine."
<Inazad> |Noeud(_,_),[] -> failwith "0ERREUR : Arbre plein avec liste vide."
<Inazad> |Feuille(_),[] -> failwith "1ERREUR : Arbre plein avec liste vide"
<Inazad> |Noeud(_,_),[] -> failwith "2ERREUR : Arbre plein avec liste vide"
<Inazad> |Feuille(_),U::[] -> "" ^ (Char.escaped (extraireFeuille a [U]))
<Inazad> |Feuille(_),U::r -> "" ^ (Char.escaped (extraireFeuille a [U])) ^ decodage a r
<Inazad> |a,l_bin -> let rec loopInList a' l' t' s' =
<Inazad> match l' with
<Inazad> |c::r when c = U -> loopInList a' r (t'@[c]) s'
<Inazad> ohh shit
<Inazad> sorry
<Inazad> should be alright ?
<Inazad> |c::r when c = Z -> begin let s' = (s' ^ Char.escaped(extraireFeuille a' (t'@[c]))); (loopInList a' r [] s') end
myu2 has joined #ocaml
<mrvn> drop the begin/end. Let already covers that. and you are missing the "in"
<Inazad> i got this output
<Inazad> how to fix it
<mrvn> you need to match Noeud(_,_),_::_
<Inazad> with what ?
<mrvn> whatever should happen when you get such an input
<Inazad> ok but how to use the input ?
<Inazad> how that I pass _ ?
bobzhang` has left #ocaml []
<mrvn> same way you do in all the other cases
<mrvn> Your line 3 and 5 match the same case by the way
<Inazad> could I replace Feuille(_),U::r and Feuille(_),U::[] by the same line ?
<mrvn> no, but the later you can change to Feuille(_), []
<Inazad> I don't get the last letter
<kaustuv> You also need: let rec decodage =
<kaustuv> or rather, let rec decodate a l_bin =
<kaustuv> s/t/g
<Inazad> ?
<mrvn> you should rewrite the thing in english and paste the complete code with an example.
<Inazad> I never getting the last letter ?
<kaustuv> The French is pretty simple though. Noeud/Feuille = Node/Leaf, extraire = extract
<kaustuv> Vide = empty, plein = full
<Inazad> why the last letter is missing ?
<mrvn> That looks totally wrong. Shouldn't b be somewhat more balanced?
<Inazad> balanced ?
<Inazad> they are placed in the tree in order or appearance
<Inazad> like
<mrvn> But that isn't a tree. That is a list.
<Inazad> ABBCCC -> C,B,A
<Inazad> anyway, I don't understand why the last letter is missing
<kaustuv> Inazad: run it in the toplevel with: #trace decodage ;;
<mrvn> It should be more like Noeud (Noeud (Feuille 'I', Feuille 'S'), Noeud (Feuille ' ', Feuille 'O',)))
<Inazad> cause the last Feuille is U;U;U
<mrvn> U means right and Z means left? Or what is encoded there?
<Inazad> yes
<Inazad> damn, I never get the last feuille
<Inazad> got it
<mrvn> Now the code makes even less sense.
<mrvn> Inazad: did you write the codage too?
Yoric has quit [Quit: Yoric]
<mrvn> Inazad: what does this give? decodage (Noeud (Noeud (Feuille 'A', Feuille 'B'), Noeud (Feuille 'C', Feuille 'D'))) [U; U; U; Z; Z; U; Z; Z]?
mnabil has joined #ocaml
edwin has joined #ocaml
<mrvn> kaustuv: move line 18 into line 14
<mrvn> kaustuv: Line 15 can only match (Vide,_), right?
sepp2k has quit [Quit: Leaving.]
ftrvxmtrx has quit [Quit: Leaving]
Inazad has quit [Ping timeout: 276 seconds]
myu2 has quit [Remote host closed the connection]
ttamttam has joined #ocaml
ygrek has quit [Ping timeout: 240 seconds]
Yoric has joined #ocaml
Yoric has quit [Read error: Connection reset by peer]
Yoric has joined #ocaml
myu2 has joined #ocaml
yezariaely1 has joined #ocaml
yezariaely1 has left #ocaml []
Yoric has quit [Client Quit]
Yoric has joined #ocaml
_andre has joined #ocaml
boscop has joined #ocaml
ftrvxmtrx has joined #ocaml
myu2 has quit [Remote host closed the connection]
myu2 has joined #ocaml
jonafan_ has joined #ocaml
Yoric has quit [Quit: Yoric]
jonafan has quit [Ping timeout: 240 seconds]
myu2 has quit [Remote host closed the connection]
Yoric has joined #ocaml
jsk has joined #ocaml
filp has joined #ocaml
tauntaun has joined #ocaml
dark has quit [Ping timeout: 240 seconds]
lopex has joined #ocaml
tauntaun has quit [Remote host closed the connection]
dark has joined #ocaml
myu2 has joined #ocaml
Associat0r has joined #ocaml
ftrvxmtrx has quit [Remote host closed the connection]
ftrvxmtrx has joined #ocaml
ygrek has joined #ocaml
tauntaun has joined #ocaml
Associat0r has quit [Quit: Associat0r]
oriba has joined #ocaml
cyanure has joined #ocaml
tauntaun has quit [Ping timeout: 246 seconds]
cyanure has quit [Ping timeout: 264 seconds]
<oriba> hello.... did freenode changed the ssl certificates some days ago?
Yoric has quit [Read error: Connection reset by peer]
Yoric has joined #ocaml
ygrek has quit [Ping timeout: 240 seconds]
agarwal1975 has joined #ocaml
myu2 has quit [Remote host closed the connection]
smerz has joined #ocaml
pdhborges has joined #ocaml
cyanure has joined #ocaml
<pdhborges> I have a little question about the type checker
<thelema_> pdhborges: go ahead
<pdhborges> in this comment http://ocaml.janestreet.com/?q=node/11#comment-27
thelema_ is now known as thelema
<pdhborges> milanst says the compyler couldn't equate
<pdhborges> 'a t and readonly t as the same type
<pdhborges> to satisfy the interface
<thelema> okay
<pdhborges> however I created a function with signature 'a -> 'a -> 'a
<pdhborges> and a polymofic record type
<pdhborges> and I could use for example
<pdhborges> and 'a record and an int record with that function
<pdhborges> no problems
<thelema> sure
<pdhborges> but hwo can the compiler equate the types in this case
<pdhborges> but not on the other case
<thelema> the problem is not exactly in the type inference in the other case, but in whether a module type matches the inferred type
<thelema> and a subtlety about phantom types makes it not do this
<pdhborges> but
<thelema> in your case, everything is perfectly normal type inference, ('a) unifies with anything
<pdhborges> yes
<pdhborges> but it has to unify
<pdhborges> 'a with 'b recor
<pdhborges> and at the same time
<pdhborges> 'a with int record
<dark> (so 'b = int)
<thelema> actually, most likely in your case, it unifies 'a with int record, and then the other 'a forces 'b = int
<thelema> and then there's no variables left after unification
<thelema> but in the given example, the inferred type is 'a -> 'a
<thelema> but the desired signature is 'a t -> readonly t
<thelema> and there's nothing that (the first) 'a can be set to to unify the two
<pdhborges> why not set 'a to 'a t?
<dark> pdhborges, oh i got what you asked. readonly t is more specific than 'a t. if you have a function with a more general type you can apply it with a more specific type, but not vice versa. that's why the types are incompatible
<dark> so a function that expects 'a t will work with readonly t, but a function that expects readonly t won't work with 'a t
<dark> and 'a works with everything :)
<thelema> pdhborges: setting 'a = 'a t fails to unify the right side
<thelema> if you go one step further and set 'a = readonly t, that fails to unify the left side
<pdhborges> I think I'm mixing to diferent things in my head hence the confusion
<dark> pdhborges, ocaml has a type called '_a that is like 'a, but once you use it for some type (like say int) you can't use it for other type
<pdhborges> I know
<pdhborges> it's a monomorphic type
<dark> yes, i thought you were thinking of 'a as being like '_a :)
<pdhborges> no thats no it
<pdhborges> not*
<pdhborges> thelema so in the first case the problem is signature mathing
<pdhborges> In my case It's just type inference
<pdhborges> s/mathing/matching
<dark> if f : ('a -> 'a -> 'a), let q = f (x : 'a record) (y : int record) works and q has type int record (because it is the most specific type from those 3 that were unified)
<dark> 'a record and int record are compatible but not equal; if you think them as sets, int record is a subset of 'a record
<thelema> They're related. In this example, the signature matching requires the left hand side to stay polymorphic, while your example works as long as all the 'a can be resolved satisfactorily
<dark> compatible, hm, in one way..
<pdhborges> this was my example
<pdhborges> now about the module
<pdhborges> if the type goes trough z
<pdhborges> what does the compiler infer for the readonly function?
<thelema> yes, k is properly polymorphic, not monomorphic
<thelema> z?
<pdhborges> yes
<pdhborges> type z = { mutable r : int } type 'a t = z
<thelema> oh yes..
<pdhborges> initially the compiler infered 'a -> 'a
<thelema> z -> z
<pdhborges> a so it's the inference for the signature that changes
<pdhborges> not the inference for the struct
<pdhborges> 'a -> 'a is more general than z -> z so it won't complain
<thelema> yes, once it's got z -> z, it can unify each of the z's separately with 'a t and readonly t
<thelema> z -> z is different from 'a t -> 'a t
<thelema> even though 'a t = z
<kaustuv> dark: OCaml does *not* have a type '_a. You can never write it in signatures, for instance. It is a feature of the OCaml implementation only.
<pdhborges> thelema: so the compilers looks at
<pdhborges> 'a t and figures it's z
<pdhborges> then at readonly t which is also z
<thelema> kaustuv: that's a fine line, splitting the OCaml implementation from the lanaguge, considering that since there's only one implementation of the language, many aspects of the language are defined by that implementation
<thelema> pdhborges: yup
<pdhborges> the signature becomes z -> z
<pdhborges> the implementations still
<pdhborges> 'a -> 'a
<thelema> well, the implementation is untyped - once typechecking is done, types are erased
<pdhborges> for implementation I mean't the struct
<pdhborges> s/'//
mnabil has quit [Read error: Operation timed out]
<thelema> the struct is still 'a -> 'a? the record? the readonly function?
<pdhborges> the readonyl function
<thelema> the readonly function is z -> z
<pdhborges> that's the signature but the type checker must match that signature with the infered signature for the readonly implementation no?
<thelema> sure, the inferred signature for "readonly t = t" is 'a -> 'a
<pdhborges> \o/ thanks guys. Today I learned quite a bit about ocaml's subtleties.
<thelema> n/p
<kaustuv> Is the issue here that this works:
<kaustuv> let f : 'a -> 'a = fun x -> x + 1
<kaustuv> but this doesn't:
<kaustuv> module M : sig val f : 'a -> 'a end = struct let f x = x + 1 end
oriba_ has joined #ocaml
<kaustuv> ?
<thelema> kaustuv: kind of.
<thelema> although more subtle.
<thelema> type 'a t = {mutable r: int}
<thelema> module M : sig val ro : 'a t -> readonly t end = struct let readonly t = t end
<thelema> this doesn't work
<thelema> but if you define the type 'a t as:
<thelema> type z = {mutable r: int}
<thelema> type 'a t = z
<thelema> then it works
oriba has quit [Ping timeout: 240 seconds]
<pdhborges> kaustuv let f : 'a. 'a -> 'a = fun x -> x + 1;; ^^
philtor has joined #ocaml
<kaustuv> Ah, the issue is that the type checker expands abbreviations before unification
<thelema> maybe. maybe the non-polymorphic type z allows it to break the dependence of 'a t on the left side from 'a t on the right side
mnabil has joined #ocaml
myu2 has joined #ocaml
<kaustuv> This works though:
<kaustuv> module M : sig type 'a t type ro val ro : 'a t -> ro t end = struct type 'a t = A type ro let ro x = (x :> ro t) end ;;
<mrvn> # let f : 'a -> 'a = fun x -> x + 1;;
<mrvn> val f : int -> int = <fun>
<thelema> yes, this changes the inferred type from 'a -> 'a to 'a t -> ro t
<mrvn> The reason why that works is that the signature you give is more a hint of the shape of type f needs to have and the type inference figures out it actually is int -> int which is the right shape.
<mrvn> On the other hand in a module signature you need exact type equality.
<thelema> mrvn: yup, 'a -> 'a is able to unify with the inferred type, so everything is okay.
<thelema> umm, not really - one can restrict types with a module signature
<kaustuv> the problem seems to be that in order for ('x -> 'x) to unify with ('a t -> 'b t) the type checker will need to prove that 'a t = 'b t, i.e. that the type parameter is a phantom. I guess the type checker doesn't have a phantomness detector
<thelema> i.e. inferred: 'a -> 'a, spec: int -> int is okay
<mrvn> true. Ok. In a module the relationship is the other way around. The function gives the looser type.
<thelema> kaustuv: that matches my mental model of what's going on more than the order of unification and type abbreviation expansion
tauntaun has joined #ocaml
joewilliams_away is now known as joewilliams
<mrvn> That 'type z = {mutable r: int} type 'a t = z' makes a difference doesn't really make sense but it has some reason somewhere in the implementation.
<thelema> mrvn: doens't kaustuv's last message clarify it?
<kaustuv> I am guessing the reason the type checker doesn't detect phantomness is that that would drastically reduce their usefulness. It would suck if the typechecker didn't complain when I tried to coerce a readonly t to a writable t.
<thelema> kaustuv: ah, yes.
<mrvn> not really. ['a] {mutable r: int} == ['b] {mutable r: int}. But it only sees that with the intermittant z type.
<mrvn> kaustuv: it only complain when the phantom type is abstract/private
<thelema> because it doesn't know about (or care about) the definition for the type at this point
<thelema> mrvn: it only sees 'a -> 'a and 'a t -> readonly t and can't unify the two
oriba_ has left #ocaml []
oriba has joined #ocaml
<thelema> the type checker doesn't substitute all the way down to basic types and then unify
<mrvn> good thing too
<Lor> What's the current recommended approach to naming modules in a library?
<Lor> Just add a package prefix to all the top-level module names?
<thelema> Lor: packing them into a top-level module is recommended as long as you don't have any problems with executable size
<Lor> Or use -pack and try to avoid module names that conflict with existing ones?
<thelema> batteries doesn't follow this good advice because of executable size issues
<Lor> Ah, the entire top-level module is always linked in?
agarwal1975 has quit [Read error: Connection reset by peer]
<thelema> yes, that's the semantics for modules
agarwal1975 has joined #ocaml
<Lor> The problem with -pack is that it's very fragile since the modules being defined must not conflict with top-level modules.
<Lor> thelema, that's implementation, not semantics.
<Lor> If a submodule is never ever used, the semantics don't change even if it's removed.
<thelema> almost - the semantics of program execution are that each phrase in each module is executed in link order
<thelema> modules can have side effects just from being linked in
<thelema> and the ocaml compiler doesn't test for this, so can't eliminate anything
<Lor> True enough.
<kaustuv> In fact it is impossible to test for it because of the halting problem
<Lor> Still an implementation issue, but a more complicated one.
<Lor> rice's theorem, you mean. Yes, but there are always conservative approximations.
<thelema> kaustuv: there's some pretty good approximations - function declarations are guaranteed to have no side effects
<mrvn> thelema: let f = incr foo; functiion () -> ()
<thelema> that's not what I meant
<thelema> that isn't a function according to the ocaml compiler, otherwise it would be polymorphic instead of monomorphic
<thelema> (ignoring that it's unit -> unit)
<mrvn> and wasn't there a bug that the compiler eliminates modules with side effects when none of it is used?
agarwal1975 has quit [Read error: Connection reset by peer]
agarwal1975 has joined #ocaml
<mrvn> # let f = incr foo; function () -> ();;
<mrvn> val f : unit -> unit = <fun>
<mrvn> How is that not a function?
<mrvn> # let f = incr foo; function x -> x;;
<mrvn> val f : 'a -> 'a = <fun>
<mrvn> works polymorphic too
<thelema> hmmm...
<mrvn> More common is probably let f = let x = ref something in function ....
<thelema> # let f = let r = ref 0 in function x -> x;;
<thelema> # Warning Y: unused variable r.
<thelema> val f : '_a -> '_a = <fun>
<thelema> yes, once mutables come into play...
<Lor> All right, so I should use -pack and just hope that ocaml gets real namespaces one day?
<thelema> n/m then, my mistake
<thelema> Lor: yes, that's the best we've got.
<mrvn> thelema: yes. if you create a ref you loose the polymorphism.
<kaustuv> OCaml has real namespaces. What you want is dead code elimination.
<Lor> I'm still not sure it's a good idea.
<Lor> Then in code it becomes difficult to see where exactly a top-level module is.
<f[x]> Lor, complain on that ticket!
<Lor> kaustuv, did you read the above bug report?
<f[x]> kaustuv, nope
<pdhborges> mrvn you example is correct
<pdhborges> incr increments the ref
<Lor> It's much clearer to open PackagePrelude than Prelude in the source code of the package, even if Prelude would eventually get packed into Package.Prelude.
<pdhborges> but the value of the expression is function () -> ()
<pdhborges> which is then bound to f
<thelema> mrvn: in any case, those kinds of "functions" can be syntactically eliminated
<kaustuv> By real namespaces I mean -for-pack
<kaustuv> which doesn't have name collisions
<mrvn> thelema: they are possible so the compiler has to consider them
<Lor> Right, the different module structures for native and bytecode compilation results even in observable runtime differences.
<kaustuv> take the bytecode compiler behind the shed and put a bullet between its eyes already
<thelema> mrvn: yes, they can't be easily eliminated by dead code elim, and have to be treated as possible "actually-evaluating" functions
* thelema would be kinda happy to deprecate the bytecode compiler
<kaustuv> (unless you use some crazy platform that doesn't have a native backend)
* pdhborges would be kind of happy to support dynamic linking in native code
<kaustuv> You have issues with Dynlink in native code?
<pdhborges> ? Dynlink?
<kaustuv> file:///usr/share/doc/ocaml-doc/ocaml.html/libref/Dynlink.html
<pdhborges> wait ocaml supports dynamic linking of ocaml modules/
<pdhborges> ?
<kaustuv> err, or the caml.inria.fr version
<kaustuv> sorry, my manual defaults to filesystem
<pdhborges> :o if ocaml supports dynamic linking why are my executables > 300kb and why are batteries executables huge?
<mrvn> .oO(Because they don't USE dynamic linking?)
Yoric has quit [Quit: Yoric]
<kaustuv> If you directly use the BatFoo modules instead of going through Batteries, your executables should be fairly small
<pdhborges> cand I load the stdlib asa plugin?
<pdhborges> also do I have to call teh Dynlink module explicetly?
<thelema> kaustuv: except if you accidentally include the IO subsystem, which is most of the code size, IIRC
<thelema> which might happen by using any module with a print function? hmmm...
<thelema> definitely some detangling would be useful
<pdhborges> :| It looks like I have to modify the source to use Dynlink
<thelema> pdhborges: batteries is dynlink enabled - as for using it in a program, iirc, mfp made a nice way to do that
<pdhborges> this is like calling dlopen manually
<pdhborges> not exactly what I had in mind
arubin has joined #ocaml
agarwal1975_ has joined #ocaml
agarwal1975 has quit [Read error: Connection reset by peer]
agarwal1975_ is now known as agarwal1975
arubin has quit [Ping timeout: 276 seconds]
arubin has joined #ocaml
npouillard has quit [Ping timeout: 260 seconds]
ccasin has joined #ocaml
ttamttam has quit [Quit: ttamttam]
ttamttam has joined #ocaml
npouillard has joined #ocaml
BiDOrD__ has quit [Ping timeout: 240 seconds]
ftrvxmtrx has quit [Quit: Leaving]
BiDOrD has joined #ocaml
DimitryKakadu has joined #ocaml
Snark has joined #ocaml
lopex has quit []
jonafan_ is now known as jonafan
lopex has joined #ocaml
mnabil has quit [Read error: Connection reset by peer]
kaustuv_ has joined #ocaml
ttamttam has quit [Remote host closed the connection]
filp has quit [Quit: Bye]
oriba has quit [Quit: Verlassend]
cthuluh has quit [Ping timeout: 260 seconds]
<f[x]> mfp, ping
cthuluh has joined #ocaml
albacker has joined #ocaml
mjonsson has joined #ocaml
ftrvxmtrx has joined #ocaml
mjonsson has quit [Quit: Leaving]
<DimitryKakadu> hallo man!
<DimitryKakadu> How to compile oasis 0.2.0 with ocaml3.12?
<DimitryKakadu> it says me module FI_metascanner is absent?
<DimitryKakadu> where can I find this module? in what library?
tauntaun has quit [Ping timeout: 255 seconds]
<thelema> DimitryKakadu: can you use the precompiled version?
<thelema> s/the/a/
<DimitryKakadu> Maybe. If Debian package exists.
eye-scuzzy has quit [Quit: leaving]
<DimitryKakadu> I've compiled all reqirements for oasis today. This error is some kind of unluck.
eye-scuzzy has joined #ocaml
<DimitryKakadu> Oh, I've founded .bin file.
cyanure has quit [Quit: Quitte]
cyanure has joined #ocaml
Yoric has joined #ocaml
Inazad has joined #ocaml
<gildor> DimitryKakadu: this is a bug, please open a bug against oasis with your error message, if you have time
Inazad has quit [Ping timeout: 240 seconds]
lamawithonel has joined #ocaml
dark has quit [Remote host closed the connection]
<mfp> f[x]: pong
<thelema> ps ax
<thelema> ls
<thelema> (don't mind me, I need more ram)
_andre has quit [Quit: leaving]
albacker has quit [Ping timeout: 276 seconds]
myu2 has quit [Remote host closed the connection]
albacker has joined #ocaml
cyanure has quit [Quit: Quitte]
Cyanure has joined #ocaml
cyy has joined #ocaml
albacker has quit [Read error: Connection reset by peer]
albacker has joined #ocaml
pdhborges has quit [Ping timeout: 245 seconds]
Inazad has joined #ocaml
tauntaun has joined #ocaml
albacker has quit [Quit: Leaving]
Edward has joined #ocaml
[1]Inazad has joined #ocaml
Inazad has quit [Ping timeout: 260 seconds]
cyy has quit [Quit: cyy]
<[1]Inazad> I don't know why I get a match failure...
<[1]Inazad> when the string is too big, I got this error..
<gildor> DimitryKakadu: second thought, Fl_metascanner is from findlib in fact
<gildor> DimitryKakadu: I'll check your package .list for version
<DimitryKakadu> my findlib's version is 1.2.5. What about yours?
[1]Inazad has quit [Ping timeout: 276 seconds]
<adrien> [1]Inazad: ocaml* should give you at least one possible pattern which you're not handling, really best to handle all these
<DimitryKakadu> gildor: my findlib's version is 1.2.5. What about yours?
<adrien> bah
Snark has quit [Quit: Ex-Chat]
enthymeme has joined #ocaml
<gildor> DimitryKakadu: 1.2.6
<gildor> DimitryKakadu: but 1.2.4 on windows
<gildor> DimitryKakadu: maybe check that you have a findlib.cma/fl_metascanner.cmi in your installation directory
Asmadeus has quit [Ping timeout: 260 seconds]
Inazad has joined #ocaml
Asmadeus has joined #ocaml
Inazad has quit [Ping timeout: 240 seconds]
DimitryKakadu has quit [Ping timeout: 255 seconds]
seafood has joined #ocaml
cyy has joined #ocaml
oriba has joined #ocaml
seafood has quit [Quit: seafood]
agarwal1975_ has joined #ocaml
agarwal1975 has quit [Read error: Connection reset by peer]
agarwal1975_ is now known as agarwal1975
oriba has quit [Quit: Verlassend]
edwin has quit [Quit: Leaving.]
edwin has joined #ocaml
Edward has quit []
edwin has quit [Client Quit]
ikaros has quit [Quit: Leave the magic to Houdini]
Edward has joined #ocaml
Morphous has joined #ocaml
Morphous has quit [Changing host]
Morphous has joined #ocaml
tauntaun is now known as tautaun_away_to_
wuj has joined #ocaml
tautaun_away_to_ is now known as tauntaun
ccasin has quit [Quit: Leaving]
Yoric has quit [Quit: Yoric]
Morphous has quit [Quit: shutdown]
Morphous has joined #ocaml
Morphous has quit [Changing host]
Morphous has joined #ocaml
agarwal1975 has quit [Read error: Connection reset by peer]
agarwal1975 has joined #ocaml