adrien changed the topic of #ocaml to: Discussions about the OCaml programming language | http://www.ocaml.org | OCaml 4.02.2 announced http://ocaml.org/releases/4.02.html | Try OCaml in your browser: http://try.ocamlpro.com | Public channel logs at http://irclog.whitequark.org/ocaml
xificurC has quit [Ping timeout: 246 seconds]
neferty has joined #ocaml
<neferty> can i specifically exclude a variant in a pattern?
MrScout has quit [Remote host closed the connection]
igoroliveira has quit [Quit: Connection closed for inactivity]
<Drup> a polymorphic variant ? no
<damason_> neferty: you could use a guard to check for the condition you want to exclude, but it sounds like you are asking specifically about something like | (_, not 5) -> "not 5" | (_, _) -> "it isn't not 5"
<damason_> neferty: not sure if it is good practice, but you can add a pattern before your pattern that will match what you don't want, so that by the time it gets to the pattern you know it is not that.
<neferty> actually i just ended up doing | `foo (#bar | #baz |#qux as x) -> ... | `foo #i_want_special_case as y -> ...
<Drup> damason_: that's terrible practice, if you do things like that, you are defeating the purpose of the pattern totally checker
<neferty> i didn't realize ocaml could "unify" the type like that
<neferty> ie. bind x to any of those types if i say that
<Drup> neferty: it's expanded
<neferty> but thinking about it, it totally makes sense
<neferty> yeah, i'm a bit of a newcomer to ocaml, and ml in general, so some things are still a bit unexpected and magic to me :)
<Drup> this part of the language is not very well known
<Drup> the # notation for poly variants, in particular
<neferty> haha, tell me about it. i'm editing code an ocaml fan coworker of mine wrote, and half of this seems like black magic to me
pyon has quit [Quit: fix config]
<damason_> Drup: I'm keen to learn how to do it better. I can link to the patch if you're happy to point me towards a better approach.
<damason_> (it's my first ever ocaml)
<Drup> sure, link
<neferty> but it's really neat, how types are handled and how they actually feel more like a tool than a limitation
pyon has joined #ocaml
<damason_> Drup: the code used to raise a warning for any statement after the "return" statement (it analyzes javascript code"
<damason_> Drup: my code changes it so it will not raise a warning for any FunctionDeclaration, or for any VariableDeclaration that has only None for the nested inits.
Guest38 has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<Drup> you use weird patterns, but appart from that, I guess it's fine
<damason_> Drup: I would put that down to inexperience - I just played around with it until I could match what I wanted and keep the type-checker happy.
<Drup> I would use "let open ... in" instead of your M.(function ... )
<Drup> I was never a fond of "foo |> List.bla (fun ...)
<damason_> Drup: is that equivalent syntax?
<Drup> but I know some people who are, so that's just taste
<Drup> yes
<damason_> cool
<damason_> I saw |> used in nearby code, so just went with that. So rather than `lst |> List.bla (fun ...)` I could do `List.bla (fun ...) lst`, right?
<Drup> yeah
<Drup> but as I said, that's taste
<Drup> some people like your version a lot
<damason_> I was about to try to define |> but I don't know how to make something infix. Is it automatic for symbols, or is there special syntax?
blAckEn3d has joined #ocaml
<Drup> It's automatic
<damason_> let |> foo bar = bar foo
<Drup> let (|>) foo bar = bar foo
<Drup> when you put parens around an operator, it makes it a "normal" function
<damason_> so `foo |> bar` would be the same as `(|>) foo bar`?
<Drup> yes
<damason_> cool. So far I am mainly just mashing ML and Haskell together in my head.
Algebr`` has quit [Remote host closed the connection]
blAckEn3d has quit [Ping timeout: 264 seconds]
browncodes has quit [Ping timeout: 252 seconds]
claudiuc has quit [Remote host closed the connection]
junger has joined #ocaml
<junger> hello everyone
<junger> sorry if this has been answered already
<junger> but could someone point me to the direction of a howto of mikmatch?
<junger> Specially in regards to using it with oasis?
<junger> *regard
<junger> Already did that
<junger> Couldn't get it to work
<Drup> including the second part ?
<Drup> "If the package's name doesn't end by .syntax ..."
<junger> Yes
<Drup> hum, that should work. I don't know much about mikmatch itself so I can't help you :/
<junger> my _build/_tags file is basically this
<junger> # OASIS_START
<junger> # OASIS_STOP
<junger> true: syntax(camlp4o)
<junger>
<junger> Ah, ok mate, thanks
<Drup> the _tags should not be inside _build
<Drup> it should be at the root
<junger> well, first mistake then
<junger> but still, no luck here
<junger> thanks anyway
<Drup> no clues :/
<junger> it seemed like a nice project to try :[
<Drup> sedlex is a bit similar
manizzle has joined #ocaml
<junger> looks like it, I'll take a stab
ygrek has quit [Ping timeout: 244 seconds]
<Drup> (and there is always the "just use re" solution)
<junger> that too :)
<junger> I'm just trying to cool toys first
<junger> plus match+regexp seems like a correct fit
<Drup> Re is cool :D
<junger> no offense meant :]
tmtwd has quit [Ping timeout: 265 seconds]
shinnya has quit [Ping timeout: 256 seconds]
manizzle has quit [Ping timeout: 250 seconds]
ygrek has joined #ocaml
Algebr has joined #ocaml
pyon has quit [Read error: Connection reset by peer]
pyon has joined #ocaml
gpietro has quit [Ping timeout: 250 seconds]
Algebr has quit [Ping timeout: 250 seconds]
ygrek has quit [Ping timeout: 255 seconds]
browncodes has joined #ocaml
gpietro has joined #ocaml
junger has quit [Read error: Connection reset by peer]
Algebr has joined #ocaml
igoroliveira has joined #ocaml
tennix has joined #ocaml
ygrek has joined #ocaml
alpen has quit [Ping timeout: 246 seconds]
alpen has joined #ocaml
Algebr has quit [Ping timeout: 244 seconds]
ygrek has quit [Ping timeout: 244 seconds]
segmond has quit [Ping timeout: 246 seconds]
psy_ has quit [Read error: No route to host]
psy_ has joined #ocaml
segmond has joined #ocaml
MercurialAlchemi has joined #ocaml
rgrinberg_ has joined #ocaml
rgrinberg_ is now known as rgrinberg
thomasga has joined #ocaml
Sorella has quit [Quit: Connection closed for inactivity]
Algebr has joined #ocaml
JuggleTux has joined #ocaml
darkf has joined #ocaml
browncodes has quit [Remote host closed the connection]
octachron has joined #ocaml
blAckEn3d has joined #ocaml
fraggle_ has quit [Read error: Connection reset by peer]
darkf_ has joined #ocaml
blAckEn3d has quit [Ping timeout: 246 seconds]
darkf has quit [Ping timeout: 244 seconds]
browncodes has joined #ocaml
igoroliveira has quit [Quit: Connection closed for inactivity]
BhavyaM has joined #ocaml
keen___________5 has joined #ocaml
keen___________4 has quit [Ping timeout: 265 seconds]
contempt has quit [Ping timeout: 264 seconds]
contempt has joined #ocaml
kushal has joined #ocaml
tmtwd has joined #ocaml
kolko has quit [Quit: ZNC - http://znc.in]
Simn has joined #ocaml
kolko has joined #ocaml
ygrek has joined #ocaml
darkf_ is now known as darkf
JuggleTux has quit [Ping timeout: 272 seconds]
rgrinberg has quit [Quit: Connection closed for inactivity]
ggole has joined #ocaml
grouzen has joined #ocaml
tmtwd has quit [Ping timeout: 260 seconds]
Algebr has quit [Remote host closed the connection]
zpe has joined #ocaml
xificurC has joined #ocaml
zpe has quit [Remote host closed the connection]
zpe has joined #ocaml
ely-se has joined #ocaml
damason_ has quit [Ping timeout: 265 seconds]
zpe has quit [Ping timeout: 240 seconds]
BitPuffin|osx has quit [Ping timeout: 264 seconds]
blAckEn3d has joined #ocaml
zpe has joined #ocaml
zpe has joined #ocaml
zpe has quit [Remote host closed the connection]
blAckEn3d has quit []
OnkV has quit [Ping timeout: 240 seconds]
Algebr has joined #ocaml
Haudegen has joined #ocaml
mort___ has joined #ocaml
sh0t has joined #ocaml
ely-se has quit [Quit: leaving]
ely-se has joined #ocaml
ggole_ has joined #ocaml
ely-se has quit [Client Quit]
ggole has quit [Ping timeout: 250 seconds]
ely-se has joined #ocaml
Intensity has quit [Ping timeout: 244 seconds]
browncodes has quit [Remote host closed the connection]
<Algebr> I do a #require on a package and get an exception that a shared library cannot be found, yet the path that is printed does exist, there is a .so at the path printed. What can I do in this strange situation.
<adrien> run file on it
<Algebr> yep, exists, not a symlink.
<adrien_znc> which arch?
<Algebr> debian x86
<Algebr> Perhaps I am not reading the error correctly. I get this: Cannot load required shared library dllmaxminddb_stubs. Reason: /home/gar/.opam/working/lib/stublibs/dllmaxminddb_stubs.so: libmaxminddb.so.0: cannot open shared object file: No such file or directory.
<Algebr> is it saying that the dllmaxmindb_stubs.so can't load libmaxminddb.so?
<adrien> 32 bits? does it match the architecture of your ocaml executable?
<adrien> and, yes, it's after the .so
<adrien> the second one
<adrien> not the first one
<Algebr> so the first load is crapping out because it can't load the second one, correct?
<adrien> yes
<Algebr> okay, I can fix that. great. I also want to make a fix to ocamlfind. when it gives the warning about ld.conf , it isn't as useful because it doesn't tell you which ld.conf...which with opam switches would be useful to know.
kakadu has joined #ocaml
ygrek has quit [Ping timeout: 246 seconds]
Anarchos has joined #ocaml
ollehar has joined #ocaml
ollehar has quit [Quit: ollehar]
ollehar has joined #ocaml
ely-se has quit [Quit: leaving]
manizzle has joined #ocaml
<gasche> Algebr: ocamlfind -printconf
<Algebr> well thats new to me.
yomimono has joined #ocaml
igitoor has quit [Ping timeout: 256 seconds]
igitoor has joined #ocaml
ely-se has joined #ocaml
igitoor has joined #ocaml
igitoor has quit [Changing host]
browncodes has joined #ocaml
<Khady> Hi. I have a warning because a parametrized tag is not used in any flag declaration. I'd like to hide it, but mark_tag_used seems to work only with "normal" tags. Is there a workaround?
browncodes has quit [Remote host closed the connection]
JuggleTux has joined #ocaml
ely-se has quit [Quit: leaving]
Algebr has quit [Ping timeout: 252 seconds]
<gasche> Khady: I would be curious to know what your style() rule does, would you care to show its definition?
pyon has quit [Quit: Stupid Emacs.]
<gasche> I think (mark_tag_used "style(code.css)") would work as a workaround, but I would like to understand if your issue means that the "is this tag used" logic needs to be improved
pyon has joined #ocaml
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
Anarchos has joined #ocaml
rand000 has joined #ocaml
grouzen has quit [Ping timeout: 240 seconds]
_andre has joined #ocaml
Sorella has joined #ocaml
zpe has joined #ocaml
dsheets has quit [Ping timeout: 246 seconds]
BitPuffin has joined #ocaml
<Khady> gasche: pdep [] "style" (fun filename -> ["resources" // filename]);
ely-se has joined #ocaml
<Khady> I'm using ppx_blob and I'd like to automaticaly recompile if my css is changed
igoroliveira has joined #ocaml
tennix has quit [Ping timeout: 260 seconds]
<gasche> Khady: so indeed this is a case of "usage logic should be refined", pdep should be taken into account
<gasche> and I think it should be part of the later 4.02 releases
<Khady> ok thanks gasche
dsheets has joined #ocaml
BhavyaM has quit [Quit: Quit the channel]
sh0t has quit [Ping timeout: 245 seconds]
enjolras4 has joined #ocaml
ollehar1 has joined #ocaml
ollehar has quit [Ping timeout: 246 seconds]
ollehar1 is now known as ollehar
pyon has quit [Remote host closed the connection]
ollehar1 has joined #ocaml
ollehar1 has quit [Client Quit]
mort___ has left #ocaml [#ocaml]
ollehar has quit [Ping timeout: 260 seconds]
pyon has joined #ocaml
sh0t has joined #ocaml
enitiz has joined #ocaml
enitiz has quit [Remote host closed the connection]
grouzen has joined #ocaml
sh0t has quit [Ping timeout: 255 seconds]
jtfmumm has joined #ocaml
ryanartecona has joined #ocaml
martintrojer has quit [Quit: ZNC - 1.6.0 - http://znc.in]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
nullcatxxx_ has joined #ocaml
enitiz has joined #ocaml
enitiz has quit [Read error: Connection reset by peer]
ely-se has quit [Quit: leaving]
Anarchos has joined #ocaml
nicoo has joined #ocaml
thomasga has quit [Quit: Leaving.]
Anarchos has quit [Client Quit]
kushal has quit [Quit: Leaving]
enitiz has joined #ocaml
ely-se has joined #ocaml
pyon has quit [Quit: Whoa, Emacs sucks.]
<gpietro> hi guys: what's the difference between "opening" a module and "using" it in the toplevel ocaml... open vs #use
<gpietro> ?
<octachron> #use "file.ml" is quite special, it reads the whole file in the toplevel
<octachron> it is more similar to `include` than `open`
pyon has joined #ocaml
<ely-se> that's lewd
enitiz has quit [Ping timeout: 255 seconds]
jonludlam has quit [Ping timeout: 264 seconds]
<octachron> another way to look at it, `#use` behaves like you copy-pasted the content of the file inside your toplevel
<enjolras4> In the same topic someone told me today that let open F in had a runtime operation. Is that true ? Why ?
<rks`> It's not
<enjolras4> It looks like a pure scoping directive if F is not first class
<enjolras4> Hmm
<flux> well, it is a runtime operation in the sense that either the module F must exist in the scope or alternatively file f.cmi of F.cmi must be available via search directory
<Drup> flux: that's not runtime
<flux> it's runtime in the toplevel :)
<enjolras4> Everything is runtime in the top-level
<Drup> compiling is runtime in the toplevel, that doesn't make any sort of sense
<flux> ;(
<ely-se> why is it called "toplevel" and not "REPL"?
<flux> well, for one ocaml doesn't have read, eval, print operations in the sense LISP has
<Drup> because you can only enter toplevel declaration ? :D
<flux> another, well, they are top level definitions you can enter there
<ely-se> :(
<enjolras4> https://janestreet.github.io/ocaml-perf-notes.html looks like the source of this claim. Doesn't look costly though
tane has joined #ocaml
<enjolras4> I'll just decide I don't care :-)
<flux> that's the spirit!
<gpietro> ok i see...
thomasga has joined #ocaml
<ggole_> It's functor application that has the runtime cost
<rks`> yes
<ggole_> That is, let open F (X) in ...
<enjolras4> Makes sense
<Drup> from the runtime point of view, modules are basically records
<Drup> the same reasoning applies, performance wise
<flux> how about with the new optimizer?!
<Drup> still record, just that it will inlines much more things
<flux> if it inlines as far as not using the record, then it's ok.. ;-)
<Drup> so, a functor application has decent chances to be inlined
<enjolras4> Is there a new optimizer ?
<Drup> yes, next version
<Drup> it makes most of this page obsolete
<ely-se> There is also an old optimizer!
<enjolras4> Nice
<enjolras4> How does it in-line functions ? Lto ?
<rks`> a document explaining the different heuristics is currently being written
<Drup> search for "flambda"
<rks`> I'm sure it will be widely available once it is ready
jonludlam has joined #ocaml
<enjolras4> Thx
<ely-se> flambda reminds me of flambé and now I'm hungry
<flux> ocaml already does inlining of code in other modules (when compiling with ocamlopt), flambda makes just all general betterments.
<flux> well, that's perhaps a not praise enough for what flambda does :)
<Drup> he, ocamlopt barely inlines
<ely-se> does it make me hungry? yes. so no praise from me
enjolras4 has quit [Quit: Error from remote client]
<bernardofpc> https://janestreet.github.io/ocaml-perf-notes.html -> btw, their let cmp_t2 a b is wrong (has a 1 and not a 0), not sure if anyone from JS here can correct the type
<bernardofpc> *typo
<rks`> well spotted
ryanartecona has quit [Quit: ryanartecona]
<rks`> bernardofpc: you can always submit an issue on https://github.com/janestreet/janestreet.github.com/issues if no one is here to fix it
<rks`> but I'll take care of this one
thomasga has quit [Quit: Leaving.]
rand000_ has joined #ocaml
rand000 has quit [Ping timeout: 255 seconds]
nullcatx_ has joined #ocaml
<bernardofpc> ah, nice
thomasga has joined #ocaml
nullcatxxx_ has quit [Ping timeout: 265 seconds]
samrat has joined #ocaml
<rks`> bernardofpc: fixed (and I fixed some assembly formatting/rendering issue as well)
troydm has quit [Quit: What is hope? That all of your wishes and all of your dreams come true? (C) Rau Le Creuset]
<ely-se> rks`: do you like working in high-pressure environments?
<ely-se> JS job descriptions say the environments have a lot of pressure. I can't imagine how somebody can consider that fun to work in. :v
<ely-se> it sounds more like a nightmare
<rks`> where did you read that? :)
troydm has joined #ocaml
<ely-se> In some job description.
<ely-se> I don't know which one anymore.
<rks`> I couldn't find it mentionned either, so I am not sure how it was meant to be understood
<rks`> (but I don't feel like I'm working "under high pressure")
<ely-se> nice
nullcatxxx_ has joined #ocaml
<Enjolras> do you know any vim trick to jump to the try associated with a with or the let associated with the in ?
nullcatx_ has quit [Ping timeout: 260 seconds]
jtfmumm has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
<rks`> ah, missunderstood
<rks`> you can just it %
<rks`> hit*
ollehar has joined #ocaml
<ely-se> Speaking of which, I should look for a new job soon. I'm getting sick of making forms all day.
<ely-se> and finding workarounds for bugs in crappy JS libraries
<ely-se> JS=javascript :P
<Enjolras> rks`: % ? isn't that to jump to a percent of the buffer ?
nullcatxxx_ has quit [Ping timeout: 246 seconds]
ryanartecona has joined #ocaml
<rks`> Enjolras: nope :) call :h %
ollehar has quit [Ping timeout: 255 seconds]
<Enjolras> thanks
ollehar has joined #ocaml
<ely-se> I wish I could find a place where I'd have little responsibility, with competent coworkers, and with a high-quality code base.
<ely-se> or maybe I should stop developing software altogether
<ollehar> ely-se: jane street is always looking for people, it seems. but they didn't want me. :(
bendiken has joined #ocaml
<ely-se> luckily it's almost weekend :3
<profan> ely-se: that seems like a "pick two" situation :P
<Drup> ollehar: jst is not the only company using ocaml
<ely-se> profan: where I work now, picking none would suffice
<profan> ely-se: ouch
<ely-se> guess how many automated tests we have :D
<profan> .. none? :p
<ely-se> :(
<profan> D:
<profan> should find somewhere which is better for your sanity
<ely-se> my latest commit messages are "Fix code duplication fest" and "Fix magic number fest"
<Enjolras> ollehar: they didn't want me either :p
<ollehar> Enjolras: huh. who do they hire, eve?
<ollehar> *even
<ollehar> Drup: sure, I know. but it's the best known ocaml company.
<ely-se> Competent people. /me runs
<profan> doesn't facebook do a fair bit of ocaml as well?
<Enjolras> ollehar: rks` it seens
<Enjolras> :p
<ely-se> facebook uses OCaml for writing tools to manipulate source code
<ely-se> such as pfff and flow
<profan> sure, typecheckers, compilers, would that not be desirable? :)
<ely-se> that'd certainly be fun
<ely-se> it doesn't involve making forms over and over again so that's already a huge plus :p
<ely-se> protip: never expect making ERP software to be a fun activity
<ollehar> ely-se: the ocaml company in copenhagen wants a js front-end guy. maybe you can work your way up there?
<Enjolras> To be honnest, i've been so bad at the second interview it makes sense they didn't want me. I woudn't have wanted me if i was the interviewer :>
<ely-se> ollehar: eek javascript nopenopenopenopeonpe
<profan> ely-se: i can imagine your list of pros: "no forms?! NO FORMS!!"
<ollehar> ely-se: yeah, I just recently started to hate js, too. don't know why.
<Drup> ollehar: he, I probably have a different definition of best
<Enjolras> nobody needs js when you have ocaml
<ollehar> Drup: best _known_ :)
<ely-se> the ideal job for me would be to get money for doing whatever I want
<Drup> ollehar: still applies
<profan> it's probably a bad bet to try to get hired for a js job and "work towards" an ocaml one :D
<Drup> ely-se: so, academia professor ? :D
<ollehar> ely-se: make a kickstarter.
<ely-se> I don't have any formal education, so that'd be hard
<rks`> Drup: double fallacy
psy_ has quit [Ping timeout: 265 seconds]
<rks`> 1/ you *don't* do whatever the hell you want
<rks`> 2/ you don't get money
<octachron> Drup, if you enjoy writing grant application?
<Drup> rks`: I know
<Drup> grant is only if you want to hire people
<Drup> it's not for your salary
<rks`> Drup: others might not, don't give them false hopes
<Drup> rks`: hum, true
<profan> i thought false hopes fueled all of humanity?
<ely-se> I also thought of getting out of software development, but I'm not good at anything else XD
<octachron> Drup, or buying equipment, or obtaining promotions, or decreasing your teaching load. Even in France, grant applications are becoming less and less avoidable
<ollehar> ely-se: carpenter, maybe?
<ollehar> I only work 80%, so I can work on my hobby projects more.
<ollehar> right now, that's mostly ocaml, though. :)
<ely-se> maybe interior designer
<ely-se> I dunno
jtfmumm has joined #ocaml
ely-se has quit [Quit: leaving]
samrat has quit [Ping timeout: 265 seconds]
<ollehar> ely-se: sounds cool
ely-se has joined #ocaml
yomimono has quit [Ping timeout: 260 seconds]
ryanartecona has quit [Quit: ryanartecona]
<ely-se> I think I have a job in mind, though I don't know whether it pays well.
jonludlam has quit [Ping timeout: 244 seconds]
<ely-se> Well, time to go home o/
<zozozo> suppose I have a type: 'a t1 = ... constraint 'a = [< `A | `B ], now I'd like to have a type 'a t2 = { foo : 'b t1 }, with 'a = [< 'b ], which doesn't work because the compiler complains that 'b is not a polymorphic variant type (though it is constrained to be), is there a way to achieve something like that ?
ollehar1 has joined #ocaml
ollehar has quit [Ping timeout: 255 seconds]
ollehar1 is now known as ollehar
<zozozo> .b 1
<zozozo> woops, sorry
mort___1 has joined #ocaml
jtfmumm has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
ely-se has quit [Quit: leaving]
<smondet> zozozo: you can try to give a name to the poly-variant: type a_or_b = [ `A | `B ] and then use it in both places ... constrain 'a = [< a_or_b ]
<smondet> btw, dunno your goal, but I think people usually want [> ... ] (not [< ... ])
jonludlam has joined #ocaml
<zozozo> smondet: well that's not exactly the same result, since to allow things like x : [ `A ] t2 = { foo : [ `A | `B ] t1 }, but not [ `A | `B ] t2 = { foo : [ `A ] t1 }
<zozozo> *since I'd like to allow
ollehar has quit [Ping timeout: 250 seconds]
<smondet> zozozo: oh I see what you want, but don't know how to achieve it :-/
<zozozo> well, in my case requiring the two types to be equal kinda works, but I was wondering if I could push it a bit, ^^
thomasga has quit [Ping timeout: 250 seconds]
aftershave has quit [Quit: Textual IRC Client: www.textualapp.com]
aftershave has joined #ocaml
aftershave has quit [Client Quit]
aftershave has joined #ocaml
<zozozo> while I'm at it, is it possible to define something like : type a = 'b t constraint 'b = [> `A ] ? not really necessary but that would make my types quite shorter in interfaces
psy_ has joined #ocaml
samrat has joined #ocaml
tennix has joined #ocaml
Lasher` has quit [Quit: leaving]
<ggole_> No, you need to bind the type variable
<zozozo> ok
<smondet> zozozo: you can hide type variables with GADTs:
<smondet> type 'a t = 'a list constraint 'a = [> `A ];;
<smondet> type b = Hide: 'a t -> b ;;
tennix has quit [Ping timeout: 255 seconds]
psy_ has quit [Ping timeout: 246 seconds]
tennix has joined #ocaml
grouzen has quit [Ping timeout: 272 seconds]
<ggole_> But then you usually can't use the contents (meaningfully)
tane has quit [Quit: Verlassend]
psy_ has joined #ocaml
mort___1 has quit [Quit: Leaving.]
MrScout has joined #ocaml
<mrvn> unless you add a witness
<mrvn> type b = Hide: 'a w * 'a t -> b
<ggole_> Sure, but you wouldn't go down that path without good reason
yomimono has joined #ocaml
ggole_ is now known as ggole
grouzen has joined #ocaml
hannes has quit [Read error: Connection reset by peer]
hannes has joined #ocaml
shinnya has joined #ocaml
grouzen has quit [Ping timeout: 240 seconds]
ryanartecona has joined #ocaml
jwatzman|work has joined #ocaml
uris77 has joined #ocaml
Guest38 has joined #ocaml
tennix has quit [Ping timeout: 252 seconds]
thomasga has joined #ocaml
R0B_ROD has joined #ocaml
<R0B_ROD> never programmed before using a book to start
zpe has quit [Remote host closed the connection]
R0B_ROD has quit [Quit: leaving]
thomasga has quit [Ping timeout: 260 seconds]
jonludlam has quit [Ping timeout: 244 seconds]
thomasga has joined #ocaml
ygrek has joined #ocaml
manizzle has quit [Ping timeout: 272 seconds]
darkf has quit [Quit: Leaving]
Algebr has joined #ocaml
mea-culpa has joined #ocaml
yomimono has quit [Ping timeout: 244 seconds]
ollehar has joined #ocaml
samrat has quit [Ping timeout: 244 seconds]
samrat has joined #ocaml
ryanartecona has quit [Quit: ryanartecona]
ryanartecona has joined #ocaml
Denommus has joined #ocaml
ollehar1 has joined #ocaml
ollehar has quit [Ping timeout: 250 seconds]
ollehar1 is now known as ollehar
ollehar is now known as ollehar2
thomasga has quit [Quit: Leaving.]
kolko has quit [Quit: ZNC - http://znc.in]
ryanartecona has quit [Quit: ryanartecona]
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
kolko has joined #ocaml
psy_ has quit [Ping timeout: 246 seconds]
jeffmo has joined #ocaml
sh0t has joined #ocaml
Simn has quit [Read error: Connection reset by peer]
Simn has joined #ocaml
ggole has quit []
kakadu has quit [Quit: Page closed]
tane has joined #ocaml
moei has joined #ocaml
ncthom91 has joined #ocaml
ousado has quit [Remote host closed the connection]
ousado has joined #ocaml
ollehar3 has joined #ocaml
ollehar2 has quit [Ping timeout: 240 seconds]
ollehar3 is now known as ollehar2
manizzle has joined #ocaml
flx_ has joined #ocaml
flux has quit [Remote host closed the connection]
flx_ is now known as flux
kolko has quit [Ping timeout: 240 seconds]
BitPuffin has quit [Remote host closed the connection]
manizzle has quit [Ping timeout: 260 seconds]
dsheets has quit [Ping timeout: 244 seconds]
lobo has joined #ocaml
ollehar2 has quit [Quit: ollehar2]
ollehar has joined #ocaml
manizzle has joined #ocaml
mea-culpa has quit [Remote host closed the connection]
kolko has joined #ocaml
mea-culpa has joined #ocaml
tobiasBora has joined #ocaml
Guest38 has quit [Read error: Connection reset by peer]
jeffmo has quit [Quit: jeffmo]
grouzen has joined #ocaml
psy_ has joined #ocaml
tennix has joined #ocaml
dsheets has joined #ocaml
tennix has quit [Ping timeout: 244 seconds]
jtfmumm has joined #ocaml
kakadu has joined #ocaml
ryanartecona has joined #ocaml
kolko has quit [Ping timeout: 246 seconds]
jave has quit [Quit: ZNC - http://znc.in]
jave has joined #ocaml
jtfmumm has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
jave has quit [Remote host closed the connection]
xet7_ has quit [Read error: Connection reset by peer]
samrat has quit [Ping timeout: 272 seconds]
xet7_ has joined #ocaml
jave has joined #ocaml
<bjorkintosh> OCaPIC: Programming PIC microcontrollers in OCaml
<bjorkintosh> is it still a viable approach to programming PIC?
systmkor has quit [Quit: Leaving]
Intensity has joined #ocaml
thomasga has joined #ocaml
<troydm> I get this when I'm trying to build tgls example using obuild http://pastebin.com/p2T59f9z
<troydm> any suggestions guys?
<ygrek> double linkage, look at cmdline carefully
ncthom91 has quit [Quit: Textual IRC Client: www.textualapp.com]
enquora has joined #ocaml
pyon has quit [Remote host closed the connection]
ollehar has quit [Ping timeout: 245 seconds]
pyon has joined #ocaml
ollehar has joined #ocaml
MercurialAlchemi has quit [Ping timeout: 250 seconds]
<companion_cube> gasche: nice email about v3 ;)
claudiuc has joined #ocaml
jtfmumm has joined #ocaml
gpietro has quit [Ping timeout: 255 seconds]
<Denommus> I forgot the syntax for records as variants of a type
Haudegen has quit [Ping timeout: 250 seconds]
Guest38 has joined #ocaml
jeffmo has joined #ocaml
Haudegen has joined #ocaml
jeffmo has quit [Client Quit]
gpietro has joined #ocaml
jeffmo has joined #ocaml
ollehar has quit [Ping timeout: 256 seconds]
enquora has quit [Quit: enquora]
Haudegen has quit [Ping timeout: 260 seconds]
Haudegen has joined #ocaml
ryanartecona has quit [Quit: ryanartecona]
jtfmumm has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
ygrek has quit [Ping timeout: 260 seconds]
lobo has quit [Quit: leaving]
Simn has quit [Quit: Leaving]
mea-culpa has quit [Remote host closed the connection]
uris77 has quit [Quit: leaving]
Submarine has quit [Remote host closed the connection]
nullcatxxx_ has joined #ocaml
ygrek has joined #ocaml
ollehar has joined #ocaml
octachron has quit [Quit: Leaving]
tane has quit [Quit: Verlassend]
damason has joined #ocaml
BitPuffin|osx has joined #ocaml
sh0t has quit [Ping timeout: 256 seconds]
xificurC has quit [Ping timeout: 240 seconds]
ollehar has quit [Read error: Connection reset by peer]
ollehar has joined #ocaml
kakadu has quit [Remote host closed the connection]
vpm has quit [Quit: co'o]
vpm has joined #ocaml
klj has joined #ocaml
erider has joined #ocaml
erider has quit [Remote host closed the connection]
ryanartecona has joined #ocaml
Denommus has quit [Quit: MAMA I'M COMING HOOOOOOOOOOOOOME]
higgs has joined #ocaml
ollehar1 has joined #ocaml
ollehar has quit [Ping timeout: 240 seconds]
ollehar1 is now known as ollehar
ollehar1 has joined #ocaml
ollehar has quit [Ping timeout: 256 seconds]
ollehar has joined #ocaml
ryanartecona has quit [Quit: ryanartecona]
ollehar1 has quit [Ping timeout: 256 seconds]
ollehar1 has joined #ocaml
<Algebr> How do you tell the compiler to shut up in this case: type foo = A | B [A; A; B] |> List.filter (function A -> true | B -> false) |> fun A -> logic
ollehar has quit [Ping timeout: 240 seconds]
MrScout_ has joined #ocaml
<Drup> you write your thing differently
<Drup> or you use polyvariants
ollehar1 has quit [Ping timeout: 256 seconds]
MrScout has quit [Ping timeout: 246 seconds]
MrScout_ has quit [Ping timeout: 246 seconds]
madroach has quit [Ping timeout: 264 seconds]
madroach has joined #ocaml
thomasga has quit [Quit: Leaving.]
tokik has quit [Quit: leaving]
tokik has joined #ocaml
jwatzman|work has quit [Quit: jwatzman|work]