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
lgd_ has joined #ocaml
demonimin has quit [Read error: Connection reset by peer]
lgd_ has left #ocaml [#ocaml]
lgd has joined #ocaml
smondet has joined #ocaml
freusque has quit [Ping timeout: 240 seconds]
nomicflux has quit [Quit: nomicflux]
wtetzner has joined #ocaml
freusque has joined #ocaml
djin has joined #ocaml
yomimono has joined #ocaml
ollehar has quit [Quit: ollehar]
Sorella has quit [Quit: Connection closed for inactivity]
yomimono has quit [Ping timeout: 255 seconds]
KV has joined #ocaml
KV has quit [Ping timeout: 246 seconds]
smondet` has joined #ocaml
smondet has quit [Ping timeout: 255 seconds]
jbrown has quit [Ping timeout: 240 seconds]
wtetzner has quit [Remote host closed the connection]
wtetzner has joined #ocaml
jbrown has joined #ocaml
djin has quit [Quit: Leaving.]
silver has quit [Read error: Connection reset by peer]
<LACampbell> is there anyway to parameterise an array by its length? like C++'s std::array
<LACampbell> or write a module that does it, I mean
<LACampbell> I think GADTs *may* be what I am looking for, but I am not sure
<Drup> LACampbell: depends, what do you want to do with the lenght ?
KV has joined #ocaml
<LACampbell> Drup: well for example with a C++ std::array<int, 2>, it will complain if you try and construct it with 3 elements at compile time
<Drup> So, yes, you can do that. I would advise against it
<LACampbell> why?
<LACampbell> and how? :D
<Drup> (it's very painful to use and will probably cause you more headaches than good, unless you really have good reasons)
<LACampbell> it's a modelling thing
wtetzner has quit [Remote host closed the connection]
<LACampbell> I;m dying to know though, how do you accomplish this?
KV has quit [Ping timeout: 246 seconds]
<Drup> LACampbell: I guess you will also want to express the fact that concatenation adds the length ?
<LACampbell> Drup: not at this point. I'm trying to model vector spaces. mainly for educational purposes. not sure if you're familiar with it.
djin has joined #ocaml
<LACampbell> I have a functor that takes a field module and makes a vector space.
<LACampbell> but would like to encode the length
<Drup> I see, and you want to encode dimenssions
<LACampbell> yes
<Leonidas> flux: there is users.profile.get now (they implemented it sometime later) which has the user info
ziyourenxiang has joined #ocaml
<Drup> So, if you don't care about concatenation, this could do: https://bpaste.net/show/722f7e58ec6e
<Drup> Otherwise, you need one more type index. This work better on lists, but it's also doable on arrays with phantom types, see this for the general technique: http://drup.github.io/2016/08/02/difflists/
<Drup> Finally, there is an ocaml lib that uses that kind of stuff to provide type safe bindings for BLAS: http://akabe.github.io/slap/
sz0 has quit [Quit: Connection closed for inactivity]
<LACampbell> Drup: but there's nothing constraining the parameter 'n' in make on line 19, is there?
<LACampbell> the 'n could be something completely different from the n
<LACampbell> checking out the second link now
<Drup> LACampbell: we suppose "int_of_num" is correct :)
<Drup> (it's quite hard to get it wrong, honestly :D)
<LACampbell> hmmmm
<LACampbell> right, so by defining ints that way, you make it impossible to use the wrong n
<Drup> yes, because with unary integers, you can track them at the type level
djin has quit [Quit: Leaving.]
<Drup> You should probably look at slap, it's in the same field (ah!) as what you want to do
<LACampbell> Drup: I figured someone would have already done it before, but I wanted to try it a bit blind, building it up piece by piece
<Drup> sure
<LACampbell> Drup: how do you create a num?it's a GADT right?
<Drup> let three = S S S Z
<Drup> (with more parens)
<LACampbell> ahhh
<LACampbell> it's very cool but at the same time not really as expressive as what C++ does. which sucks because C++ is a pain to use
nomicflux has joined #ocaml
KV has joined #ocaml
KV has quit [Ping timeout: 272 seconds]
jbrown has quit [Ping timeout: 240 seconds]
lgd has quit [Ping timeout: 248 seconds]
jbrown has joined #ocaml
al-damiri has quit [Quit: Connection closed for inactivity]
copy` has quit [Quit: Connection closed for inactivity]
teknozulu has joined #ocaml
jlongster has joined #ocaml
LACampbell has quit [Ping timeout: 245 seconds]
mfp has quit [Ping timeout: 240 seconds]
KV has joined #ocaml
d0nn1e has quit [Ping timeout: 258 seconds]
d0nn1e has joined #ocaml
KV has quit [Ping timeout: 245 seconds]
jlongster has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
LACampbell has joined #ocaml
infinity0 has quit [Ping timeout: 272 seconds]
infinity0 has joined #ocaml
infinity0 has quit [Remote host closed the connection]
gjaldon has joined #ocaml
infinity0 has joined #ocaml
jao has quit [Ping timeout: 258 seconds]
infinity0 has quit [Remote host closed the connection]
infinity0 has joined #ocaml
KV has joined #ocaml
jbrown has quit [Ping timeout: 240 seconds]
KV has quit [Ping timeout: 248 seconds]
teknozulu has quit [Read error: Connection reset by peer]
nomicflux has quit [Quit: nomicflux]
jbrown has joined #ocaml
pierpa has quit [Ping timeout: 255 seconds]
moei has quit [Read error: Connection reset by peer]
moei has joined #ocaml
Muzer has quit [Read error: Connection reset by peer]
ohama has quit [Ping timeout: 248 seconds]
NJBS has quit [Quit: Catastrophic failure.]
KV has joined #ocaml
ohama has joined #ocaml
govg has quit [Ping timeout: 246 seconds]
KV has quit [Ping timeout: 256 seconds]
nicoo has quit [Remote host closed the connection]
nicoo has joined #ocaml
Muzer has joined #ocaml
gjaldon has quit [Remote host closed the connection]
gjaldon has joined #ocaml
jbrown has quit [Ping timeout: 240 seconds]
govg has joined #ocaml
jbrown has joined #ocaml
KV has joined #ocaml
KV has quit [Ping timeout: 240 seconds]
gjaldon has quit [Remote host closed the connection]
gjaldon has joined #ocaml
MercurialAlchemi has joined #ocaml
gjaldon has quit []
govg has quit [Ping timeout: 248 seconds]
govg has joined #ocaml
KV has joined #ocaml
KV has quit [Ping timeout: 248 seconds]
afk is now known as awal
pyx has joined #ocaml
pyx has quit [Client Quit]
jbrown has quit [Ping timeout: 240 seconds]
jbrown has joined #ocaml
kakadu has joined #ocaml
freusque has quit [Quit: WeeChat 1.4]
KV has joined #ocaml
KV has quit [Ping timeout: 246 seconds]
sh0t has joined #ocaml
Simn has joined #ocaml
govg has quit [Ping timeout: 240 seconds]
KV has joined #ocaml
slash^ has joined #ocaml
KV has quit [Ping timeout: 248 seconds]
jnavila has joined #ocaml
govg has joined #ocaml
demonimin has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 248 seconds]
silver has joined #ocaml
jbrown has quit [Ping timeout: 240 seconds]
jnavila has quit [Ping timeout: 240 seconds]
jbrown has joined #ocaml
mfp has joined #ocaml
jnavila has joined #ocaml
KV has joined #ocaml
<companion_cube> well, the type system of OCaml has lots of good properties; C++ is very powerful but templates are actually more macros than a type feature
<flux> macros with good hygiene, can be defined in the same stage of compilation, can work with the type information..
<companion_cube> yes, yes, macros on the AST, not the text
<companion_cube> it's much better than C macros
<companion_cube> but still, it's not part of the type system itself
snhmib has joined #ocaml
<flux> you can have templates inside structs/classes, they are part of function signature search.. what would it mean if they were "part of the type system itself"?
<companion_cube> pre-checking constraints on the template parameters
<companion_cube> but ok, it's not too clear cut, you're right
<companion_cube> I believe template instanciation is mutually recursive with type checking anyway
<companion_cube> because of overloadings adn this kind of things
<companion_cube> (and specialization)
<flux> but even that's pretty much there because SFINAE, so if a search fails then it can merrily continue searching elsewhere. not "pre-checking" but "during checking" :)
<companion_cube> anyway, rust's approach is cleaner imho, albeit a bit less powerful
<flux> just last week I had this one encounter with C++
<flux> we had this Optional class, pretty much 'a option, that has operator* for dereferencing and operator bool() for checking if there's a value
<companion_cube> did you specialize it for pointer types?
<flux> it turns out that you can use an instance of Optional<T> wherever you would use bool, char, int, double.. because operator bool() makes it castable into bool and those other types (double as well!) can be casted from bool
<flux> I did not, its normal use case is with value types. I mena, with pointers you could just use.. pointers.
<companion_cube> ah right, I was thinking in terms of traits
<companion_cube> (rust)
<flux> that problem was fixed by having a non-implemented template <typename U> operator U(); so now it worked with bool casting ok, and other casts blow a horrible error ;)
<companion_cube> hmm, so you explicitely write the cast to any other type, is that it?
<companion_cube> but without implementing it
<flux> yes
<flux> so the template is chosen for every other case but the explicit bool
<companion_cube> nice
lgd has joined #ocaml
<companion_cube> so this is a use case of SFINAE?
<flux> not really
<flux> maybe if there were multiple similar ways to get to the value and some of them worked and some didn't
<flux> but in this case the bool is preferred because it's explicit
<companion_cube> ah right, you do get an error if you use optional instead of int
KV has quit [Ping timeout: 272 seconds]
octachron has joined #ocaml
MercurialAlchemi has joined #ocaml
AlexDenisov has joined #ocaml
jnavila has quit [Ping timeout: 240 seconds]
AlexDeni_ has joined #ocaml
AlexDenisov has quit [Ping timeout: 240 seconds]
sepp2k has joined #ocaml
jbrown has quit [Ping timeout: 240 seconds]
govg has quit [Ping timeout: 240 seconds]
tmtwd has joined #ocaml
jbrown has joined #ocaml
bigs_ has quit [Ping timeout: 240 seconds]
mattg has quit [Ping timeout: 246 seconds]
Sorella has joined #ocaml
beaumonta is now known as abeaumont
KV has joined #ocaml
noddy has joined #ocaml
KV has quit [Ping timeout: 240 seconds]
sepp2k has quit [Ping timeout: 248 seconds]
noddy has quit [Ping timeout: 240 seconds]
sepp2k has joined #ocaml
noddy has joined #ocaml
KV has joined #ocaml
noddy has quit [Ping timeout: 248 seconds]
jbrown has quit [Ping timeout: 240 seconds]
govg has joined #ocaml
Xadnem has joined #ocaml
noddy has joined #ocaml
jbrown has joined #ocaml
nomicflux has joined #ocaml
mattg has joined #ocaml
bigs_ has joined #ocaml
noddy has quit [Quit: WeeChat 1.6]
tane has joined #ocaml
erider has joined #ocaml
erider has quit [Remote host closed the connection]
omarramo has joined #ocaml
<omarramo> hey guys, I wanted to ask what let () = does
<companion_cube> `let () = foo` evaluates `foo` and matches its output with `()`
<companion_cube> by typing, it always works
<companion_cube> (but required `foo:unit`)
<companion_cube> requires*
<companion_cube> you might see `let () = foo in bar` instead of `foo; bar` sometimes
<omarramo> what do you mean by matches its output with ()?
<companion_cube> well, `let x = y` accepts patterns for `x`, not just a single variable
<companion_cube> `let (x,y) = (1,2) in …` for example
<companion_cube> but for `let () = foo in …`, the only value foo:unit can have is ()
<omarramo> I am asking because I saw it in the code at the bottom of this site: https://ocaml.org/learn/tutorials/file_manipulation.html
<omarramo> what is it needed for here specifically?
<companion_cube> ah, the toplevel one
<companion_cube> well, it's a bit confusing, indeed
<companion_cube> in OCaml, toplevel statements can only `let`-bindings of the form `let foo = bar`
<companion_cube> (typically, `let foo x y = bar` for functions)
<companion_cube> you can also write any expression, but have to add a `;;` afterwards (and sometimes before) to tell the parser where each statement finishes
<companion_cube> some people (including me) dislike `;;` a lot, so we only write toplevel `let` statements
<companion_cube> for statements that are only useful for their side effects, of type unit, in particular the "main", we write `let () = <main here>`
<companion_cube> we could write `let _ = <main here>` but that would let type errors go through
<omarramo> ah okay, I was wondering why I didn't have to write ';;' after each function in my last homework
<omarramo> but that explains it, thanks a lot
yomimono has joined #ocaml
jlongster has joined #ocaml
jlongster has quit [Client Quit]
lgd has quit [Quit: Leaving.]
tmtwd has quit [Ping timeout: 258 seconds]
cpdean has joined #ocaml
<cpdean> hey everyone, i'm trying to follow the LLVM ocaml tutorial, but the code they provide has syntax errors i'm not able to figure out how to fix http://llvm.org/docs/tutorial/OCamlLangImpl2.html
<cpdean> File "lexer.ml", line 7, characters 2-3:
<cpdean> and that line looks like :
<cpdean> | [< ' (' ' | '\n' | '\r' | '\t'); stream >] -> lex stream
<Drup> gah, someone need to update that tutorial ...
<cpdean> it seems that camlp4 requires ocaml syntax i can't figure out
<cpdean> and camlp4's docs seem to focus more on its own world rather than how to actually build code that runs on a computer
<Drup> yeah, it uses genlex, which relies on a camlp4 syntax extension
<cpdean> is genlex a whole different compiler?
<Drup> no no, it's just a syntax extension/library
<cpdean> ah ok, and the 'camlp4 syntax extension' is like a plugin for OCaml's compiler tools?
<Drup> a syntax extension is just that: something that extends the syntax
<cpdean> gotcha
<cpdean> that's a thing that i've really been struggling with learning ocaml
d0nn1e has quit [Ping timeout: 248 seconds]
unbalanced has joined #ocaml
<cpdean> because does it do that through vanilla ocaml library things? or does it modify the behavior of the tools that compile ocaml code?
<Drup> ah yes, they don't tell you how to build things with this tutorial ...
wtetzner has joined #ocaml
<cpdean> yeah thats the command i run to get the error
<cpdean> "ocamlbuild toy.byte"
<Drup> you have camlp4 installed ?
<cpdean> seems like it
<Drup> huum, not sure :/
<cpdean> which camlp4
<cpdean> /Users/cdean/.opam/4.03.0/bin/camlp4
<cpdean> the `lexer.ml` has ZERO references to campl4 so i suspect the author of this tutorial is leaving out the fact that you have to tell the binary that builds this code to do this in "camlp4 mode" or whatever
<Drup> that's what the _tags file is for
<cpdean> welp.
<cpdean> lets see if adding that fixes this
<cpdean> well what do you know
<cpdean> i completely glossed over _tags because i skimmed and thought it was a ctags file
<cpdean> and of course this tutorial doesn't explain what _tags does
<cpdean> this is the first i've heard of this https://ocaml.org/learn/tutorials/ocamlbuild/Tags.html
<cpdean> thanks Drup!
jbrown has quit [Ping timeout: 240 seconds]
Guest26 has joined #ocaml
shinnya has joined #ocaml
omarramo has quit [Quit: Konversation terminated!]
jbrown has joined #ocaml
Sorella has quit [Quit: Connection closed for inactivity]
lgd has joined #ocaml
lgd has quit [Client Quit]
madroach has joined #ocaml
unbalanced has quit [Ping timeout: 256 seconds]
ocaml834 has joined #ocaml
ocaml834 has quit [Ping timeout: 260 seconds]
jao has joined #ocaml
AlexDeni_ has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
jrslepak has joined #ocaml
silver_ has joined #ocaml
silver_ has quit [Remote host closed the connection]
jbrown has quit [Ping timeout: 240 seconds]
pierpa has joined #ocaml
<flux> so yesterday a colleague decided to dive in OCaml. it was a bit surprising to me that he chose to do it with bucklescript, replacing his previously-in-elm-written piece of code with OCaml.
<flux> (my years of advocacy finally paid off ;-))
jbrown has joined #ocaml
<companion_cube> I don't know what the deal is with bucklescript
<flux> at least he was concinced with the quality of javascript buckescript creates
<flux> I can see how much better it is when let () = print_endline "hello" produced js console.log("hello")
<flux> Printf.printf was a bit more verbose, but not by much
shinnya has quit [Ping timeout: 256 seconds]
<companion_cube> it depends on whether you want to use ocaml as sugar for JS, or JS as runtime for OCaml :-)
<flux> and if you already have a lot of js - which is likely the case for most any web developer - what might be the preferred option?-)
jnavila has joined #ocaml
<Drup> to use js code in OCaml, you are going to need to figure out some typing anyway, and that's the real pain point. All the rest is easy and/or transparent
ziyourenxiang has quit [Quit: Leaving]
yomimono has quit [Ping timeout: 240 seconds]
<flux> regardless of the typing - which I understand is an issue with ie. typescript, elm - having a bit less of black box in between can still feel like a bonus.
<flux> I think the main benefit (and not small one) of js_of_ocaml vs bucklescript is that it can work with directly from byte code not generated for it, right?
<flux> actually he also liked how it generated each module into a separate .js file, instead of one big executable as what elm did
xorpse has joined #ocaml
eikke has joined #ocaml
eikke has quit [Ping timeout: 240 seconds]
jlongster has joined #ocaml
KV has quit [Ping timeout: 255 seconds]
so has joined #ocaml
eikke has joined #ocaml
wtetzner has quit [Remote host closed the connection]
copy` has joined #ocaml
djin has joined #ocaml
omarramo has joined #ocaml
<omarramo> hey guys, what is the := smybol for in ocaml?
octarin has joined #ocaml
<flux> it is an operator that assigns values to references
<flux> let a = ref 42 in a := 55
wtetzner has joined #ocaml
<omarramo> hm okay, what is ; for then? I see it at the end of a line sometimes
<flux> it is sort of an operator as well. it takes the left side, the right side and returns the right side.
<flux> it is usually used to sequence side-effectful code
<omarramo> aahh okay
<omarramo> so basically like cheating
jbrown has quit [Ping timeout: 240 seconds]
<companion_cube> sometimes it's useful :-)
<flux> would be interesting if it were an actual operator. would there be downsides?
<flux> (the benefit of course being the ability to redefine it)
jnavila has quit [Ping timeout: 240 seconds]
<flux> reminds me of the bjarne stroustrup whitepaper on unicode, whitespace and missing whitespace overloading :)
<Drup> flux: well, it has kind of a special meaning, since it's type is 'a -> unit -> unit or unit -> unit -> unit, depending of the -strict-sequence option
<flux> well that would be easy.. but now I realize it would probably be difficult with ie. record value definitions
<octachron> flux, you mean { a= …; b = … }? Context are sufficiently different to distinguish between the two
<reynir> flux: you can write »e1 ;%flux e2« :D
<flux> octachron, but consider this. it's { a = expr ; b = expr } - now if expr can also have ;, there is a conflict in the parser?
<flux> I suppose expressions can even now have ; so that was bad ;-)
<flux> so the record ; has higher importance there
<octachron> flux; another example [(a;b;c)] and [a;b;c]
jbrown has joined #ocaml
<octachron> (and then add (;) l a = a :: l for optimised confusion)
<Drup> "optimised confusion"
<flux> I guess overloading ; wouldn't be that useful, it still wouldn't be applicable to monadic sequencing
AlexDenisov has joined #ocaml
scitesy has joined #ocaml
sepp2k has quit [Quit: Leaving.]
Guest62099 is now known as DanielRichman
<flux> hmm, I've been monitoring my ocaml program's memory usage for a day now
DanielRichman has quit [Quit: leaving]
DanielRichman has joined #ocaml
cpdean has quit [Quit: Leaving.]
<flux> the program uses pulseadio for recording audio, runs fft and correlation on it, and that's basically it (except when it finds what it is looking for it does something more)
<flux> it seemed to consume 880 megabytes of virtual memory. seemed a bit much, but ok, it doesn't seem to go over that
<flux> but then suddenly the memory usage dropped to 450 megabytes :-o
scitesy has quit [Read error: Connection reset by peer]
<adrien> compaction?
<flux> seems like it, just somewhat surprising that it happens so rarely, has so big an effect and that the memory consumption doesn't keep always increasing without it
<adrien> I think it's also because ocaml won't return the memory to the OS even though it perfectly could
<adrien> :P
infinity0 has quit [Remote host closed the connection]
<adrien> you can easily make the runtime print a message when it does the compaction
infinity0 has joined #ocaml
<flux> I guess I'll do that if I'll get any more worried about that ;)
Algebr has joined #ocaml
infinity0 has quit [Remote host closed the connection]
omarramo has quit [Quit: Konversation terminated!]
infinity0 has joined #ocaml
scitesy has joined #ocaml
Anarchos has joined #ocaml
cpdean has joined #ocaml
snhmib has quit [Ping timeout: 255 seconds]
xorpse has quit [Ping timeout: 240 seconds]
michbad has joined #ocaml
nightmared has joined #ocaml
<cpdean> hey does the ocaml community have a consensus on what's the ideal parsing library? so far its looking like Menhir or Camlp4.
<octachron> Camlp4 is not really consensual nor ideal for parsing
<Drup> cpdean: menhir
<cpdean> at the moment they both kinda look like syntax for specifying grammar and out comes a syntax tree
snhmib has joined #ocaml
<Anarchos> dypgen
<Drup> Anarchos: not for regular prog languages. dypgen is for crazy self extensible GLR stuff
<Drup> cpdean: menhir is a really good parser generator, it gives good error messages and if you are used to yacc/bison, you shouldn't have issue with it
<cpdean> this will be my first attempt at writing a language
<cpdean> and first project bigger than thirty lines of ocaml
<Drup> gotta start somewhere :)
<jerith> I usually use something like angstrom, but then I'm usually parsing data rather than code.
<LACampbell> you can write your own tokenizer going char by char like I did. fun but not very productive I guess
<Anarchos> Drup like coq Notations ;)
<Drup> Anarchos: indeed
<Anarchos> Drup i really needed an extensible parser, and i use dypgen to embed it in a functor :)
<Drup> cpdean: just do ocamllex+merlin, there are plenty of examples, it should be easy to start
<Drup> menhir*
<thizanne> (but still do merlin though)
<companion_cube> dypgen can do extensible syntax?
<Drup> companion_cube: that's kind of the point of dypgen
<Drup> doing things like Coq notations
<companion_cube> oh, neat
<cpdean> coq is one of the reasons i wanna get into ocaml
<LACampbell> companion_cube: yeah I much prefer ocamls type system to C++s. except in this one rare case - C++ can have a value as part of a type sig.
<Drup> (GLR parsers are magic)
<cpdean> what is like magic about them? (i'm totally unfamiliar with them)
<Drup> The algorithms are a bit .. hairy ?
<cpdean> oh… so you mean the fact that they work is magic, not they do magic?
<Drup> It does things, and the results are amazing, but while I have decent ideas of how LR and LL parsing works .. GLR .. I have no clue
djin has quit [Quit: Leaving.]
<cpdean> ah yeah i have no idea how LR and LL work, just write the BNF and cross your fingers...
<Drup> menhir with -explain gives you really good error messages when your grammar is ambiguous
<cpdean> oh nice
<cpdean> can you write tests that work with menhir
<cpdean> call into a fn that runs the lexer/parser
<Drup> menhir generates plain OCaml functions that you can call like any other OCaml functions, so you can do whatever you want with them
djin has joined #ocaml
<Drup> LACampbell: having dependent types opens a rather difficult can of worms
djin has quit [Client Quit]
scitesy has quit [Read error: Connection reset by peer]
<LACampbell> Drup: is std::array actually dependently typed? rust does something similar too. I thought dependent typing was some open research problem, and yet C++ has it?!
<companion_cube> (rust does not have dependent types yet)
<companion_cube> C++ does it in a very unprincipled way
<Drup> "types that contains values" ≡ dependent types
<Algebr> LACampbell: you mean like template<typename T, int foo = 5> ?
<LACampbell> Algebr: yeah
<LACampbell> companion_cube: rust arrays have a length as part of the type parameter. what is that then?
<Drup> (and yes, C++ has pretty much all the types features under the sun, in a big ball of unprincipled half checked mess)
<companion_cube> it's a builtin
<Algebr> if you think that then you could say C stack arrays are dependtly typed, since int foo[5] would be part of the type?
<Drup> You can't compute with it, no ?
<Drup> Algebr: the integers is not part of the type
<Drup> int* is the type of foo
<LACampbell> huh? so std:array<int, 5> is not actually a different type to std::array<int, 4> ?
<LACampbell> companion_cube: what's a built in?
jlongster has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
<Algebr> Drup: no, I'm pretty sure that the type of foo is array of length 5 there
<companion_cube> I mean the compiler treats it specially
<companion_cube> same as arrays in Go
<octachron> (Drup, are you implying that you do not want to play tetris with your type system?)
cpdean has quit [Quit: Leaving.]
snhmib has quit [Ping timeout: 255 seconds]
pon1980 has quit [Quit: WeeChat 1.6]
<Drup> Algebr: it's part of the syntax, but it's not part of the semantics
<LACampbell> companion_cube: in rust or C++? are you saying that it's some magic thing you can't create yourself?
<companion_cube> yes, exactly
<companion_cube> (in rust)
<Drup> if you write void foo (a : int[4]) { ... }, nothing will checks that a is of size 4
<companion_cube> they plan to have type-level integers, but for now it's only for arrays
<Drup> (in C, not C++, I barelly know C++)
<companion_cube> same as, in go you have slices of T, but cannot parametrize your own types
<companion_cube> (meaning Go has no generics)
<Drup> int[n] for type expressions is equivalent to int[] which is equivalent to int*
<LACampbell> Drup: in C++ it will check
<LACampbell> using std::array
<Drup> LACampbell: yes, but not with int[n], no ?
<LACampbell> not sure how but it does
cpdean has joined #ocaml
<LACampbell> so basically - in rust its built in magic, in C++ its dependent typing but done badly?
<LACampbell> Drup: yeah, that's correct
<Drup> since the check is purely template metprogramming voodoo
<companion_cube> I don't really know if C++ does dependent typing "badly", but it's a very very complicated system
<companion_cube> and type checking is a bit unorthodox :D
<companion_cube> I wouldn't bet a cent on its soundness
snhmib has joined #ocaml
<octachron> companion_cube, can a turing-complete type system be sound?
<LACampbell> hmm. so the best way to do it in ocaml is to do church encoding, like Drup showed me yesterday
<octachron> LACampbell, if you want binary encoding, it is also possible but a lot more complex
<companion_cube> not sure
<companion_cube> that's why most dependent languages try to have a notion of terminating computation ^^
<Drup> octachron: even with terminating expressions ...
<LACampbell> actually I think I could do the same thing in ocaml if I had macros
<Drup> It's hard to talk about soundness in a language where you can cast to and from void*
<LACampbell> Drup: I miss that feature in ocaml. not that I'd use it all the time, but still.
<Drup> LACampbell: in slap, they have a little syntax extensions
<octachron> LACampbell, macros to compute the S(…(S(…)…) encoding?
<Algebr> Drup: asked in the C channel, foo is int[5] with reference to c11 6.3.2.1p3
<companion_cube> but foo is convertible immediately to int*, isn't it?
<Algebr> it decays to int*
<companion_cube> yeah
<companion_cube> it only matters when you allocate on the stack
<Drup> Algebr: is there any check whatsoever on the lenght on the array, be it dynamic or static ?
<Algebr> but I think the number is part of the signature so that sizeof works
<companion_cube> C is such a minefield :/
<Drup> but if it's not checked, it's always bogus, so what's the point of adding it for sizeof ?
wtetzner has quit [Remote host closed the connection]
<LACampbell> http://ideone.com/lutSZp this fails at compile time in C++, which I thought was fairly impressive
<LACampbell> Drup: in C? not really
<LACampbell> not once you pass it into a function
<LACampbell> my solution is to make my own structs with a raw C array and a length, and use that exclusively
jbrown has quit [Ping timeout: 240 seconds]
<Drup> LACampbell: of course, I'm explaining to Algebr what I mean by "The length is not part of the type"
<LACampbell> octachron: I more meant macros to take a "3" and convert it to some adt "Three". though I am not sure what the situation for macros is like in Ocaml
<Drup> LACampbell: you can write that in a ppx
Onemorenickname has joined #ocaml
<octachron> LACampbell, if you want to fail at compile time whatever is the price in term of complexity, I think tensority is quite good: https://github.com/Octachron/tensority
larhat has joined #ocaml
<Drup> oh, you added the 'i' suffix for integers, nice :D
<octachron> I would not advise to use it in its current state, however
<Drup> octachron: this code example is so full of hack, it's fabulous
<octachron> Drup, not for integer … for indices, because I have a different kind for size integer
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
<LACampbell> octachron: looks really cool
<LACampbell> ppx seems like the way to go
<Drup> octachron: you should package nat (with the int ppx) in a standalone package
<octachron> Drup, yeah, this example could be entitled "don't look at the types if you still have SAN poin lefts"
<Drup> oh no, this is highly amusing
freusque has joined #ocaml
jbrown has joined #ocaml
<Drup> oh, but you can't really write additions with that
<octachron> Drup, no indeed. The last time that I tried to combine binary representation + addition, I ended up at https://github.com/Octachron/rational_in_types
calculemus has joined #ocaml
<octachron> and then stopped, because 838 line of types for one line of code was a little bit too much
<Drup> "Only 3 bits fixed-precision integers are implemented, it is not clear how much further the OCaml compiler can be tortured by adding more bits." :D
<Algebr> Why does Random.bits only give 30 bits and not 31?
<copy`> Algebr: I'd guess it's intended to generate positive numbers
<Algebr> oh derp, so one bit is eaten up for parity I guess
cpdean has quit [Quit: Leaving.]
<def`> C++ is an open research problem (but very badly stated)
<def`> (arf, stuck in backlog :()
larhat has quit [Quit: Leaving.]
<copy`> Algebr: One bit is eaten to distinguish pointers and integers and the other bit is eaten for the sign
<companion_cube> def`: :D
<Algebr> yea, was wondering about that 31st bit
<thizanne> def`: you're never too late when you bitch about C++
<jerith> I once had a traumatic experience with C++ and I've avoided it ever since.
slash^ has quit [Read error: Connection reset by peer]
<Algebr> I like C++
<jerith> (The traumatic experience was mostly not C++'s fault.)
cpdean has joined #ocaml
average has quit [Quit: leaving]
average has joined #ocaml
Xadnem has quit [Quit: leaving]
larhat has joined #ocaml
Guest26 has quit [Read error: Connection reset by peer]
RonnieHolm has joined #ocaml
RonnieHolm has quit [Quit: ERC Version 5.3 (IRC client for Emacs)]
<LACampbell> def`: oh come on C++ isn't so bad. Just ignore 75% of the language and finely hone your work arounds for the 25% you do use. this shouldn't take you more than 5 years.
ronnie has joined #ocaml
ronnie has quit [Remote host closed the connection]
RonnieHolm has joined #ocaml
AlexDenisov has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
AlexDenisov has joined #ocaml
AlexDenisov has quit [Client Quit]
AlexDenisov has joined #ocaml
AlexDenisov has quit [Client Quit]
AlexDenisov has joined #ocaml
AlexDenisov has quit [Client Quit]
jbrown has quit [Ping timeout: 240 seconds]
jao has quit [Remote host closed the connection]
RonnieHolm has quit [Remote host closed the connection]
kakadu has quit [Remote host closed the connection]
jbrown has joined #ocaml
jao has joined #ocaml
<milodavis> Does anyone have any idea why Eliom would return a 404 error on all pages? Is this an exception handling behavior? If so, how do I see the exception?
<Drup> Have you looked at the logs ?
<Drup> (and/or enable debug mode in Makefile.option)
<milodavis> I've enabled debug mode which doesn't tell me much other than that I am requesting a page. Which logs should I be looking at?
<milodavis> I've checked the logs and don't see anything obviously wrong
<milodavis> Is there a way to list the URLs that are configured?
<Drup> I don't remember one :/
<Drup> Did you properly registered your services and all that ?
<milodavis> Drup: I think so. Here's the link to the repository https://github.com/MiloDavis/scouting
<milodavis> There should only be one service registered at the root of the domain
<Drup> that should answer over /
<Drup> try removing the "", to get the behavior you want
<milodavis> Drup: Still nothing
<Drup> ok, give me a few minute to install core and base, so that I can test ...
<milodavis> Thanks. I'm using the dev version of Base to fix a bug they had in the last release
<Drup> huh
Onemorenickname has quit [Ping timeout: 240 seconds]
fantasticsid has joined #ocaml
<milodavis> Drup: Sorry...
P4Titan has joined #ocaml
jlongster has joined #ocaml
<P4Titan> Hi all
<Drup> it's ok, I just removed config.eliom and the whole dependency
<P4Titan> I'm using lwt, and I created a thread
<P4Titan> is there a way to duplicate this thread
<P4Titan> and run the two with join
<Drup> P4Titan: You can, but there is little point. What are you really trying to achieve ?
octachron has quit [Quit: Leaving]
<orbitz_> I can never remember this: what's the proper way to handle the unbound type variable error when you have an open polymorphic variant/
<Drup> milodavis: I'm extremely confused
<Drup> please open a bug report
<milodavis> Will do. Any ideas on how to make the example more minimal?
<P4Titan> Drup: Each thread is a client to a server
<P4Titan> and I would like to spawn multiple
<Drup> milodavis: just remove config.eliom[i]
<Drup> P4Titan: how do you spawn it ?
<milodavis> Drup: Will do
<P4Titan> Lwt_io.with_connection sockaddr client_handler
<P4Titan> client_handler is a function of mine
<Drup> P4Titan: then wrap that in a function, and call that multiple time
fantasticsid has quit [Remote host closed the connection]
<Drup> There is no real notion of cloning for lwt promises that would duplicate the work
snhmib has quit [Ping timeout: 245 seconds]
<P4Titan> aye
<P4Titan> I just wrapped it, and all is dandy
<P4Titan> thanks! I tried searching but got nothing meaningful for the cloning
<P4Titan> of promises
Onemorenickname has joined #ocaml
snhmib has joined #ocaml
orbitz_ has quit [Quit: Reconnecting]
Algebr has quit [Ping timeout: 255 seconds]
orbitz has joined #ocaml
tane has quit [Quit: Leaving]
larhat has quit [Quit: Leaving.]
larhat has joined #ocaml
larhat has quit [Client Quit]
larhat has joined #ocaml
larhat has quit [Client Quit]
larhat has joined #ocaml
larhat has quit [Client Quit]
larhat has joined #ocaml
larhat has quit [Client Quit]
larhat has joined #ocaml
larhat has quit [Client Quit]
larhat has joined #ocaml
larhat has quit [Client Quit]
michbad has quit [Ping timeout: 255 seconds]
larhat has joined #ocaml
larhat has quit [Client Quit]