<xificurC>
the last line says - : int = 12 , so the return type is int, not int Lwt.t, right?
<Leonidas>
xificurC: utop unwraps Lwt.t
<Leonidas>
(automatically)
<Leonidas>
xificurC: let r = Lwt.bind (Lwt_io.read_line Lwt_io.stdin) (fun s -> Lwt.return ((int_of_string s) + 1));;
<Leonidas>
val r : int Lwt.t = <abstr>
<Leonidas>
-> int Lwt.t
<xificurC>
Leonidas: that explains a lot. I'll go to the ocal top-level then, this is confusing
mengu has joined #ocaml
AlexRussia has quit [Ping timeout: 265 seconds]
<Leonidas>
xificurC: but I'd rather write it like this:
<Leonidas>
Lwt_io.read_line Lwt_io.stdin >|= (fun s -> int_of_string s + 1);;
<Leonidas>
(>|=) is Lwt.map
<xificurC>
cool
<xificurC>
let me try that in ocaml toplevel
<Leonidas>
(>>=) is Lwt.bind
<Leonidas>
(open Lwt.Infix)
<Leonidas>
xificurC: it is not really confusing, actaully it is rather handy, since you can see the value of your Lwt-wrapped stuff directly without having to >|= some_printer_fn your results :-)
AlexRussia has joined #ocaml
<Leonidas>
ok, maybe a bit confusing if you don't know about it
<xificurC>
Leonidas: yeah, I imagine it is helpful, but it really confused me with the types
<xificurC>
and now my code hangs when I run it in ocaml
<xificurC>
doesn't seem to stop after entering newline
<xificurC>
/s/entering newline/hitting enter/
<Leonidas>
whitequark: I am wondering, can I somehow generate native code from the ocaml bindings? Llvm_target.TargetManchine.emit_to_file can emit object data or assembly, but I want an executable.
<Leonidas>
xificurC: I imagine lwt does not play well with the toplevel
<Leonidas>
I guess utop does some magic to make it work nevertheless
<companion_cube>
xificurC: I tried let r = Lwt.bind .......;;
codefo has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<companion_cube>
it waits for an input line
<xificurC>
do you guys use utop
<companion_cube>
then, the toplevel works again
<companion_cube>
yes
<Leonidas>
of course
<xificurC>
lwt manual said I had to #require "lwt.simple-top" but it's completely messed up now :)
<xificurC>
ok, I'll stick to utop then, bearing in mind the *magic*
AlexRussia has quit [Ping timeout: 264 seconds]
<xificurC>
is there anything useful I should include in my .ocamlinit?
<Leonidas>
I was wondering whether this unwrapping can be disabled, but apparently not
zpe has quit [Remote host closed the connection]
<xificurC>
lwt looks like a monad
<Leonidas>
it is
<xificurC>
cool, at least something I got right today. Should I care about the syntax extensions mentioned at the end of the manual?
<xificurC>
is it widely used
<reynir>
or Lwt_io.read_line Lwt_io.stdin >|= int_of_string >|= (+) 1
<reynir>
oh I was scrolled up
<Leonidas>
xificurC: I use the syntax extension, but not the camlp4-one but rather the ppx-one
<Leonidas>
I think it is useful, but if I had to chose between camlp4 and no-camlp4 it would be the latter almost always.
<xificurC>
Leonidas: checking it out, thanks. One last question (for now), do you open anything globally? Or do you just always type out Lwt_io.stdin and stuff
<reynir>
3.11.2 makes me sad
<Leonidas>
xificurC: I only open Lwt.Infix globally
<Leonidas>
sometimes I alias modules to shorter names.
<whitequark>
Leonidas: you need a linker for that
<whitequark>
shell out.
<whitequark>
there is no linker you can programmaticaly drive, for now.
<Leonidas>
whitequark: ok, thanks. So I am not overlooking anything.
<Leonidas>
whitequark: while at it, can I somehow emulate what "opt" does via the API?
<whitequark>
what specifically?
<whitequark>
opt does a lot of things.
<Leonidas>
whitequark: optimizing a bitcode file, like opt -O3.
<companion_cube>
oh, maybe you need to install ppx_tools
<companion_cube>
(I suspect lwt.ppx uses ppx_tools.metaquot)
<xificurC>
companion_cube: I have ppx_toold 0.99.2
<xificurC>
tools too
Haudegen has joined #ocaml
<xificurC>
should I run anything in utop before that?
<companion_cube>
I just run : #use "topfind";; #require "lwt.ppx";;
<xificurC>
companion_cube: that works :) You wrote #use "lwt.ppx" before
<xificurC>
and I didn't run #use "topfind"
<reynir>
oh you're not using utop anymore?
<companion_cube>
ohh
<companion_cube>
sorry
<reynir>
I think you don't need to do #use "topfind" in utop.
<companion_cube>
it's #require "lwt.ppx";; of course
<reynir>
oh nvm
<xificurC>
companion_cube: thanks
fedjo has quit [Quit: Leaving.]
fedjo has joined #ocaml
_andre has joined #ocaml
<kakadu>
Reventlov: Does non-profilable version compile successfully?
ygrek has quit [Ping timeout: 264 seconds]
mengu has joined #ocaml
larhat1 has joined #ocaml
thomasga has joined #ocaml
larhat has quit [Ping timeout: 246 seconds]
sdothum has joined #ocaml
siddharthv_away is now known as siddharthv
lordkryss has joined #ocaml
thomasga has quit [Quit: Leaving.]
mengu has quit [Remote host closed the connection]
siddharthv is now known as siddharthv_away
<Reventlov>
Kakadu: yup.
thomasga has joined #ocaml
mengu has joined #ocaml
reem has joined #ocaml
reem has quit [Ping timeout: 256 seconds]
thomasga has quit [Quit: Leaving.]
badkins has joined #ocaml
ghostpl_ has quit [Remote host closed the connection]
xavierm02 has joined #ocaml
<xavierm02>
Hi, I'm trying to have trees to represent stuff and I'd like to encode in the type that some constructors weren't used so that I can make some simplification functions and then not have to match everything. Is that possible? Thank you in advance for your answers. http://pastebin.com/aMCbZ0k4 (for this example, a yes expr is an expr containing a Y and a no expr is an expression not containing one)
<companion_cube>
well you already have a GADT?
<companion_cube>
if a function requires a no expr, the yes cases will not have to be matched
<companion_cube>
you already did everything required
<xavierm02>
companion_cube: The problem is in the transformation f, I get a type error. http://pastebin.com/a04WbDTC
<ggole>
You could use polymorphic variants
<ggole>
In general though, trying to do this is painful.
<ggole>
Another (rather verbose) option is to define different types for each pass
AlexRussia has joined #ocaml
<companion_cube>
also, in GADT you cannot easily deal with several branches
<companion_cube>
xavierm02: you were almost there. look at the differences
mengu has quit [Remote host closed the connection]
paradoja has joined #ocaml
<xavierm02>
companion_cube: Thanks. I had tried with type but hadn't copied the " -> F1 (f x, f y)" part. I thought it was just syntactic sugar but apparently it's not >_<
shinnya has joined #ocaml
<companion_cube>
it's harder to infer in presence of GADTs, apparently
<companion_cube>
GADTs have lots of small traps like this
<ousado>
also the cases have different types
ygrek has joined #ocaml
<xavierm02>
ah right. The Fi forced the type of the arguments. That's why it didnt' want it >_<
c74d has quit [Remote host closed the connection]
ghostpl_ has joined #ocaml
paradoja has quit [Ping timeout: 256 seconds]
<ousado>
hm, how would one write that example with an explicit parameter?
c74d has joined #ocaml
<ousado>
let rec f ( e : type maybe . maybe expr) : no expr = match e with ... <- I get a syntax error for this one
freling has joined #ocaml
<ousado>
Error: This '(' might be unmatched
zoetus has joined #ocaml
<zoetus>
hello everyone!
<ggole>
ousado: let f : .<type> = fun arg1 arg2 -> body
<zoetus>
i have a quick question about .mli files
<zoetus>
if i create a file foo.mli and define a signature in there, shouldn't i be able to refer to the module type Foo in other places?
<ousado>
ggole: ah, ok, thanks
<whitequark>
module type of Foo
<whitequark>
not module type Foo
<zoetus>
oh
<ggole>
Hmm, there's some sugar for (type a), too...
<ggole>
let rec f (type a) (expr : a expr) : no expr = match expr with ...
<ggole>
I find this form confusing though
<zoetus>
i mean, why can't i do something like `let m = (module M : Foo)`
<zoetus>
where `M` is some other module conforming to the signature
AlexRussia has quit [Ping timeout: 256 seconds]
<ggole>
Because Foo is a module, not a module type
<zoetus>
oh, even if i didn't give an implementation that corresponds with foo.mli?
<ggole>
Yep
<zoetus>
ah, i see
<zoetus>
so is there any way to define this module type at the top level? if i define it in foo.mli, I'll have to refer to it everywhere as Foo.Foo, right?
<whitequark>
no, yes
<whitequark>
(by convention module types use UPPERCASE)
<whitequark>
(so, Foo.FOO)
<whitequark>
I usually have a foo_intf.mli somewhere with these.
<ggole>
Well, you can refer to it as module type of Foo
<ggole>
(But that isn't any better.)
<zoetus>
oh gotcha, thanks
<zoetus>
oh you mean, as in `let m = (module M : module type of Foo)`?
<ggole>
Yes.
yminsky has joined #ocaml
<zoetus>
okay, makes sense
<zoetus>
i sometimes wish these file conventions were optional in some way
<ggole>
(Although I don't think that's quite the right syntax...)
AlexRussia has joined #ocaml
<ggole>
Huh, you can't use 'module type of' or 'sig ... end' there
sepp2k has joined #ocaml
<whitequark>
nope. you need an alas
<whitequark>
*alias
dant3 has joined #ocaml
thomasga has joined #ocaml
mengu has joined #ocaml
Algebr has joined #ocaml
yminsky has quit [Quit: yminsky]
jwatzman|work has joined #ocaml
fedjo has quit [Ping timeout: 246 seconds]
oriba has joined #ocaml
yminsky has joined #ocaml
x1n4u has joined #ocaml
yminsky has quit [Quit: yminsky]
pdewacht has quit [Ping timeout: 265 seconds]
paradoja has joined #ocaml
ptc has joined #ocaml
ptc is now known as Guest262
<xificurC>
what should I put in .merlin EXT for it to recognize the lwt ppx syntax extension?
<companion_cube>
nothing, just PKG lwt.ppx
JuggleTux has quit [Quit: Lost terminal]
pdewacht has joined #ocaml
darkf has quit [Quit: Leaving]
<xificurC>
companion_cube: that seems to be working, except it's reporting a strange error
<xificurC>
let%lwt ch = Lwt_io.read_char Lwt_io.stdin in int_of_char ch
<xificurC>
on _in_ it says 'Syntax error inside let, expected and'
freling has quit [Read error: Connection reset by peer]
freling1 has joined #ocaml
freling1 is now known as freling
<xificurC>
forgot to wrap the end in Lwt.return but it's still not working
zoetus has quit [Quit: Page closed]
<Drup>
xificurC: is it at top level ?
<xificurC>
Drup: yes
nullcat_ has quit [Ping timeout: 246 seconds]
<Drup>
"let ... in ..." is not valid at top level
<dmbaturin>
let _ = let ... in ...
shinnya has quit [Ping timeout: 264 seconds]
mengu has quit [Remote host closed the connection]
nullcat_ has joined #ocaml
reem has joined #ocaml
<xificurC>
thanks guys. Is it idiomatic to return unit at the end? Or is let _ ok
<Drup>
unit is better
<xificurC>
also, if I want to try and build it, what do you suggest to use? ocamlbuild? Or is there something more used?
nullcat_ has quit [Ping timeout: 265 seconds]
<companion_cube>
ocamlbuild should be fine
<Algebr>
For cohttp, how do I fire off a request? I see the helpers that wrap this up but I need to fire off a custom built up request
ghostpl_ has quit [Remote host closed the connection]
uris77 has joined #ocaml
<reynir>
what about Sys.argv.(0) ?
<haesbaert>
that "should" be the whatever you typed, not the actually path
<haesbaert>
*actual
<Leonidas>
oh well, might as well check the source code
ptc_ has joined #ocaml
<ggole>
It comes from caml_exe_name... I don't see where that is populated though
<reynir>
for me it's the absolute path even though I only typed "utop"
<haesbaert>
hmm I'm probably wrong then
<Leonidas>
in native code it seems to be always an absolute path
<Leonidas>
according to Changes
Denommus has joined #ocaml
<Leonidas>
ggole is right, it comes from caml_exe_name and that is populated in {asmrun,byterun}/startup.c
maufred has quit [Ping timeout: 252 seconds]
xavierm02 has quit [Ping timeout: 246 seconds]
ghostpl_ has joined #ocaml
maufred has joined #ocaml
<ggole>
Seems it reads /proc/ (on Unix)
<ousado>
whenever I searched for a reliable way to do this, I found there is none
<Leonidas>
looks like it is okay for my purposes
<ggole>
Then it falls back on searching the exe path, finally returning just the name(eg, argv[0]) if nothing can be found
ollehar1 has joined #ocaml
maufred has quit [Ping timeout: 244 seconds]
TheLemonMan has joined #ocaml
maufred has joined #ocaml
oriba has quit [Quit: Verlassend]
TheLemonMan has quit [Client Quit]
<Leonidas>
whitequark: llvm.mli LinkageType seems to be incorrect, there is no Link_once_odr_auto_hid, Dllimport, Dllexport, Ghist, Linker_private or Linker_private_weak as far as I see from the llvm docs.
badon has quit [Read error: Connection reset by peer]
badon_ has joined #ocaml
badon_ is now known as badon
matason has quit [Quit: matason]
MrScout_ has quit [Read error: Connection reset by peer]
tianon has quit [Read error: Connection reset by peer]
matason has joined #ocaml
MrScout_ has joined #ocaml
tianon has joined #ocaml
shinnya has joined #ocaml
marynate has quit [Quit: Leaving]
keen_____ has joined #ocaml
keen____ has quit [Ping timeout: 246 seconds]
dant3 has quit [Remote host closed the connection]
dant3 has joined #ocaml
Mathuin2 has joined #ocaml
<Mathuin2>
hello
<Denommus>
hi
<Mathuin2>
I'm setting up utop and love it so far, but I'd like to get rid of the prompt. I added "UTop.prompt: """ in my utoprc but that doesn't do the trick, any ideas ?
dant3 has quit [Ping timeout: 264 seconds]
<Drup>
there is something about that in the FAQ
reem has quit [Remote host closed the connection]
reem has joined #ocaml
<Mathuin2>
Drup: which said to «set UTop.prompt»
<Mathuin2>
«You can customize the prompt of utop by setting the reference UTop.prompt.»
<Drup>
ah, yeah
<Drup>
that's in .ocamlinit
<Drup>
not in utoprc
<Drup>
it's a caml value
<ggole>
UTop.prompt := "";; in the toplevel?
<zoetus>
so do people have general strategies for mitigating the circular-dependency problem in large projects?
<Mathuin2>
ggole: "Error: This expression has type bytes but an expression was expected of type LTerm_text.t React.signal"
<ggole>
Of course, that would be too easy.
<Drup>
Mathuin2: React.S.const ""
reem has quit [Ping timeout: 246 seconds]
<Mathuin2>
Drup: React is unbound and I can't seem to open it
<def`>
#require "react";;
lnich has quit [Remote host closed the connection]
<def`>
(weird that UTop is bound and not React?!)
<Mathuin2>
«this expression has type bytes React.signal but an expression was expected of type LTerm_text.t React.signal»
<Mathuin2>
def`: this works, thanks
<Mathuin2>
according to the doc, prompt has type LTerm_text.t React.signal Pervasives.ref
<Drup>
oh, LTerm_text.t, fancy
<ggole>
An alias for string? Because of the bytes thing?
<Drup>
nope, it's styled UTF8 codepoint array
tianon has quit [Read error: Connection reset by peer]
<def`>
LTerm_text tries is unicode-sanitized (… or tries at least)
<Drup>
Mathuin2: (LTerm_text.of_string "")
<def`>
utf8* sorry
<Drup>
def`: and styled
<Drup>
it's important
tianon has joined #ocaml
<def`>
:)
<ggole>
Surely the software should do such annoying busywork for you
<Drup>
(otherwise, you could just used zed_rope, and it's more efficient)
<Mathuin2>
Fixed that with «UTop.prompt := React.S.const (LTerm_text.of_string "");;», thanks guys \o/
gal_bolle has joined #ocaml
<Mathuin2>
I'll try making utop run that at every startup
<Drup>
put it in .ocamlinit
<Drup>
that should do it.
ggole has quit []
<gal_bolle>
is it possible to use ocamldebug to debug a program whose sources are not in the current directory? When I try doing that, it won't find the source for my modules
AlexRussia has quit [Ping timeout: 246 seconds]
<Mathuin2>
ok Drup, thanks
<Mathuin2>
thanks all, bue
<Mathuin2>
bye
Mathuin2 has left #ocaml ["WeeChat 1.1.1"]
ptc_ has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
mort___ has quit [Ping timeout: 256 seconds]
Hannibal_Smith has joined #ocaml
Hannibal_Smith has quit [Client Quit]
Anarchos has joined #ocaml
Hannibal_Smith has joined #ocaml
kakadu has quit [Quit: Page closed]
ghostpl_ has quit [Remote host closed the connection]
jwatzman|work has quit [Quit: jwatzman|work]
mort___ has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
yminsky has joined #ocaml
tianon has joined #ocaml
reem has joined #ocaml
paradoja has joined #ocaml
yminsky has quit [Quit: yminsky]
avsm has quit [Quit: Leaving.]
ygrek has quit [Ping timeout: 272 seconds]
thomasga has quit [Quit: Leaving.]
thomasga has joined #ocaml
MrScout_ has quit [Ping timeout: 256 seconds]
jwatzman|work has joined #ocaml
gal_bolle has quit [Quit: Konversation terminated!]
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
dant3 has joined #ocaml
AlexRussia has joined #ocaml
ghostpl_ has joined #ocaml
dant3 has quit [Ping timeout: 252 seconds]
ptc has joined #ocaml
Submarine has joined #ocaml
Submarine has quit [Changing host]
Submarine has joined #ocaml
leowzukw has joined #ocaml
freling has quit [Quit: Leaving.]
kakadu has joined #ocaml
AlexRussia has quit [Ping timeout: 272 seconds]
AlexRussia has joined #ocaml
antkong has joined #ocaml
Haudegen has quit [Ping timeout: 252 seconds]
vpm has quit [Quit: \_x<]
dsheets has quit [Ping timeout: 265 seconds]
vpm has joined #ocaml
reem has quit [Remote host closed the connection]
avsm has joined #ocaml
ousado has quit [Remote host closed the connection]
ousado has joined #ocaml
ousado has quit [Changing host]
ousado has joined #ocaml
reem has joined #ocaml
Haudegen has joined #ocaml
swgillespie has joined #ocaml
thomasga has quit [Ping timeout: 265 seconds]
matason has quit [Ping timeout: 256 seconds]
ollehar1 has quit [Quit: ollehar1]
nullremains has quit [Ping timeout: 272 seconds]
uris77 has quit [Ping timeout: 246 seconds]
leowzukw has quit [Quit: Lost terminal]
codefo has joined #ocaml
TheLemonMan has joined #ocaml
antkong has quit [Ping timeout: 264 seconds]
mxv has joined #ocaml
<mxv>
Hi, my Googling is failing me. If I redefine a float, "type t = float". How would I create a constructor that accepts a float and returns a t, float -> t ?
<mrvn>
mxv: let make x = x
<mrvn>
it does
<mrvn>
ups
<mxv>
it compiles
<mxv>
but if I use it in a different module, it just says Error this function has type float -> float -> Point.t
<Leonidas>
Drup: what is a styled array?
slash^ has quit [Read error: Connection reset by peer]
<Drup>
Leonidas: each codepoint as style information (underline, color, ...)
<Leonidas>
ah
<Drup>
it's tailored for terminal printing, not for string-like manipulation
<nicoo>
mxv: Does your module's interface expose that t = float ?
<Leonidas>
yes, that makes a lot of sense :)
<nicoo>
mxv: Also, what are you trying to achieve ?
<mxv>
nicoo, yes.
<mxv>
unsigned floats.
<Leonidas>
mxv: obviously you're doing something that you're not mentioning, because OCaml has no Point.t type :-)
<nicoo>
o_O
<Leonidas>
mxv: if you don't want your implementation to shine through, then don't expose that information in the signature
<nicoo>
mxv: Also, `this function has type float -> float -> Point.t` cannot possibly be about `make = fun x -> x`
<mxv>
nicoo, t's not.
<mxv>
I have a "Point.create (Axis.create x) (Axis.create y)"
<nicoo>
mxv: Please provide the whole error message and the relevant code
<mxv>
nicoo, one sec
larhat1 has quit [Quit: Leaving.]
claudiuc has joined #ocaml
flxx has joined #ocaml
flx_ has joined #ocaml
flux has quit [Read error: Connection reset by peer]
flx_ is now known as flux
<mxv>
nicoo, sorry I just removed all the other code in the module and boiled it down this problem to its code - and it worked. It must be something else that's causing the issue
flx has quit [Read error: Connection reset by peer]
<nicoo>
'k
<mxv>
nicoo, thanks for being my duck :)
<nicoo>
You are welcome
<nicoo>
(just don't call me “mon canard” :þ)
nullcat has joined #ocaml
nullcat has quit [Read error: Connection reset by peer]
nullcat has joined #ocaml
_andre has quit [Quit: leaving]
ollehar1 has joined #ocaml
Hannibal_Smith has quit [Quit: Leaving]
uris77 has joined #ocaml
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
jwatzman|work has quit [Quit: jwatzman|work]
swgillespie has joined #ocaml
ptc has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
dant3 has joined #ocaml
badon_ has joined #ocaml
badon has quit [Disconnected by services]
freling has joined #ocaml
badon_ is now known as badon
ericwa has joined #ocaml
dsheets has joined #ocaml
larhat has joined #ocaml
ptc has joined #ocaml
WraithM has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
larhat has quit [Quit: Leaving.]
nullcat__ has joined #ocaml
nullcat has quit [Ping timeout: 272 seconds]
Hannibal_Smith has joined #ocaml
nullcat__ has quit [Read error: Connection reset by peer]
nullcat has joined #ocaml
Submarine has quit [Remote host closed the connection]
WraithM has quit [Quit: leaving]
acieroid has quit [Ping timeout: 256 seconds]
seangrove has joined #ocaml
<seangrove>
Is there some syntax for matching and assigning the "rest of a list" to a bindings?
<adrien>
let hd :: tl = some_list in ...
<adrien>
?
<seangrove>
adrien I think that's it, thanks :)
<seangrove>
Let me try
<pippijn>
you don't want to do that though
<pippijn>
because some_list might be empty
<seangrove>
Oh, why not?
<pippijn>
and that would fail at runtime with a Match_error
<adrien>
the compiler will warn you about that case
<pippijn>
if you're 100% sure it's not empty, you can do that, but the compiler won't know and will warn you
<pippijn>
which is annoying
<adrien>
you should do such operations inside a "match some_list with | hd :: tl -> .... | [] -> ...."
tianon has quit [Read error: Connection reset by peer]
mengu__ has joined #ocaml
tianon has joined #ocaml
<adrien>
seangrove: compile it and se for yourself
Algebr has quit [Ping timeout: 255 seconds]
freling has quit [Quit: Leaving.]
<seangrove>
adrien: Heh, yes, I ran it in utop before asking, but just wanted to make sure I wasn't missing anything obvious
<seangrove>
Still learning to trust the OCaml compiler
<adrien>
remove one case, add another, see how the compiler reacts ;-)
dbp has joined #ocaml
kakadu has quit [Remote host closed the connection]
Haudegen has quit [Ping timeout: 252 seconds]
antkong has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
yminsky has joined #ocaml
antkong has quit [Ping timeout: 252 seconds]
Haudegen has joined #ocaml
<Anarchos>
compcert 2.4 compiled on haiku
badkins has quit []
<seangrove>
I'm in `utop --emacs`, and I #use "somefile.ml" and somefile.ml expects OtherModule to be loaded and available, so that utop complains that Error: Unbound module OtherModule
<seangrove>
OtherModule then in turn expects ThirdModule to be loaded...
<seangrove>
Is there a way to have utop know where all these modules are and to load them appropriately, or do I have to manually load each on in reverse-order?
sepp2k has quit [Quit: Konversation terminated!]
nullcat has quit [Read error: Connection reset by peer]
<reynir>
there's #load_rec
swgillespie has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
mxv has quit [Remote host closed the connection]
<seangrove>
reynir: How does that work if the modules are other ml files in my project?
codefo has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<nicoo>
seangrove: FYI, you can write `json :: [post]` as `[json; post]`
<nicoo>
(After all, `[post]` is merely `post :: []`
<nicoo>
)
Haudegen has quit [Ping timeout: 245 seconds]
<seangrove>
nicoo: Yeah, suppos I was trying to keep it consistent, I'll make that change
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
<nicoo>
You don't have to. Was just saying you can (and it is usually considered to be more idiomatic)
zoetus has quit [Ping timeout: 246 seconds]
gargaml has joined #ocaml
ghostpl_ has quit [Remote host closed the connection]
ptc has quit [Quit: My MacBook Pro has gone to sleep. ZZZzzz…]
Haudegen has joined #ocaml
<seangrove>
nicoo: Thanks for the tip, definitely want to write idiomatic ocaml
MercurialAlchemi has quit [Ping timeout: 265 seconds]
Algebr has joined #ocaml
antkong has joined #ocaml
<xificurC>
if I have player.ml(i) I can use stuff from the module just by typing e.g. Player.t, if I'm in the same folder, right?
<xificurC>
compiling works with that but merlin doesn't pick up the module
<xificurC>
hm, adding `S .' to .merlin seems to do the trick
<xificurC>
I was wrong, it doesnt :)
<Drup>
xificurC: if you are using ocamlbuild, add B _build
<xificurC>
Drup: that means I have to first compile the files for merlin to recognize them?
<Drup>
yes
<xificurC>
hm, ok thanks
destrius has quit [Remote host closed the connection]
<xificurC>
can you type-code something like 'integers from 1 to 10'?
<Drup>
you mean, define a type which contains only integers from one to ten ?
<xificurC>
Drup: yes
<Drup>
technically you can: "type t = Zero | One | ... | Ten"
<Drup>
:D
<Drup>
One*
<Drup>
don't do that.
uris77 has quit [Quit: leaving]
<xificurC>
Drup: :)
<Drup>
the other way is to had a smart constructor that will check if the integer is in the right range
<xificurC>
Drup: refinement types is the official name? Something like type t = int [t > 0 && t <= 10]
<Drup>
yes, that's the official name
<Drup>
(or just plain dependents types)
<xificurC>
is a record creation of { t with field = 0 } efficient? Or does one use mutable fields more
<Drup>
more efficient doesn't always mean better.
<Drup>
(and in this case, the trade off is not always clear)
<xificurC>
Drup: I know, I was just asking if the new records shares the rest of t or if a new copy is made on the call
<xificurC>
s/records/record/
TheLemonMan has quit [Quit: leaving]
swgillespie has joined #ocaml
<Drup>
yes
<Drup>
it will preserve sharing
keen_____ has quit [Read error: Connection reset by peer]
keen_____ has joined #ocaml
<xificurC>
thanks
mengu__ has quit [Remote host closed the connection]
yminsky has quit [Quit: yminsky]
Hannibal_Smith has quit [Quit: Leaving]
oriba has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
acieroid has joined #ocaml
ghostpl_ has joined #ocaml
gargaml has quit [Quit: WeeChat 1.1.1]
Algebr has quit [Ping timeout: 256 seconds]
ghostpl_ has quit [Ping timeout: 246 seconds]
ollehar1 has quit [Quit: ollehar1]
Anarchos has quit [Quit: Vision[0.9.7-H-20140108]: i've been blurred!]
xificurC has quit [Ping timeout: 258 seconds]
Haudegen has quit [Ping timeout: 256 seconds]
badkins has joined #ocaml
tianon has quit [Read error: Connection reset by peer]
tianon has joined #ocaml
Denommus has quit [Quit: going home]
dant3 has quit [Remote host closed the connection]