flux changed the topic of #ocaml to: Discussions about the OCaml programming language | http://caml.inria.fr/ | 3.11.0 out now! Get yours from http://caml.inria.fr/ocaml/release.html
malc_ has quit [Read error: 110 (Connection timed out)]
Yoric[DT] has quit ["Ex-Chat"]
alexyk has quit []
pumpkin has joined #ocaml
pumpkin has left #ocaml []
malc__ has quit ["leaving"]
alexyk has joined #ocaml
<alexyk> how do you dump a structure to stdout from an executable in the same way it looks in toplevel?
mauke has joined #ocaml
<thelema> alexyk: can't. toplevel has access to types that gets erased during compilation.
<alexyk> thelema: ok, but then just pretty-print as a tree?
<olegfink> alexyk: sexp.
<alexyk> olegfink: is it a package?
<olegfink> or deriving, if you like haskell.
<olegfink> yep.
<mauke> is there a function for splitting a string into a list of words?
<alexyk> thx!
<alexyk> mauke: Str.split (Str.regexp " ") words
<alexyk> olegfink: will it print a whole list or array of tuples and things?
<olegfink> that's the intent
<mauke> ah, Str.regexp "[ \t\n]+" seems to work
<alexyk> mauke: yep, stick any non-words crap in there
<mauke> alexyk: plain " " doesn't work for consecutive spaces
<olegfink> alexyk: see sections 4.5 and 4.9 of the readme
gaja has quit ["leaving"]
<alexyk> ok here's a serious fun challenge: transpose a list of lists, m by k -- in a fastest and most efficient way, also lookin' good :)
<alexyk> we have m lists of k elements each, now want k of m, lik etransposing a matrix
<olegfink> use metaocaml :-)
<alexyk> olegfink: well I'm in a real one for now :)
<olegfink> :/ without metaocaml it's just plain coding
<alexyk> olegfink: what's metaocaml anyway? can I compile it and link with the regular one?
<mauke> would it be cheating to copy the definition from Haskell?
<olegfink> metaocaml is a MSP extension for ocaml, and unfortunately no, you can't
<olegfink> hmm, no, seems I can't do what I want
<alexyk> mauke: if it works in ocaml, that's fine :)
<alexyk> olegfink: what's MSP?
<olegfink> multi-stage programming, see http://metaocaml.org/
<olegfink> but for now I failed miserably to build a transpose function with it
Axioplase has quit ["Lost terminal"]
<alexyk> ok, if range0 n is 0..(n-1), here we go:
<alexyk> List.map (fun n -> List.map (fun li -> List.nth li n) lili) (range0 ((List.length (List.hd lili))-1))
<alexyk> where lili is the original list of lists
<alexyk> and range0 is trivial :)
<olegfink> you can simplify the line a bit using something like (>>)
<mauke> seems to run
Axioplase has joined #ocaml
<alexyk> olegfink: what does >> do?
<alexyk> F#'s |> ? :)
<olegfink> in my personal world, x >> f is f x
<olegfink> yep.
<alexyk> well, it's officially |> now then :)
<alexyk> the collective supercedes the personal, comrade :)
<alexyk> and | looks like pipeline, so it's even makes sense
<olegfink> hmm, it's too late here, so I have a really strange version of transpose
<olegfink> let rec transpose list = try List.map List.hd list :: transpose (List.map List.tl list) with Failure "tl" -> [];;
<olegfink> can't think of better way checking for the [].
<alexyk> wow
<alexyk> it actually is more list-like
<alexyk> but we can't pattern-match nicely on a lili so we have to raise, right?
<olegfink> why, we can, something like []::_ should do
<olegfink> but it doesn't look 'nice'
<alexyk> mauke: interesting, but complex :)
<olegfink> let rec transpose = function []::_ -> [] | list -> List.map List.hd list :: transpose (List.map List.tl list);;
<olegfink> this should do.
<mauke> alexyk: I blame OCaml's lack of list comprehensions :-)
<alexyk> olegfink: awesome! now I can go eat something happily :)
alexyk has quit []
<olegfink> but it's probably slow as hell, O(n*(n+m))
<thelema> olegfink: umm, your first match is wierd -- if the input is a list that starts with the empty list, return the empty list.
<olegfink> hehe, yeah, and then I finally understood why my solution happened to be smaller than mauke's haskell translation
<olegfink> if I handle everything correctly, I'll get the haskell version
* olegfink tries to find some justification for his actions on #ocaml
<olegfink> this first match was meant to say 'if we have finished deconstructing the lists'
<olegfink> thelema: wait, what's the correct transposition of [[];[];[]]?
<olegfink> Prelude Data.List> transpose [[],[],[]]
<olegfink> []
<olegfink> hm
<olegfink> then I don't get where my version is wrong
alexyk has joined #ocaml
<alexyk> olegfink: are you in .ru? :)
<eydaimon> alexyk: I'd guess germany
<alexyk> eydaimon: how? :)
<mauke> % dnsname 62.141.52.142
<mauke> ns.km13836-23.keymachine.de
<eydaimon> $ geoiplookup 62.141.52.142
<eydaimon> GeoIP Country Edition: DE, Germany
<alexyk> ah, I use colloquy which doesn't show raw things by default
<mauke> /whois
<alexyk> ah, right-click does
<alexyk> right-click same as \/whois
<alexyk> mac rules
<eydaimon> if you use irssi, I wrote a script called 'whereis' which is handy :)
alexyk has quit [Remote closed the connection]
alexyk has joined #ocaml
<alexyk> ha, I said mac rules and collouy crashed
<olegfink> alexyk: nah, that's just Stirlitz mode, I'm actually in .ru
<alexyk> olegfink: SPb or Moscow?
<olegfink> spb
<alexyk> what a boatload of crap this guy generates, while at google
<alexyk> olegfink: SPb is much like Seattle, very good for programming through bad weather :) in a cafe with a double latte
<olegfink> heh, I've never been to seattle, but I believe you, my friends live there.
<olegfink> and you are somewhere in the northeast, far from seattle?
<alexyk> I consulted in SPb last summer and it was a blast... now I moved back east to Dartmouth, near Boston
<alexyk> In SPb I stayed on the Griboyedov's canal, and could go into a cafe 24 hours a day, the chain name suddenly escapes me, it's all over...
<alexyk> SPb is a very FP-friendly city :)
<olegfink> heh, I still can't find the time to get to SPbHUG meetings, people say they're pretty interesting
<alexyk> ah, the blasted "kofehauz" :)
<alexyk> (such a non-name you forget it in 1 year)
<olegfink> mneh, I don't like it for some reason
<olegfink> they have too many cafes in the network to be any good.
<alexyk> it's like starbucks in the US... instead folks in Seattle prefer small artisan coffee houses...
<alexyk> but generally one can't imagine a better place to program than in a cafe in SPb overlooking a canal with wifi
<olegfink> well, my flat isn't a bad place as well, though there's that stupid building because of which I can't see Neva out of my window
<olegfink> alexyk: tell me where exactly does my transpose suck.
<alexyk> olegfink: why, you transpose is super!
<alexyk> I'm busy sticking it into my PhD-grade system :)
<olegfink> it's really a stripped down version of the haskell transpose, so there ought to be cases when it behaves incorrectly.
<alexyk> well I have a rectangular lili, so I won't have any edge cases
<olegfink> (I realised that after some meditation on the haskell version, long after writing my own, and I still don't quite understand the former)
<olegfink> Prelude Data.List> transpose [[1,2],[1,2,3]]
<olegfink> [[1,1],[2,2],[3]]
<olegfink> ah, right
<olegfink> funny, I should really go to sleep now, I didn't even think about non-rectangular matrices :/
<olegfink> alexyk: what's your thesis, btw?
<alexyk> well it's still open-ended, but generally treating real-world sensor data as a language, and applying computational linguistics methods to it
<alexyk> so all the nice OCaml and Haskell NLP tools come in handy
<alexyk> inferring people behavior with ocaml hacks :)
<olegfink> cool, so you probably know about Shan's master thesis?
<olegfink> I don't understand most of it, but it looks cool.
<alexyk> Шень? :)
<alexyk> or not, am not sure
<alexyk> ah interesting; but it's more into the formal methods side, and I'm a rather probabilistic bayesian guy, reality is nothing like Haskell :)
<olegfink> yeah, but the thing shan's doing to linguistics looks for a lowlife like me like an absolutely different level of understanding things.
dfritz has joined #ocaml
<olegfink> but real-world things rule as well
<alexyk> olegfink: interesting, am gonna peruse it :)
<alexyk> the word Shan has a specific meaning to 57ites :)
<olegfink> you mean in the variant Shen?
<alexyk> exactly
<dfritz> Does anyone know how I can get the up arrow to work in Read-Evaluate-Print mode? Whenever I press up i get "^[[A." I know I have to put my terminal into different mode but I cannot remember the specific command.
<alexyk> olegfink: so his fame spread to SPb? :)
<alexyk> dfritz: programmer-monk.net => readline
<alexyk> dfritz: or rlwrap
<mauke> dfritz: that's not a terminal mode, you need a program that interprets special keys, keeps a history, etc
<olegfink> advert_mode "use acme"
<olegfink> alexyk: 'to' or 'from'? I thought he's more in spb...
<alexyk> olegfink: probably... to us he was in Moscow :) may be he is a dual-headed deity
<alexyk> ok, I need to very quickly debug, then decorate my xmas tree! bye for now
<olegfink> hmm, at least I attended his lectures at PDMI for sure.
ygrek has quit [Remote closed the connection]
<olegfink> have fun
alexyk has quit []
rhar has joined #ocaml
<dfritz> mauke: I installed readline like alexyk described but in the ocaml interpreter I still cannot access the previous statement with the up arrow. Is there anything else I need to do
Optikal__ has joined #ocaml
<mtoups> hi folks, getting a compile error on the following line i can't figure out: let outchannel = Pervasives.open_out_gen ([Open_wronly;Open_creat;Open_binary]) (0o640) Sys.argv(2) in
<mtoups> yields:
<mtoups> This function is applied to too many arguments,
<mtoups> maybe you forgot a `;'
<mtoups> Pervasives.open_out_gen definitely has type open_flag list -> int -> string -> out_channel
<mtoups> am i missing something obvious here?
s4tan has quit []
<olegfink> mtoups: Sys.argv(2) are two tokens, you want Sys.argv.(2)
<olegfink> dfritz: you probably have to build a custom toplevel which will use readline.
<dfritz> olegfink: I just found what i was looking for. if i start the toplevel with `ledit ocaml` i can use my arrows fine.
<mtoups> ahhhh the .
<mtoups> olegfink: thanks
<olegfink> yep, that's an option.
jeddhaberstro has quit []
<thelema> what was the reason for binary incompatibility across ocamlc releases?
TaXules has quit [Remote closed the connection]
Mr_Awesome has quit [Read error: 110 (Connection timed out)]
Mr_Awesome has joined #ocaml
rhar has quit ["This computer has gone to sleep"]
rhar has joined #ocaml
struktured has quit [Connection timed out]
struktured has joined #ocaml
apples` has quit ["Leaving"]
Mr_Awesome has quit [Read error: 110 (Connection timed out)]
dfritz has quit [Read error: 60 (Operation timed out)]
sporkmonger has quit []
Amorphous has quit [Read error: 110 (Connection timed out)]
Amorphous has joined #ocaml
Associat0r has joined #ocaml
Mr_Awesome has joined #ocaml
dfritz has joined #ocaml
ygrek has joined #ocaml
<flux> mfp, it would sort of spawn a new process. perhaps like: spawn (fun () -> let rec loop () = sync (receive chan) >>= fun msg -> print_endline msg; loop () in loop ()) >>= fun () -> ..keep doing something else..
Associat0r has quit []
Snark has joined #ocaml
rhar has quit ["Leaving"]
alexyk has joined #ocaml
<alexyk> is there a binary search on array in the library?
<flux> no
<flux> fortunately ocaml is such a great language for expressing algorithms, that you'll be ready in no time :)
dfritz_ has joined #ocaml
<alexyk> flux: well, get an edge case wrong, and you regret it's not in the library
<alexyk> I wonder how many li'l libraries are shuffled around by ocaml programmers until batteries take hold
dfritz has quit [Read error: 110 (Connection timed out)]
dfritz has joined #ocaml
ygrek has quit [Remote closed the connection]
dfritz_ has quit [Read error: 110 (Connection timed out)]
_zack has joined #ocaml
_zack has quit ["Leaving."]
asabil has quit [Read error: 110 (Connection timed out)]
_zack has joined #ocaml
ygrek has joined #ocaml
love-pingoo has joined #ocaml
love-pingoo has quit [Read error: 60 (Operation timed out)]
asabil has joined #ocaml
__me has joined #ocaml
<mfp> flux: then what you're looking for is a (unit -> 'a Lwt.t) -> unit function
<mfp> and, most counterintuitively, it is let spawn f = ignore (f ()) seriously
love-pingoo has joined #ocaml
Camarade_Tux has joined #ocaml
Palace_Chan has quit [Client Quit]
Kerris7 has quit ["Who is Candlejack? Is he going to c"]
MelanomaSky has quit ["leaving"]
rwmjones has joined #ocaml
Camarade_Tux has quit ["Leaving"]
rwmjones has quit [Read error: 104 (Connection reset by peer)]
Snark has quit ["Ex-Chat"]
Kerris7 has joined #ocaml
__me has left #ocaml []
__me has joined #ocaml
Yoric[DT] has joined #ocaml
vixey has joined #ocaml
hkBst has joined #ocaml
marmotine has joined #ocaml
__me has left #ocaml []
<flux> mfp, you can spawn a new thread without being in the monad?
<flux> or task, or tasklet, or whatever :)
ikaros has joined #ocaml
ygrek has quit [Remote closed the connection]
Kerris7 has quit [Read error: 60 (Operation timed out)]
vixey has quit [Remote closed the connection]
gaja has joined #ocaml
sporkmonger has joined #ocaml
vixey has joined #ocaml
<mfp> flux: yes, I realized that when I saw Lwt_preemptive.init (: int -> int -> (string -> unit) -> 'a Lwt.t) being used this way -> ignore (Lwt_preemptive.init minthreads maxthreads Ocsigen_messages.errlog);
<mfp> if the thread would block (e.g. IO op), it is added to an internal queue
<mfp> ah, you need to be within the Lwt.t monad at some point, though, if you want control to go back to blocked threads
TaXules has joined #ocaml
ygrek has joined #ocaml
__me has joined #ocaml
<flux> mfp, yes, I want to stay inside the monad
<mfp> then ignore should do
struktured has quit [Read error: 110 (Connection timed out)]
<mfp> flux: this is how ocsigen listens on incoming ports: let wait_end_init = wait () in List.iter (fun i -> ignore (listen false i wait_end_init)) ports; where listen does wait_end_init >>= fun () -> wait_connection ...
<mfp> when the init is done, it does wakeup wait_end_init (); and the server is up
<flux> hmm
<flux> interesting :)
alexyk has quit []
ygrek has quit [Remote closed the connection]
pango_ has quit [Remote closed the connection]
pango_- has joined #ocaml
Gionne has joined #ocaml
pango_- is now known as pango_
<Gionne> hello, i don't understand why this doesn't work http://pastebin.com/m606ccfcb
<Yoric[DT]> Gionne: too complex, try to find something shorter if you want people to inspect it :)
<Smerdyakov> Holy smokes. I second Yoric[DT]'s assessment.
<Gionne> ok i'l try to clarify it in my mind first.
<Smerdyakov> Not to mention that the code contains no specification, so it's impossible for us to know what Gionne means by "work."
<Yoric[DT]> I guess it means "compile".
<Gionne> yes compile
<Gionne> ;)
<Gionne> it is the calc_first at line 46 that has problems
<Gionne> the problem is that i have a [<fun>] as a result while i need the <fun> result
<Yoric[DT]> Usual advice: try and narrow it down to a short extract.
<flux> I did'nt look (on a mobile), but often adding explicit type annotations can help tracking down type problems
<Gionne> i'll try
love-pingoo has quit ["Connection reset by pear"]
Demitar_ has joined #ocaml
Flodis has joined #ocaml
willb has quit [Connection timed out]
Demitar_ has quit ["Burn the land and boil the sea. You can't take the sky from me."]
<Gionne> sorry, i can't handle this problem yet: i have a list of <fun> - : (string * '_a -> string * (bool * symbol list)) list how do i print results? sorry for asking again.
<flux> mfp, indeed, (return () >>= fun _ -> Printf.printf "Plop"; return ()) works as if by magic
<flux> mfp, I suppose it runs in its own thread then
<flux> (from the toplevel that is)
<mfp> are you just ignoring the result when applied to ()?
<mfp> in that case, everything should be executed right away
<flux> I'm entering that expression in the toplevel
<flux> I would b expecting to receive unit Lwt.t I would need to apply to some function
<mfp> misread it
<flux> ah, neve rmind
<flux> I guess return () >>= _ would evaluate immediately anyway?
<flux> need to try more :)
<mfp> everything will be evaluated until it finds a blocking call
<mfp> like Lwt.wait or Lwt_unix.read
<flux> Lwt doesn't seme to have the concept of 'channels', does it?
<mfp> the current Lwt.t gets registered in some queue and will be resumed later, when another thread is blocked and the system reschedules the threads
<flux> threading the blocked Lwt.t around for someone to Lwt.wakeup it looks difficult
<mfp> no channels IIRC
<flux> I wonder how one would go aroud implementing the Event-module for Lwt given the primitives it provides
<mfp> needs not be Lwt.wakeup, just another thread doing Lwt_unix.read would reschedule
<mfp> uhm I might have implemented this before actually
<flux> wakeup (wait () >>= fun _ -> Printf.printf "plop\n%!"; return ()) () does absolutely nothing?
<flux> I would not use unix domain sockets for IPC, if I can avoid it (I may not be able to), especially if I already have light-weight threads..
<mfp> ah I'd just implemented MVars on top of Lwt -> http://eigenclass.org/hiki/lightweight-threads-with-lwt
_zack has quit ["Leaving."]
ikaros has quit [Read error: 110 (Connection timed out)]
<flux> I suppose channels too should be feasible
ikaros has joined #ocaml
<flux> right, you use ignore_result to make the thing tick?
<mfp> seems so :P
<mfp> I don't have much more info than you at this point, I barely remembered I had written this :|
<mfp> righto, the critical part is this pattern match in ignore_result: | Sleep -> add_waiter x (fun x -> ignore_result x)
pango_ has quit [Remote closed the connection]
<mfp> actually, ignore works too
<mfp> I don't know why the above thing with wakeup doesn't do anything
<flux> I would love to have (async) Lwt_event. perhaps one day I will :)
<mfp> if I try to wakeup unit Lwt.t twice, I get an Invalid_argument "wakeup", meaning the state has changed from Sleep to something else
willb has joined #ocaml
pango_ has joined #ocaml
<flux> https://webdav.seas.upenn.edu/viewvc/unison/branches/merge/src/lwt/example/relay.ml?view=markup&rev=1 makes things run with Lwt_unix.run, which is how I'd expect things to work..
<flux> hmm.. how hard would it be to have a campl4 extension, that instead of providing a "do" notation, would transform code in form let a = 42 in let! b = return 43 in let !c = foo b in return 0 .. to let a = 42 in return 43 >>= fun b -> .. etc?
<flux> looks like it should be simpler than the do.. <-- -extension?
<flux> and more fitting to the rest of the syntax, no?
<flux> (let !c should be let! c)
<mfp> I tried to add support for let! x = ... to pa_monad a couple days ago in fact
<mfp> ran into some problem and killed the thing with git reset --hard
<flux> :)
<flux> well, pa_monad is quite a big beast in itself. is it even worth using it as a base? you preserved the 'perform' keyword?
<flux> (which does give some nice features, like defining the monad to use; but in interaction with pa_openin that could perhaps be not needed)
<mfp> it does the xxx; yyy => bind xxx (fun () -> yyy) for me
<flux> right, forgot about that :)
<flux> let! _ = .. in .. would be perhaps less convenient
<flux> (or even let! () = .. )
<mfp> it'd be let! () = ... in but OTOH no longer let () = ... in
<mfp> so maybe no special ; handling would be better
<flux> most of the time I want some return value anyway
<flux> and also it messes up the indentation if I chain let a = .. in and non-let expressions :)
<mfp> could have perform' and perform, with and without ; as bind
<flux> what would you need perform for, if you have let! and no ;?
<flux> (and you assume current >>= operator)
<mfp> perform allows to specify the monad module
<mfp> or >>= plus fail
<flux> but as I said, using open Foo in.. would cover that functionality?
<mfp> could probably do without, with open_in
<mfp> right
<flux> I usually open the module with the >>= operator anyway
<mfp> so hmmm let! x = and ; with the current meaning or perform + ; as bind, a single extension could support both for convenience
<flux> that sounds like a plan :)
alexyk has joined #ocaml
__me has left #ocaml []
olegfink has quit [Remote closed the connection]
<flux> (although, I could live without perform if it simplified the extension significantly)
asabil has quit ["Ex-Chat"]
Flodis1 has joined #ocaml
glondu`` has quit [Read error: 104 (Connection reset by peer)]
glondu`` has joined #ocaml
<mfp> glondu``: I recognized your name + host from the ocsigen ML... mind a quick ocsigen question?
Flodis has quit [Read error: 110 (Connection timed out)]
Flodis1 has quit ["Leaving."]
apples` has joined #ocaml
Gionne has quit ["Leaving"]
<flux> pft.. I've been trying to write a monad that constructs Event.events for ages, I'm considering to use prolog to infer my types :)
vixey has quit [No route to host]
ikaros has quit [".quit"]
rwmjones has joined #ocaml
itewsh has joined #ocaml
vixey has joined #ocaml
Camarade_Tux has joined #ocaml
kig has joined #ocaml
ikaros has joined #ocaml
willb has quit ["Leaving"]
olegfink has joined #ocaml
ikaros has quit [".quit"]
itewsh has quit [Remote closed the connection]
rwmjones has quit ["Leaving"]
<alexyk> so how many people recompiled ocaml from cvs in godi?
<alexyk> http://alain.frisch.fr/natdynlink.html says to reconfigure godi-ocaml-src, which I did, but that just builds a godi package 3.10.2godi99, and doesn't rebuild ocaml and everything else by itself
<mfp> I built 3.11.0+beta2-dev2 that way and don't remember doing anything different from what's described in that page
* mfp checks in godi_console
<alexyk> well after updating godi-ocaml-src, I now go and try to rebuild godi-ocaml, it shows (from source) as an option, and test configuration shows /opt/godi/lib/godi/saved-src/ocaml.tar.gz which is made just now -- then godi fails
<mfp> ah I have OCAML_CVS_REVISION = release311
<alexyk> busy...Fatal error: exception Assert_failure("godi_plan.ml", 741, 20)
<alexyk> mfp: nice, does it build the native toplevel then?
<mfp> nope, the toplevel is not built by default
<alexyk> well my godi has no plan anymore :(
<mfp> I'd have to drop a patch somewhere in godi's build dir to enable it, I suppose
<mfp> can you install from scratch? it's going to recompile everything anyway, so you're not losing that much
<alexyk> mfp: is godi updated to 3.11 already?
<mfp> AFAIK not, but I installed 3.11.0+beta2-dev2 using godi-ocaml-src
<alexyk> ok... well my godi's broken now, so I have to fix it first -- have many packages selected, am lazy to redo it manually
<mfp> I'm fairly new to GODI (just installed it to try 3.11 + Batteries, normally use Debian), don't know where that list is stored
Stefan_vK has joined #ocaml
<alexyk> do folks write to caml-list for godi problems?
<alexyk> I'm hitting an assertion failure so that's one
<Camarade_Tux> there's a godi-list
Stefan_vK1 has quit [Read error: 110 (Connection timed out)]
willb has joined #ocaml
Palace_Chan has joined #ocaml
<alexyk> ok -- godi breaks with the cvs ocaml for me... anyone done it right?
<alexyk> (trying again...)
glondu`` is now known as glondu
<glondu> mfp: still need me?
pumpkin has joined #ocaml
mohbana_ has joined #ocaml
<mohbana_> hi, any (good) papers that compare alice and ocaml
pumpkin has left #ocaml []
<mfp> glondu: hi, I'm thinking about building (native) ocsigen apps statically, without using Dynload or anything, to simplify deployment
<mfp> glondu: I've been taking a look at the code and it seems to be possible, but I wanted to ask you if you can foresee problems with this
<mfp> looks like I essentially have to change server/server.ml to turn the let _ = ... at the bottom into some function of type (unit -> unit) -> unit accepting a function that will register the extensions
<mfp> plus add the functions needed for the hook to the desired exts
<mfp> that is, move let _ = register_extension ... to another file, linked into eliom.cma but ignored when building a standalone app
<glondu> ù
<glondu> mfp: I guess you can just intermix extension and modules with the equivalent of let _ = ...
<glondu> a priori, you shouldn't need to touch the extensions themselves
<mfp> well eliom for instance has got let _ = register_extension ..., so it'd try to register itself when the module is initialized
<mfp> is it OK if that happens before the server does whatever it normally does before the Dynload stuff?
<glondu> mfp: oh, you're right for eliom
<mfp> s/Dynload/Dynlink/
<mfp> it's a pity there's no way to detect whether a module is being loaded with dynlink or not
<mfp> things would be easier then, just let _ = if Dynload.loading_current_module () then register_extension ...
mohbana_ has left #ocaml []
<mfp> I guess a new global variable to indicate whether Dynlink is in use or not would do
<mfp> argh s/Dynload/Dynlink/ again what's wrong with me
<glondu> mfp: hmmm... I don't think the register_extension is a problem
<glondu> it can be called if the module is statically linked
<mfp> so it's ignored if it happens before the server is ready, or idempotent?
<alexyk> mfp: at which point did you edit godi ocaml-src, and what did you do next -- just rebuild godi-ocaml?
<alexyk> I couldn't get the boostrap_stage2 going after manually editing godi.conf with release311
<mfp> alexyk: sorry, don't remember really. I think I just configured godi-ocaml-src and selected also godi-ocaml
<alexyk> mfp: ok, so you just installed godi as usual, and then did it from menus, right?
<mfp> hmmm I don't remember editing godi.conf actually
<mfp> yes
<alexyk> okok
<mfp> configure godi-ocaml-src, set OCAML_CVS_REVISION = release311
<alexyk> mfp: yup, in old godi that lead to assert failure, will try with a fresh one
<mfp> weird, worked for me
<mfp> was going to update to 3.11.0 (from beta2), but I think I'll install from scratch to a diff dir to make sure I don't lose the current, working, one
<mfp> will tell you if it works
<mfp> glondu: thanks, I'll see what happens when linking everything statically and compiling with ocamlopt, might come up with something to show on the ML
* mfp afk for a while
snhmib has quit ["Good riddance!"]
snhmib has joined #ocaml
Camarade_Tux has quit ["Leaving"]
<glondu> mfp: IIRC, Ocsigen performs some global side-effects before dynlinking a module to make its configuration available to it; you have to do the same, of course (this can be done by inserting small modules between each extension on the linker call)
<glondu> however, I've never tried this myself
BlackHC| has joined #ocaml
<BlackHC|> hello
<BlackHC|> I have a hugely annoying issue with OcamlBrowser
<BlackHC|> when I run ocaml from the command line and use #load and open on a custom module it works
<BlackHC|> when I do the same in OcamlBrowser's Shell it fails with "Unbound module"
<BlackHC|> Im using Windows Vista
<BlackHC|> and Ive wasted a stupid hour on this issue already
<BlackHC|> using ocaml 3.10.2
<alexyk> anybody aware of ngram models in ocaml?
jeddhaberstro has joined #ocaml
rpg_ has quit [Remote closed the connection]
kig has quit [Remote closed the connection]
alexyk has quit []
marmotine has quit ["mv marmotine Laurie"]
Yoric[DT] has quit ["Ex-Chat"]
<mfp> glondu: yes, saw that, I'll try :)
<mfp> BlackHC|: oh never used the OCamlBrowser shell before, any reason to prefer it to the ocaml toplevel?
<BlackHC|> you have an editor too
<BlackHC|> and can easily load it in the shell for further testing
<mfp> BlackHC|: I think you have to use the #directory directive to let the toplevel find the .cmi files
<BlackHC|> hmm weird
<BlackHC|> I just used open first
<BlackHC|> and then #load
<BlackHC|> and it seems to work now :
<BlackHC|> :o
<BlackHC|> I dont get it
<mfp> now that's weird
<mfp> maybe a conflicting name?
<BlackHC|> dunno
<BlackHC|> Ive added to the paths in the browser
<BlackHC|> and then Ive started the shell
seafood has joined #ocaml
vixey has quit ["There exists an infinite set!"]
hkBst has quit [Connection reset by peer]