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
robthebob has quit [Quit: Leaving]
ulfdoz_ has joined #ocaml
ulfdoz has quit [Read error: Operation timed out]
ulfdoz_ is now known as ulfdoz
khia0 has joined #ocaml
lopex has quit []
bzzbzz has joined #ocaml
zsparks has quit [Read error: Operation timed out]
zsparks has joined #ocaml
vivanov has joined #ocaml
ymasory has quit [Quit: Leaving]
philtor has joined #ocaml
<adrien> NaCl: callbacks should automagically be executed inside lwt threads
tnguyen has joined #ocaml
ulfdoz has quit [Ping timeout: 252 seconds]
<adrien> I'm after a data structure that would match the notion of selecting several elements: a zipper is nice to focus one element, but what about several ones?
Snark_ has joined #ocaml
philtor has quit [Ping timeout: 252 seconds]
<flux> ..list of zippers?
khia0 has quit [Remote host closed the connection]
khia0 has joined #ocaml
Associat0r has joined #ocaml
khia0 has left #ocaml []
axiles has joined #ocaml
Cyanure has joined #ocaml
Snark_ is now known as Snark
munga has joined #ocaml
Cyanure has quit [Remote host closed the connection]
tnguyen has quit [Remote host closed the connection]
munga has quit [Ping timeout: 240 seconds]
Cyanure has joined #ocaml
ikaros has joined #ocaml
thomasga has joined #ocaml
thomasga has quit [Ping timeout: 240 seconds]
thomasga has joined #ocaml
thomasga1 has joined #ocaml
thomasga has quit [Read error: No route to host]
ftrvxmtrx has quit [Quit: This computer has gone to sleep]
sgnb has quit [Remote host closed the connection]
rossberg has joined #ocaml
rossberg has quit [Remote host closed the connection]
rossberg has joined #ocaml
avsm has joined #ocaml
Associat0r has quit [Quit: Associat0r]
sgnb has joined #ocaml
ftrvxmtrx has joined #ocaml
munga has joined #ocaml
Tommytom has joined #ocaml
<Tommytom> Hello, can I have an objects list in Ocaml ?
<rproust> Tommytom: yes
<rproust> they must be of the same type
<Tommytom> Yes of course, so I don't understant my mistake
<Tommytom> understand
<rproust> is your codee pasted somewhere?
<rproust> what error does it output?
<Tommytom> Can you build it ?
<Tommytom> I have a problem on list_clients
<Tommytom> Non
<Tommytom> No
<Tommytom> Excuse me, I confused in my code :)
<rproust> ok
<Tommytom> Line 66, is it correct ?
<rproust> it seems to be
<rproust> but it might not infer type properly
<rproust> what's the error message?
<Tommytom> list_pck : '_a; need_send_update : bool; sendOtherPck : '_a -> unit;
<Tommytom> _.. >
<Tommytom> list ref, contains type variables that cannot be generalized
<rproust> when you declare list_pck (l.28) you should put an explicit type
<Tommytom> How ?
<rproust> val mutable list_pck = ref ([] : <appropriate type> list)
<rproust> you replace line 28 by this modified version
<Tommytom> Okay
<Tommytom> And why ref ?
<rproust> with <appropriate type> being the type of elements of the list list_pck…
<rproust> sry
<rproust> no ref
<Tommytom> Ok
<Tommytom> thank you
<rproust> val mutable list_pck = ([] : <elt type> list)
<vivanov> is there a library to work with matrices -- mutliply, invert, ... ?
<Tommytom> val mutable list_pck = ([] : string list)
<Tommytom> list_pck : '_a;
<Tommytom> How is it possible ?
lopex has joined #ocaml
<hcarty> vivanov: The two main ones are probably ocamlgsl and lacaml
<hcarty> vivanov: Both are available here - http://www.ocaml.info/home/ocaml_sources.html
<vivanov> hcarty: thx :)
sepp2k has joined #ocaml
ikaros has quit [Quit: Ex-Chat]
edwin has joined #ocaml
munga has quit [Ping timeout: 276 seconds]
thomasga1 has quit [Quit: Leaving.]
Tommytom has left #ocaml []
oriba has joined #ocaml
oriba has left #ocaml []
dnolen has joined #ocaml
<gildor> avsm, thelema_: are you interested in creating/managing an OCaml community on github ?
<avsm> sorry, no time
<avsm> happy to assist as i can though
<avsm> btw,what is "an ocaml community on github" ? :)
<gildor> no time also, but as we talked about it during last OCaml Meeting, I thought it can be good
nimred has quit [Ping timeout: 276 seconds]
<gildor> avsm: don't know, I am really not a good github user, but I see several communities on the latest github poster
<avsm> strikes me that we just need a hackage.haskell.org equivalent. the details of the underlying version control dont matter too much
<gildor> avsm: heu, yes, that the reason why I am working on oasis-db -- and what I told you at the meeting
<avsm> yeah, and i think that's fine.
<gildor> (i.e. the VCS choice is orthogonal to OCaml)
<gildor> ah ok, great to hear that
<avsm> mixed up in that talk was also some thoughts about free software and why github was bad, which i didnt agree with and thought was irrelevant
<avsm> that's all my comments were about… i think oasis-db would be very useful to have
<gildor> avsm: ah no, I gave 2 talks, one was about ocamlcore.org (and forge.o.o) and one about oasis-db
<avsm> anyway, it's all good stuff. having something is better than nothing :P
<gildor> the one with mixed content was about forge.o.o, but I know that the forge doesn't fit all needs
<gildor> whereas oasis.o.o is a generic purpose CPAN for the whole OCaml community
<avsm> right: i prefer github to the forge (just a personal preference), but i would definitely use oasis.o.o
<gildor> ok, so I go back to work ;-)
dnolen has quit [Quit: dnolen]
<avsm> enjoy :)
vivanov has quit [Ping timeout: 264 seconds]
vivanov has joined #ocaml
vivanov has quit [Ping timeout: 264 seconds]
vivanov has joined #ocaml
vivanov has quit [Ping timeout: 246 seconds]
lamawithonel_ has joined #ocaml
lamawithonel has quit [Ping timeout: 255 seconds]
vivanov has joined #ocaml
<thelema_> gildor: what do you mean by an ocaml community on github?
* NaCl wonders why lablgtk's file browser looks so old
<thelema_> linked against an old gtk? maybe its code needs to be updated to use a newer file browser
<NaCl> nah, the gtk here is pretty new
<NaCl> hmmm
<gildor> thelema_: I don't really know, they talk about communities here: http://labs.linkfluence.net/community/2011/06/20/github-poster.html
<NaCl> I think the code needs to be updated
* NaCl wonders why git is so popular
* gildor just wonder as NaCl does
<kerneis> reliable and efficient storage
<kerneis> you can do everything you wish, even unreasonable things
<thelema_> gildor: I suspect that is related to this and not to any explicit community making: https://github.com/languages/OCaml
<gildor> thelema_: ok
<NaCl> kerneis: yeah, but, the thing seems to be love to be quite complicated
<kerneis> people use it in spite of its complexity
<kerneis> because it's the most powerful
<gildor> without wanting to go into a VCS war, I think git has this little touch of black magic that makes people feel they got the power
<NaCl> gildor: heh, indeed.
* NaCl stops
<gildor> and maybe knowing git is a kind of leet speaking, you feel that you belong to this class of people that understand git
* NaCl looks at fossil again
<gildor> but this is IMHO, I use git but don't know it
<NaCl> all I do with git is commit and push
<flux> git is a nice tool for baking patches into a upstreamable form
* rproust doesn't feel like he has the power when using git… He feels afraid!
<NaCl> what did I forget to do this time?
<flux> and once you've baked your patches sufficiently, you can extract the stuff in a git-importable format and send it to the mailing list
* thelema_ uses git mostly because of gitk
<flux> which is how some big open source projects work from the POV of a random contributor
* NaCl thinks he'll try out fossil
sepp2k has quit [Ping timeout: 250 seconds]
sepp2k has joined #ocaml
avsm has quit [Quit: Leaving.]
<NaCl> and lablgtk uses its own file dialog
<thelema_> NaCl: really? wow. jooky.
<NaCl> yeah
lopex has quit []
lamawithonel_ has quit [Ping timeout: 250 seconds]
boscop has quit [Ping timeout: 255 seconds]
boscop has joined #ocaml
Cyanure has quit [Remote host closed the connection]
philtor has joined #ocaml
ulfdoz has joined #ocaml
palomer has joined #ocaml
<palomer> am I right in guessing that descr_of_in_channel can throw an exception?
<thelema_> yes, it's documented to do so
<thelema_> hmm, maybe...
* thelema_ realizes he's looking at BatUnix, not Unix
<palomer> touchԲ
<palomer> looking at the c file that's what I'm getting
<palomer> but in_channel_of_descr doesn't throw an exception
<palomer> int fd = Channel(vchannel)->fd;
<palomer> if (fd == -1) { errno = EBADF; caml_sys_error(NO_ARG); }
<palomer> return Val_int(fd);
<thelema_> yup
<palomer> caml_sys_error throws an exception, right?
<thelema_> caml_raise_sys_error(str);
<NaCl> thelema_: actually, it isn't custom. It's just the "old one that nobody uses anymore?
<NaCl> s/\?/./
<thelema_> caml_raise_with_arg((value) caml_exn_Sys_error, msg);
<thelema_> exception Sys_error of string
<thelema_> yes, it should raise this exception
<palomer> ahh, gotcha
<thelema_> NaCl: ah, it bound the old one and never updated to newer filepickers, probably to keep backwards compatibility
<NaCl> yeah
<NaCl> Looking at the lablgtk source, this is scaring me a bit
<thelema_> NaCl: the source?
<NaCl> lablgtk source
<thelema_> it's a bit complex.
<thelema_> with bit = <large value>
<NaCl> yeah
avsm has joined #ocaml
* NaCl suddenly feels that this endeavour will not end up well
<thelema_> the endeavour of updating to a new filepicker?
<NaCl> rather, adding the new one in, yes.
caligula_ has quit [Remote host closed the connection]
<NaCl> and the older one is much simpler
<NaCl> but deprecated
ulfdoz has quit [Read error: Operation timed out]
ulfdoz has joined #ocaml
enthymeme has joined #ocaml
Associat0r has joined #ocaml
caligula has joined #ocaml
avsm has quit [Quit: Leaving.]
lamawithonel_ has joined #ocaml
ftrvxmtrx has quit [Quit: This computer has gone to sleep]
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
Associat0r has quit [Quit: Associat0r]
ankit9 has quit [Ping timeout: 255 seconds]
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
bob` has joined #ocaml
lamawithonel_ has quit [Excess Flood]
enthymeme has quit [Ping timeout: 258 seconds]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
ftrvxmtrx has joined #ocaml
lamawithonel_ has quit [Ping timeout: 240 seconds]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Ping timeout: 255 seconds]
lamawithonel_ has joined #ocaml
enthymeme has joined #ocaml
lamawithonel_ has quit [Ping timeout: 255 seconds]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Excess Flood]
<hcarty> NaCl: If I recall correctly, the new file chooser form is available from lablgtk. I think one of the included demos uses it.
lamawithonel_ has joined #ocaml
<NaCl> hcarty: indeed it is
<NaCl> conveniently, it is undocumented in the tutorial
<NaCl> AFAICT
<hcarty> NaCl: I hit the same problem when I first tried lablgtk
<NaCl> limited/old documentation?
<hcarty> Finding the modern file chooser
<hcarty> And some limited documentation, although I found that once I "got" lablgtk's structure it became easier
<hcarty> I haven't used it in a while though, so I doubt that I get it anymore :-)
<NaCl> mmmm fun
<NaCl> thanks for pointing that out
<hcarty> It wasn't bad - it's just very different from most other OCaml libraries I've used
lamawithonel_ has quit [Excess Flood]
<hcarty> Probably out of a desire to match the underlying Gtk library structure
lamawithonel_ has joined #ocaml
<thelema_> and the heavy use of objects + polymorphic variants, probably unmatched by any other library
<hcarty> I wrote this before no longer needing it: http://forge.ocamlcore.org/projects/gtk-light/
<hcarty> That wrapper made my (very simple) GUI needs easier.
<hcarty> thelema_: Quite
milosn_ has joined #ocaml
milosn_ has quit [Client Quit]
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
ftrvxmtrx has quit [Quit: This computer has gone to sleep]
ankit9 has joined #ocaml
lamawithonel_ has quit [Ping timeout: 255 seconds]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Ping timeout: 255 seconds]
Snark has quit [Quit: Ex-Chat]
<adrien> NaCl: lablgtk's documentation is mostly inexistant: it's gtk's documentation
<adrien> needs an "intro to lablgtk" which mostly says "really close to gtk, see gtk's doc, and we have optional parameters (and that implies X and Y)" and a few other things (but it shouldn't be very long)
lamawithonel_ has joined #ocaml
<hcarty> adrien: From what I remember, the lablgtk translation of the Gtk tutorial does a decent implicit job of illustrating those points
<hcarty> Something explicit would be nice though
<adrien> it illustrates them but you're still wondering from time to time
lamawithonel_ has quit [Remote host closed the connection]
lamawithonel_ has joined #ocaml
<NaCl> adrien: alrightey... time to look at the new file chooser stuff
<adrien> ah, and I'm supposed to look at how I can make a custom model for listviews
<adrien> flux: I don't really understand how a list of zipper is nice for lists with multiple elements that can be selected
<NaCl> adrien: uh, I have no idea how to use this. >_<
<adrien> NaCl: the new file chooser?
<NaCl> yeah
<NaCl> oh. examples
lopex has joined #ocaml
lamawithonel_ has quit [Ping timeout: 255 seconds]
lamawithonel__ has joined #ocaml
lamawithonel__ has quit [Ping timeout: 255 seconds]
<flux> adrien, well, I don
<flux> 't either
<thelema_> adrien: the zippers represent both the sublists and the currently selected element in each
lamawithonel__ has joined #ocaml
munga has joined #ocaml
othiym23 has joined #ocaml
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
<NaCl> adrien: I'll be using the FileChooserButton. My current issue is figuring out where everything is.
<NaCl> Like modules
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
ikaros has joined #ocaml
<adrien> thelema_: but if I'm selecting several elements at a single level?
<adrien> NaCl: ocamlbrowser?
<thelema_> adrien: I guess you could have a multiway zipper, but that seems overly complex
<thelema_> that said, maybe there's some code out there for multi-cursor zippers
<thelema_> or maybe not...
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
munga has quit [Remote host closed the connection]
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
<NaCl> adrien: om nom nom
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
bob` has quit [Ping timeout: 250 seconds]
<adrien> thelema_: well, I'd like to use something nicer than a list (which is what is done in gtk, and which is the reason you have "#next" but not "#previous")
<adrien> but actually, maybe that a zipper will just work
<adrien> it'll require iterating over all the elements in order to collect them but that's something that is only done at the end
<thelema_> adrien: what's the whole problem? gtk is using a list for what?
<adrien> thelema_: listviews, and I want to use a pure data structure on the ocaml side and the best way is to implement the GTree.model (iirc) class and use that
lamawithonel__ has quit [Excess Flood]
<adrien> but I'm a bit too tired to actually say anything "useful" tonight I think
<thelema_> ok, I'll leave it alone too, then.
* thelema_ is fighting with espresso
lamawithonel__ has joined #ocaml
<adrien> should be good by next monday, but today, no
<adrien> errr, not next monday since I'll probably be attending Graspop (\m/)
thomasga has joined #ocaml
thomasga has quit [Client Quit]
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
robocop has joined #ocaml
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
lamawithonel__ has quit [Excess Flood]
<hcarty> thelema_: What is the process for uploading a package to the odb-ready oasis-db?
lamawithonel__ has joined #ocaml
<thelema_> hcarty: log in to ocamlforge, go here: http://oasis.ocamlcore.org/dev/upload and upload your tarball
<hcarty> thelema_: Does the tarball need the fully generated build system, or is the _oasis file enough?
<thelema_> it helps a lot if there's an _oasis file, otherwise you'll get pretty minimal metadata and odb will try to autodetect omake/make
<hcarty> A better question is probably - does the uploaded tarball get used directly by odb, or is it modified somehow?
<thelema_> it should probably be a release tarball, not just a source tarball
<hcarty> thelema_: Cool, thanks.
<thelema_> I don't believe that gildor modifies it, although I'm not certain.
<thelema_> I've always ran oasis setup before tarring
lamawithonel__ has quit [Excess Flood]
<thelema_> eventually, when gildor implements online _oasis editing, it'll modify the tarball and regen the setup files
lamawithonel__ has joined #ocaml
<hcarty> Do you know if versions like 2.0alpha1 are accepted and understood by oasis-db and odb?
<thelema_> yes, they are
<thelema_> oasis's version is 0.2.1~alpha1, and a number of other things I've packaged are version x.y.z-oasis1
lamawithonel__ has quit [Excess Flood]
<thelema_> odb doesn't care about separators, just grouping numbers and non-numbers and doing an element-by-element comparison
lamawithonel__ has joined #ocaml
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
<flux> and 0.0.3 vs 0.0.13 works like in debian?
<thelema_> 0.0.3 < 0.0.13
<thelema_> the number groups are turned into ints before comparison
<thelema_> at least in odb, I assume something even smarter in oasis-db
ftrvxmtrx has joined #ocaml
<flux> there should be a library to guarantee consistency :)
oriba has joined #ocaml
<thelema_> my suggestion for that library:
<thelema_> let to_ver_comp = function Delim s -> Str s | Text s -> Num (int_of_string s)
<thelema_> let parse_ver v =
<thelema_> try full_split (regexp "[^0-9]+") v |> List.map to_ver_comp
<thelema_> with Failure _ -> failwith ("Could not parse version: " ^ v)
<thelema_> (Str has been opened for this)
<flux> soo.. not thread safe then?-)
<thelema_> :P
sepp2k has quit [Quit: Leaving.]
<thelema_> minimal version-number library: http://pastebin.com/Yu0yi6rr
<thelema_> L11: I wonder if I should ignore trailing ".0"s
lamawithonel__ has quit [Ping timeout: 255 seconds]
lamawithonel__ has joined #ocaml
<hcarty> thelema_: Does .tar.gz vs .tar.bz2 matter?
<thelema_> hcarty: .gz better, .bz2 should work
<thelema_> but definitely hackish support in odb
<thelema_> oh, n/m, odb .bz2 just fine. oasis-db, gildor says it should be fine, but iirc, there were some problems
<thelema_> maybe they're fixed. maybe not.
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
<hcarty> Ok, I'll go with .tar.gz
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
lamawithonel__ has quit [Excess Flood]
<hcarty> My modified version of xstrp4 is now odb-able. In theory at least!
lamawithonel__ has joined #ocaml
<thelema_> hcarty: what's the package name?
<thelema_> n/m
<thelema_> yup, it seems to have worked for me - I'll promote it to testing
<hcarty> thelema_: Thank you
<thelema_> fwiw, you can do this kind of administration as well, if you have time
<hcarty> thelema_: I just saw :-) I'm poking around a bit on the interface now
* thelema_ is surprised at the deps
lamawithonel__ has quit [Excess Flood]
* thelema_ wonders what happens if batteries isn't installed
<hcarty> thelema_: It shouldn't depend on batteries
lamawithonel__ has joined #ocaml
<thelema_> it seems that syntax_batteries should, no?
<thelema_> not to compile, but to use
<hcarty> Ah, yes. That does require Batteries to use
<thelema_> so in the meta file, it probably needs batteries
<thelema_> as a require
<hcarty> But I didn't want to make it a firm requirement since syntax_batteries is more of a demo than anything
<thelema_> fair enough.
<hcarty> Ah, I see
<thelema_> I dunno if oasis will make that a compile requirement to put it there.
ulfdoz has quit [Ping timeout: 264 seconds]
<hcarty> I'll check
<hcarty> Doesn't look like it
<thelema_> good.
lamawithonel__ has quit [Excess Flood]
jamii has joined #ocaml
lamawithonel__ has joined #ocaml
lamawithonel__ has quit [Remote host closed the connection]
lamawithonel__ has joined #ocaml
<thelema_> hcarty: can xstrp4 drop the need to escape $ not followed by {?
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
<hcarty> thelema_: $foo interpolates the value foo
<thelema_> $500.00 doesn't interpolate to anything, and shouldn't need escaping
<hcarty> thelema_: That could be removed, requiring $(foo) or ${foo, ...}
<thelema_> POLS?
<hcarty> thelema_: I'm not sure how to handle that sanely
<hcarty> POLS?
<adrien> sanity, who needs sanity?
<thelema_> \$[a-zA-Z.]+ gets expanded
<thelema_> Principle of Least Surprise
<hcarty> Ah
<thelema_> it might be reasonable to apply this expansion to all strings, so the pseudo-keyword "interpolate" could be dropped
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
<thelema_> if the intent is to make common constructs easier, "interpolate" is a quite long keyword to turn this on.
<thelema_> s/easier/easier to type/
<hcarty> thelema_: I don't generally use the interpolate form
robocop has quit [Quit: Quitte]
<hcarty> But then again I haven't used xstrp4 that much
* thelema_ is basing this all on the sample file, which seems to exclusively use interpolate
<hcarty> sample.ml is from the original distribution, but it should still be applicable
<hcarty> An xstrp4-based extension could be created which acts on all strings
<hcarty> And the \$ escaping needs to change anyway, as OCaml gives a warning about an illegal backslash escape
<thelema_> lol
lamawithonel__ has quit [Excess Flood]
<hcarty> thelema_: \$[a-zA-Z.]+ doesn't expand to anything but $[a-zA-Z.]+ (plus the warning, of course...)
<hcarty> thelema_: alpha1 is in the name for a good reason :-)
lamawithonel__ has joined #ocaml
<thelema_> I was just using regexp syntax to specify what strings would be expanded without any ()
<hcarty> thelema_: They are
lamawithonel__ has quit [Excess Flood]
jamii has quit [Read error: Connection reset by peer]
lamawithonel__ has joined #ocaml
<thelema_> well, congrats on your first oasis-db release
bob` has joined #ocaml
<hcarty> thelema_: Thank you
<hcarty> And thank you for the xstrp4 feedback. I appreciate it.
<thelema_> no problem
axiles has quit [Remote host closed the connection]
lamawithonel__ has quit [Ping timeout: 255 seconds]
lamawithonel__ has joined #ocaml
philtor has quit [Ping timeout: 240 seconds]
edwin has quit [Remote host closed the connection]
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
ftrvxmtrx has quit [Read error: Operation timed out]
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
ftrvxmtrx has joined #ocaml
lamawithonel__ has quit [Excess Flood]
lamawithonel__ has joined #ocaml
philtor has joined #ocaml
lamawithonel__ has quit [Ping timeout: 255 seconds]
lamawithonel has joined #ocaml
lamawithonel has quit [Excess Flood]
sepp2k has joined #ocaml
lamawithonel has joined #ocaml
lamawithonel has quit [Excess Flood]
lamawithonel has joined #ocaml
george_z0rwell has joined #ocaml
boscop_ has joined #ocaml
boscop has quit [Disconnected by services]
boscop_ is now known as boscop
boscop has quit [Changing host]
boscop has joined #ocaml
lamawithonel has quit [Ping timeout: 263 seconds]
sepp2k has quit [*.net *.split]
philtor has quit [*.net *.split]
ftrvxmtrx has quit [*.net *.split]
ankit9 has quit [*.net *.split]
Morphous_ has quit [*.net *.split]
impy has quit [*.net *.split]
mal`` has quit [*.net *.split]
pheredhel has quit [*.net *.split]
mfp has quit [*.net *.split]
wtetzner has quit [*.net *.split]
Reaganomicon has quit [*.net *.split]
mal`` has joined #ocaml
philtor has joined #ocaml
ankit9 has joined #ocaml
mfp has joined #ocaml
Morphous_ has joined #ocaml
wtetzner has joined #ocaml
nimred has joined #ocaml
sepp2k has joined #ocaml
ikaros has quit [Quit: Ex-Chat]
lamawithonel has joined #ocaml
lamawithonel has quit [Excess Flood]
lamawithonel has joined #ocaml
ftrvxmtrx has joined #ocaml
pheredhel has joined #ocaml
lamawithonel has quit [Excess Flood]
lamawithonel has joined #ocaml
lamawithonel has quit [Excess Flood]
lamawithonel has joined #ocaml
lamawithonel has quit [Excess Flood]
lamawithonel has joined #ocaml
lamawithonel has quit [Ping timeout: 250 seconds]
lamawithonel has joined #ocaml
lamawithonel has quit [Ping timeout: 250 seconds]
lamawithonel has joined #ocaml
lamawithonel has quit [Excess Flood]
lamawithonel has joined #ocaml
lamawithonel has quit [Read error: Operation timed out]
lamawithonel has joined #ocaml
lamawithonel has quit [Ping timeout: 250 seconds]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Ping timeout: 250 seconds]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
<hcarty> thelema_: When I want to replace xstrp4 with a newer version on oasis-db, is it enough to upload the newer tarball, test, and promote from unstable to testing?
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
oriba has left #ocaml []
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
Morphous_ has quit [Ping timeout: 250 seconds]
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
oriba has joined #ocaml
oriba has left #ocaml []
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
Morphous_ has joined #ocaml
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
eye-scuzzy has quit [Read error: Operation timed out]
lamawithonel_ has quit [Ping timeout: 250 seconds]
lamawithonel_ has joined #ocaml
eye-scuzzy has joined #ocaml
bob` has quit [Ping timeout: 264 seconds]
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
sepp2k has quit [Quit: Leaving.]
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml
lamawithonel_ has quit [Excess Flood]
lamawithonel_ has joined #ocaml