adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | Current MOOC: https://huit.re/ocamlmooc | OCaml 4.04.0 release notes: http://ocaml.org/releases/4.04.html | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
unbalancedparen has joined #ocaml
hovind has quit [Ping timeout: 246 seconds]
wtetzner has quit [Remote host closed the connection]
rps_ has joined #ocaml
zpe has quit [Ping timeout: 240 seconds]
<rps_> I ma begiiner. I wrote as simple .ml file containing let a = Printf.printf "Hello, World!" compiled with ocamlc -o hello hello.ml on windows 7. Ran with ocaml hello. I am getting File "hello", line 1, characters 2-3: Error: Illegal character (\144)
<rps_> can somebody help?
<rps_> can't figure out
<jbrown> if you're doing "ocaml hello" to run a binary, that's not right... try just "hello" on its own
mfp has quit [Quit: Leaving]
unbalancedparen has quit [Quit: WeeChat 1.7]
vicfred has quit [Quit: Leaving]
<rps_> with just hello. I get. 'hello' is not recognized as an internal or external command, operable program or batch file.
<jbrown> oh, rename it to hello.exe maybe?
* jbrown guesses.
<jbrown> (I'm not actually sure how bytecode execution works on Windows -- it'd be just ./hello on Linux.)
<rps_> it works! thanks
<jbrown> :-)
<jbrown> np
silver has quit [Read error: Connection reset by peer]
rps_ has quit [Quit: Page closed]
zpe has joined #ocaml
mengu has quit [Quit: Leaving...]
jao has quit [Ping timeout: 260 seconds]
breitenj has quit [Ping timeout: 256 seconds]
breitenj has joined #ocaml
romildo has joined #ocaml
romildo has quit [Quit: Leaving]
madgoat has joined #ocaml
madgoat has left #ocaml [#ocaml]
zpe has quit [Ping timeout: 260 seconds]
pote_ has quit [Ping timeout: 260 seconds]
pote_ has joined #ocaml
frefity has quit [Ping timeout: 260 seconds]
frefity has joined #ocaml
nore has quit [Ping timeout: 260 seconds]
pote_ has quit [Ping timeout: 268 seconds]
frefity has quit [Ping timeout: 260 seconds]
Guest90511 has quit [Ping timeout: 260 seconds]
kandu has joined #ocaml
pote_ has joined #ocaml
tizoc has quit [Ping timeout: 260 seconds]
frefity has joined #ocaml
nore has joined #ocaml
tizoc has joined #ocaml
zpe has joined #ocaml
govg has joined #ocaml
Ayey_ has joined #ocaml
Ayey_ has quit [Ping timeout: 240 seconds]
MercurialAlchemi has joined #ocaml
govg has quit [Ping timeout: 258 seconds]
_whitelogger has joined #ocaml
nomicflux has joined #ocaml
lolisa has quit [Quit: KVIrc 4.9.1 Aria http://www.kvirc.net/]
nomicflux has quit [Quit: nomicflux]
osa1 has joined #ocaml
<osa1> which files should I look at for compilation of pattern matching to flambda? (or whatever IL it's being compiled to?)
_whitelogger has joined #ocaml
Simn has joined #ocaml
Ayey_ has joined #ocaml
gtristan has quit [Ping timeout: 260 seconds]
Ayey_ has quit [Ping timeout: 246 seconds]
gtristan has joined #ocaml
zpe has quit [Ping timeout: 258 seconds]
shinnya has joined #ocaml
hovind has joined #ocaml
Ayey_ has joined #ocaml
slash^ has joined #ocaml
tane has joined #ocaml
Ayey_ has quit [Ping timeout: 240 seconds]
cbot has quit [Quit: Leaving]
Ayey_ has joined #ocaml
Ayey_ has quit [Ping timeout: 268 seconds]
hovind has quit [Ping timeout: 258 seconds]
zpe has joined #ocaml
AlexDenisov has joined #ocaml
jnavila has joined #ocaml
jnavila has quit [Ping timeout: 240 seconds]
jnavila has joined #ocaml
AlexDenisov has quit [Ping timeout: 240 seconds]
AlexDeni_ has joined #ocaml
argent_smith has joined #ocaml
hovind has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 268 seconds]
AlexDenisov has joined #ocaml
AlexDeni_ has quit [Ping timeout: 264 seconds]
minn has quit [Ping timeout: 240 seconds]
flacko has joined #ocaml
<flacko> What is the >|= operator?
<mrvn> whatever you declare it to be
<mrvn> Error: Unbound value >|=
<mrvn> WTF? # ( >=? );;
<mrvn> Hint: Did you mean >=?
<mrvn> Error: Unbound value >=?
<flacko> And it puzzles me
<flacko> By the way, is there simple rest framework? Webmachine and eliom made me pull my hairs out
<mrvn> lwt defines a few operators so you can string operations together.
jnavila has quit [Quit: It was time]
frefity has quit [Ping timeout: 260 seconds]
zpe has quit [Ping timeout: 260 seconds]
frefity has joined #ocaml
freechips has joined #ocaml
govg has joined #ocaml
jnavila has joined #ocaml
_whitelogger has joined #ocaml
flacko has quit [Quit: WeeChat 0.4.2]
osa1 has quit [Ping timeout: 258 seconds]
jnavila has quit [Quit: It was time]
silver has joined #ocaml
zpe has joined #ocaml
kakadu has joined #ocaml
govg has quit [Read error: Connection reset by peer]
kakadu has quit [Remote host closed the connection]
average has quit [Remote host closed the connection]
average has joined #ocaml
govg has joined #ocaml
romildo has joined #ocaml
<romildo> How can one define the fix data type constructor in Ocaml?
<romildo> The definition in Haskell is:
<romildo> newtype Fix f = Fx (f (Fix f))
<rightfold> romildo: You need higher-kinded types for this.
<romildo> Ok. Now I have remembered that this question has been asked before and I have found a link to it: http://stackoverflow.com/questions/12995044/fix-data-type-in-ocaml
haesbaert has quit [Remote host closed the connection]
MercurialAlchemi has joined #ocaml
gtristan has quit [Ping timeout: 240 seconds]
<mrvn> What Is Fx?
<rightfold> It's an abstraction that implements type recursion
<rightfold> It is used for recursion schemes among other things
<mrvn> So not a Constructor.
<rightfold> In pseudo-OCaml (with HKTs) it would look like type f Fix = Fx of (f Fix) f
<mrvn> No, that would be a constructor then.
<rightfold> type 'f fix = Fx of ('f fix) 'f actually
<rightfold> It's early
<mrvn> A Constructor doesn't do any evaluation and it seems you want to evaluate (f (Fix f)) to produce the type. Thats Functor territory.
<rightfold> For example
tweek__ has left #ocaml [#ocaml]
<rightfold> type ('a, 'b) list_f = Nil | Cons of 'a * 'b
zpe has quit [Ping timeout: 258 seconds]
<mrvn> I think the stackoverflow answere is best
slash^ has quit [Quit: Leaving]
<rightfold> type 'a list = ('a list_f) fix (* assume partial type application *)
gtristan has joined #ocaml
octachron has joined #ocaml
frefity has quit [Ping timeout: 240 seconds]
hovind has quit [Ping timeout: 268 seconds]
frefity has joined #ocaml
Anarchos has joined #ocaml
zpe has joined #ocaml
toolslive has quit [Ping timeout: 240 seconds]
toolslive has joined #ocaml
slash^ has joined #ocaml
tane has quit [Quit: Leaving]
<zozozo> type are naturally recursive in ocaml so while you can't express the fixpoint combinator for types in ocaml, I do belive you can manaully define any type it could, or am I missing something ?
minn has joined #ocaml
pilne has joined #ocaml
<rightfold> You can define recursive types, yes.
<rightfold> But abstractions like recursion schemes are more tricky.
<rightfold> e.g. bottom_up (fu : 'a functor) (f : 'a fix -> 'a fix) (x : 'a fix) : 'a fix = f (Fx (fu.map (bottom_up f) (un_fx x)))
<rightfold> where type 'f functor = {map : ('a -> 'b) -> 'a 'f -> 'b 'f} :')
Anarchos has quit [Quit: Vision[0.9.8]: i've been blurred!]
_y has quit [Ping timeout: 260 seconds]
Fistine has quit [Ping timeout: 246 seconds]
govg has quit [Quit: leaving]
govg has joined #ocaml
tobiasBora has quit [Ping timeout: 268 seconds]
FreeBirdLjj has joined #ocaml
Muzer has quit [Ping timeout: 256 seconds]
_y has joined #ocaml
tobiasBora has joined #ocaml
Fistine has joined #ocaml
romildo has quit [Quit: Leaving]
shinnya has quit [Ping timeout: 258 seconds]
spew has joined #ocaml
Muzer has joined #ocaml
argent_smith has quit [Ping timeout: 256 seconds]
zpe has quit [Ping timeout: 256 seconds]
FreeBird_ has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 260 seconds]
fraggle_ has joined #ocaml
argent_smith has joined #ocaml
argent_smith has quit [Ping timeout: 240 seconds]
argent_smith has joined #ocaml
Simn has quit [Ping timeout: 260 seconds]
haesbaert has joined #ocaml
slash^ has quit [Read error: Connection reset by peer]
wtetzner has joined #ocaml
zpe has joined #ocaml
richi235 has quit [Remote host closed the connection]
copy` has joined #ocaml
shinnya has joined #ocaml
spew has quit [Ping timeout: 240 seconds]
Simn has joined #ocaml
spew has joined #ocaml
AlexDenisov has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
nomicflux has joined #ocaml
minn has quit [Ping timeout: 264 seconds]
FreeBird_ has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
shinnya has quit [Ping timeout: 240 seconds]
FreeBird_ has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 256 seconds]
spew has quit [Ping timeout: 240 seconds]
slash^ has joined #ocaml
nomicflux has quit [Quit: nomicflux]
<lapinot> hi, i'm looking for a way to parametrize menhir rules by arbitrary ocaml values (a bit like what is possible in ocamllex). I know this has not a lot of sense since menhir rules aren't ocaml functions at all but what i want to express is an infinite family of rules (going another level up, i want to do typed parsing: int_expr is easy, just like bool_expr but fun_a_b_expr can't really be expressed)
<lapinot> this is maybe impossible with menhir, maybe i should look for a parser combinator instead of a grammar-based parser generator
<Drup> lapinot: you can functorize menhir parsers
<Drup> I think the documentation describes that
gniquil has joined #ocaml
gniquil has quit [Client Quit]
<lapinot> Drup: indeed (i have already used that feature in the past) but rules in one instanciated parser cannot call rules from another
<Drup> I just read the thing in parens ...
<Drup> don't mix type checking and parsing.
<Drup> parse first, then typecheck
<Drup> generating typed expressions is exactly equivalent to do typechecking, and you will not manage to do that with a parser (especially a LR(1) one)
zpe has quit [Ping timeout: 258 seconds]
FreeBird_ has quit [Remote host closed the connection]
mengu has joined #ocaml
FreeBirdLjj has joined #ocaml
<mrvn> Drup: you can do a lot. For me the question is more if you should. Should "1 + 0.5" give a parse error at the "." or is it better to parse that and give a type error on "1.5"?
<lapinot> Drup: maybe you're right.. i was thinking of doing this in one step because i'm not implementing any type inference but only leveraging the one of the host language (ocaml) by representing the AST with a gadt (thus constructing an ast is equivalent to letting ocaml check that everything is well-typed)
<lapinot> mrvn: you're example is quite enlightening, i'll think about that
<lapinot> note: now i'm looking into camlp4's stream-parsing extension to build a simple recursive descent parser
<Drup> lapinot: but you *are* doing typechecking as soon as you have a transformation from untyped data to typed data
<Drup> and text is very much an untyped data
<mrvn> lapinot: Note that it is verry simplified. Normaly you would tokenize this into "int literal" "int op" "float literal" so you would still be able to report that "float literal 1.5" was wound where "int" was expected
<mrvn> s/wound/found/
<Drup> trying to make that fit in a parser in general is going to cause your more headache than anything. Using an handwritten parser will not really help you.
nicoo has quit [Remote host closed the connection]
cbot has joined #ocaml
<Drup> The only sensible method is to parse an untyped AST and then typecheck it into your typed AST.
nicoo has joined #ocaml
<mrvn> lapinot: you can do all the type checking during parsing but anything non trivial will have to allow for some unchecked intermediate states and then go up and down the AST to refine it. For example when you parse "fun f -> f a b" the types only become clear as you build the term up.
<mrvn> lapinot: but do you want your type checking and intference split up all through your parser?
marsam has joined #ocaml
<mrvn> either way I wish you luck. Personally I'm still undecided on it. I started experimenting with a GADT typed grammar 2 years ago but then run out of spare time.
<mrvn> Never got to the interesting things like value restrictions and such.
<Drup> yeah, that's because it's mostly a bad idea
<lapinot> Drup: indeed, that would be typechecking, but my point was that anyway typechecking is mostly a one-liner since i'm letting caml do it, thus it would make some sense to compress it
<Drup> lapinot: you are only letting OCaml do it because you currently only write your AST in OCaml
<Drup> so the "typechecking" is compile time
<Drup> you can't move that typechecking to runtime, which is what you need if you have a parser
<Drup> so, no, you can't use a one-line typechecking algorithm "I'll just use OCaml" now. ;)
<mrvn> lapinot: you won't get around cases of 'match foo with Int x -> ... | _ -> printf "type error\n"' to do runtime checks.
<lapinot> Drup: actually you can use ocaml's compile time typechecking at runtime with some clever tricks using GADTs and what haskell calls "phantom types"
<Drup> No you can't :)
<octachron> another point is how much parsing generater tool can accommodate the extensive type annotations needed for GADTs
<mrvn> lapinot: WHat you get out of the GATDTs is that the parse can never return an expression for "1 + 1.5"
<Drup> lapinot: phantom types only give you the garantee that the typed data is well formed (and that transformation over this data preserves the well formedness)
<Drup> it doesn't give you *any* runtime type checking capabilities
<Drup> (first and foremost because, by definition of phantom types, they don't exists at runtime)
<mrvn> Drup: you can turn a lot of type checks into parse errors though since the grammar will simply not accept wrong types.
<Drup> mrvn: except if you do that, you get a highly contextual grammar
<Drup> you are not making that fit in menhir, and the parser will be insane, if you ever manage to do that
<mrvn> Drup: nah, just a huge one.
<mrvn> you can't type check everything but LR(1) allows a lot already.
<Drup> mrvn: not with an infinte type universe
<Drup> (which you have as soon as you have tuples, so good luck)
<mrvn> sure it does. it still allows a lot even with an infinte type universe
<Drup> mrvn: have you actually tried on paper ?
<mrvn> Drup: I tried in ocaml
<Drup> link please :p
<lapinot> indeed, i need to precise that i wouldn't have any typedef statement and i could even add the condition that function arguments should be hinted (this project is only me having a basic assignement and doing some extensions to it because it's fun)
<mrvn> nothing public. But surely you can see that you can write your grammar so that "+" only accepts int, 'a or '_a expressions and transforms them to int expression.
<Drup> mrvn: because + is too simple. Try generic function calls.
<mrvn> Drup: did you miss the part about "you can't do it all"?
<Drup> "(19:31:37) mrvn: lapinot: you can do all the type checking during parsing but anything non trivial will have to allow for some unchecked intermediate states"
<Drup> so, no, you can't.
<mrvn> Drup: that wasn't about encoding the types in the grammar. That was about manually checking types while you parse.
<Drup> please stop saying things that are right only in your tiny example case.
<Drup> (and with ugly hacks)
<mrvn> Drup: please stop trying to disprove a "works for some cases" by showing examples of where it doesn't
<Drup> lapinot: as someone who wrote quite some amount of GADT code, the things to remember are the following: 1) don't mix steps, moving from untyped data to typed data is the hardest part of most GADT stuff 2) don't try to encode complicated properties in your GADT, the complexity of the encoding grows far too fast 3) don't use GADTs for real-world languages, it does not scale :p
<Drup> GADTs are nice for small DSLs and to encode specific properties, in a way that doesn't invade all the program too much (for example, compact arrays in the style of https://blogs.janestreet.com/why-gadts-matter-for-performance/)
zpe has joined #ocaml
hongbo has joined #ocaml
sh0t has joined #ocaml
marsam has left #ocaml ["Killed buffer"]
richi235 has joined #ocaml
TheLemonMan has joined #ocaml
AlexDenisov has joined #ocaml
<rightfold> Don't make grammars context-sensitive. It's always unconditionally bad.
FreeBirdLjj has quit [Remote host closed the connection]
FreeBirdLjj has joined #ocaml
zpe has quit [Ping timeout: 240 seconds]
jmiven has quit [Quit: co'o]
jmiven has joined #ocaml
FreeBird_ has joined #ocaml
FreeBirdLjj has quit [Ping timeout: 246 seconds]
FreeBird_ has quit [Read error: Connection reset by peer]
FreeBirdLjj has joined #ocaml
richi235 has quit [Remote host closed the connection]
baboum has joined #ocaml
flupe has joined #ocaml
AlexDeni_ has joined #ocaml
AlexDenisov has quit [Ping timeout: 240 seconds]
flupe has quit [Quit: Leaving]
slash^ has quit [Remote host closed the connection]
cbot has quit [Ping timeout: 240 seconds]
zpe has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 240 seconds]
baboum has quit [Quit: Leaving]
FreeBirdLjj has quit [Read error: Connection reset by peer]
FreeBirdLjj has joined #ocaml
FreeBirdLjj has quit [Remote host closed the connection]
argent_smith has quit [Quit: Leaving.]
TheLemonMan has quit [Quit: "It's now safe to turn off your computer."]
octachron has quit [Quit: Leaving]
zpe has quit [Ping timeout: 260 seconds]
gtristan has quit [Ping timeout: 260 seconds]
strykerkkd has joined #ocaml
wtetzner has quit [Remote host closed the connection]
wtetzner has joined #ocaml
wtetzner has quit [Read error: Connection reset by peer]
baboum has joined #ocaml
baboum has quit [Client Quit]
silver_ has joined #ocaml
zpe has joined #ocaml
silver has quit [Ping timeout: 240 seconds]
AlexDeni_ has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
sh0t has quit [Remote host closed the connection]
silver_ has quit [Quit: rakede]
pzp has joined #ocaml
zpe has quit [Ping timeout: 240 seconds]
jao has joined #ocaml
nomicflux has joined #ocaml
nomicflux has quit [Client Quit]
jao has quit [Remote host closed the connection]
Simn has quit [Quit: Leaving]
nomicflux has joined #ocaml
nomicflux has quit [Client Quit]
rpip has joined #ocaml
Guest87589 has joined #ocaml
nore has quit [Ping timeout: 256 seconds]
Guest87589 has quit [Quit: (www.nnscript.com :: NoNameScript 4.22 :: www.esnation.com)]
Soni has quit [Ping timeout: 260 seconds]
cbot has joined #ocaml
Soni has joined #ocaml
zpe has joined #ocaml