FreeBirdLjj has quit [Remote host closed the connection]
nullcatxxx_ has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
nullcatxxx_ has joined #ocaml
manizzle has joined #ocaml
madroach has quit [Ping timeout: 246 seconds]
madroach has joined #ocaml
badon has quit [Ping timeout: 272 seconds]
^elyse^ has quit [Quit: Leaving...]
Sorella has quit [Quit: Connection closed for inactivity]
Major_Biscuit has quit [Quit: WeeChat 1.3]
nullcatxxx_ has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
ollehar has quit [Quit: ollehar]
BitPuffin|osx has joined #ocaml
struk|desk|away is now known as struk|desk
meiji11 has joined #ocaml
ril has joined #ocaml
Korhonen has quit [Read error: Connection reset by peer]
Korhoset has joined #ocaml
Korhoset has quit [Remote host closed the connection]
Korhonen has joined #ocaml
segmond has quit [Ping timeout: 240 seconds]
luigy has quit [Ping timeout: 260 seconds]
ril has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
luigy has joined #ocaml
ril has joined #ocaml
segmond has joined #ocaml
struk|desk is now known as struk|desk|away
ril has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
pierpa has quit [Ping timeout: 265 seconds]
govg has joined #ocaml
Bahman has joined #ocaml
Bahman has quit [Read error: Connection reset by peer]
meiji11 has quit [Ping timeout: 240 seconds]
nullcatxxx_ has joined #ocaml
agumonkey has joined #ocaml
Bahman has joined #ocaml
Bahman has quit [Read error: Connection reset by peer]
JacobEdelman is now known as bott
bott is now known as JacobEdelman
struk|desk|away is now known as struk|desk
johnelse has quit [Ping timeout: 256 seconds]
mac10688 has quit [Ping timeout: 246 seconds]
johnelse has joined #ocaml
johnelse is now known as Guest89422
struk|desk is now known as struk|desk|away
ygrek has quit [Ping timeout: 260 seconds]
nullcatxxx_ has quit [Read error: Connection reset by peer]
darkf has joined #ocaml
badon has joined #ocaml
cody` has quit [Quit: Connection closed for inactivity]
psy_ has joined #ocaml
psy_ has quit [Read error: No route to host]
psy_ has joined #ocaml
psy_ has quit [Max SendQ exceeded]
psy_ has joined #ocaml
govg has quit [Ping timeout: 255 seconds]
govg has joined #ocaml
badon has quit [Disconnected by services]
badon_ has joined #ocaml
badon_ is now known as badon
rrika has joined #ocaml
slash^ has joined #ocaml
ncthom91 has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
MercurialAlchemi has joined #ocaml
clog has quit [Ping timeout: 265 seconds]
clog has joined #ocaml
jonludlam has quit [Remote host closed the connection]
Kakadu has joined #ocaml
nullcatxxx_ has joined #ocaml
nullcatxxx_ has quit [Client Quit]
nullcatxxx_ has joined #ocaml
palomer has quit [Quit: palomer]
nullcatxxx_ has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
JacobEdelman has quit [Quit: Connection closed for inactivity]
tane has joined #ocaml
contempt has quit [Ping timeout: 256 seconds]
contempt has joined #ocaml
mcint has quit [Quit: hibernating...]
struk|desk|away is now known as struk|desk
badon has quit [Disconnected by services]
badon_ has joined #ocaml
badon_ is now known as badon
nicoo has quit [Quit: WeeChat 1.3]
nicoo has joined #ocaml
nicoo has quit [Remote host closed the connection]
nicoo has joined #ocaml
BitPuffin|osx has quit [Ping timeout: 246 seconds]
sbrouf has joined #ocaml
rand_ has joined #ocaml
rand_ has quit [Read error: Connection reset by peer]
struk|desk is now known as struk|desk|away
sbrouf has quit [Ping timeout: 260 seconds]
sbrouf has joined #ocaml
IP92 has joined #ocaml
<IP92>
can I have a module definition and some function definitions outside any module in one file?
psy_ has quit [Ping timeout: 255 seconds]
sbrouf has quit [Ping timeout: 265 seconds]
Haudegen has quit [Ping timeout: 255 seconds]
^elyse^ has joined #ocaml
contempt has quit [Disconnected by services]
contempt has joined #ocaml
<lyxia>
Yes you can have a module and a function next to each other.
Pepe_ has quit [Remote host closed the connection]
psy_ has joined #ocaml
psy_ has quit [Max SendQ exceeded]
psy_ has joined #ocaml
Haudegen has joined #ocaml
<IP92>
http://pastebin.com/Pzg9L2Pd why am I receiving that "This expression has type string but an expression was expected of type StringSet.elt" on line 18 ?
<zozozo>
IP92: you know you can juste write : module StringSet = Set.Make(String)
<IP92>
zozozo: didn't know that
<zozozo>
well, the String module defines both type t and a compare function, so it implements the required interface that Set.Make expects
<zozozo>
IP92: that's bescause of your first 'if', basically, you wrote : "(if () then blabla); false"
<zozozo>
so because of the semicolon, the expression in the then branch of the if should have type unit
<lyxia>
BTW in OCaml, use = and <> instead of == and !=
<IP92>
what's the difference?
<lyxia>
== != are physical equality and meant to be used on mutable data
<lyxia>
= and <> are the usual equality that do what you expect
<IP92>
ok. another clarifying question, ocaml returns the result of the last statement in the function, but that last statement needn't be physically last in the code, right?
<companion_cube>
it returns the result of the expression
<companion_cube>
there aren't really 'statements'
<IP92>
well yea, but the rest of my statement was correct?
<companion_cube>
a; b is an expression that evaluates a, then behaves like b (and returns the same as b)
^elyse^ has quit [Quit: Leaving]
dsheets has joined #ocaml
dsheets has quit [Ping timeout: 240 seconds]
Pepe_ has joined #ocaml
sbrouf has joined #ocaml
cyraxjoe_ has quit [Ping timeout: 265 seconds]
ia0 has quit [Quit: leaving]
ia0 has joined #ocaml
orbifx has joined #ocaml
pierpa has joined #ocaml
d0nn1e has quit [Ping timeout: 265 seconds]
d0nn1e has joined #ocaml
sbrouf has quit [Ping timeout: 246 seconds]
Kakadu has quit [Quit: Page closed]
mac10688 has joined #ocaml
IP92 has quit [Quit: Leaving]
Simn has joined #ocaml
^elyse^ has joined #ocaml
types has joined #ocaml
<types>
how can i tell obuild to compile in debug mode?
<Korhonen>
I take it there is no way to set up some event which fires when a record field gets modified except just setting up a loop and looing for it, right?
<Drup>
I think you should probably use a smart mutator instead, which fires the event
ggole has joined #ocaml
types has quit [Quit: Leaving]
<dmbaturin>
Korhonen: Perhaps make the record type abstract and only allow modifying it through a function that does the notifications too.
<dmbaturin>
Or use an object with a mutable field if you are in OO mood. :)
struk|desk|away is now known as struk|desk
w1gz has quit [Read error: Connection reset by peer]
<Korhonen>
dmbaturin, yeah, but that too would require some loop to be set up I guess
<Korhonen>
At least, I don't think Ocaml has first class continuations.
<ggole>
There's a delimited continuations library, delimcc
struktured has joined #ocaml
<Drup>
Korhonen: why would you need delimcc for this to work ?
ollehar has joined #ocaml
<ggole>
Yeah, I've always viewed continuation values as a neat trick that shouldn't be used without a *really* good reason
<dmbaturin>
Korhonen: There are also cooperative multitasking libraries such as Lwt.
contempt has quit [Disconnected by services]
contempt has joined #ocaml
struk|desk is now known as struk|desk|away
ncthom91 has joined #ocaml
mcint has joined #ocaml
ncthom91 has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
struk|desk|away is now known as struk|desk
sbrouf has joined #ocaml
^elyse^ has quit [Quit: Leaving]
jbrown has joined #ocaml
struktured has quit [Ping timeout: 265 seconds]
ollehar has quit [Remote host closed the connection]
struktured has joined #ocaml
octachron has joined #ocaml
jbrown has quit [Ping timeout: 260 seconds]
struk|desk is now known as struk|desk|away
ygrek has joined #ocaml
mcint has quit [Quit: hibernating...]
PigDude has joined #ocaml
types has joined #ocaml
<types>
can i return multiple values from a lwt thread?
<PigDude>
i've been working with standard ml for the past year, mostly for studying compiler stuff. i've heard good things about ocaml and was thinking about using it for a new project (static analysis thing), have you all worked w/ sml? is there any reason to choose ocaml over it for this sort of work?
<PigDude>
i've heard about facebook using ocaml quite a bit for these sorts of things, sml doesn't seem as popular commercially even though mlton and smlnj both seem like pretty good implementations
<struktured>
types: what do you mean? if any lwt function handles type 'a, then of course you could, right?
orbifx has quit [Quit: AtomicIRC: The nuclear option.]
<types>
struktured: i am sure it works but i dont know how i can combine a tuple of the values to one 'a value
<struktured>
PigDude: I went through same trial myself. Just pick ocaml. In short, it has much better momentum and support than sml.
<PigDude>
struktured: did you run into strange issues w/ sml in production or anything like that? what were the drawbacks?
<Drup>
types: use tuples ? :D
<struktured>
PigDude: I switched to ocaml well before then.
<struktured>
PigDude: used SML mostly in academicia (at CMU), then I tried using it for some side projects but realized ocaml was a sweet spot
<PigDude>
for library support i guess?
<struktured>
*academia
<Drup>
PigDude: ocaml as tooling and community, sml doesn't
<Drup>
has*
<PigDude>
Drup: not with that attitude it doesn't :D
<Drup>
It's not really an attitude, it's a fact :/
<struktured>
yeah he's just stating truth
<PigDude>
ok thanks, i've been curious about this for a while and most of the comparisons i find online amount to frustration about targetting multiple implementations
<PigDude>
(in sml)
<PigDude>
maybe this thwarts library development etc.
<Drup>
PigDude: I realise how this could be mis-interpreted, the truth is that I prefer some of sml's decision, but it's really 95% the same language, except one ecosystem is much much larger
<companion_cube>
and Ocaml has new features
<types>
Drup: i tried that first, but i can not make it work
<Drup>
types: could you show what you are trying to do ?
<PigDude>
Drup: ok thanks i'll have to crack the spine of my 'real world ocaml' :)
^elyse^ has joined #ocaml
<Drup>
PigDude: By curiosity, what's the project ?
<Drup>
types: what's the error with that ?
<Drup>
(you can remove all the parens) :p
<types>
Drup: Error: This expression has type 'a * 'b
<types>
but an expression was expected of type 'c Lwt.t
<PigDude>
Drup: a fast linter supporting multiple languages
jbrown has joined #ocaml
<struktured>
argh Rresult.R.bind signature..it needs a release
^elyse^ has quit [Ping timeout: 256 seconds]
types has quit [Quit: Leaving]
<Drup>
arf, he's gone
<struktured>
let's just assume he figured out and his 100% happy with his solution then
<Drup>
well, maybe he will see the logs: The context is missing, so I can't really say what's wrong, but this works: http://pastebin.archlinux.fr/1810783, So I think the problem is elsewhere
ncthom91 has joined #ocaml
<struktured>
Drup: max_int is not a valid argument to Random.int apparently
<Drup>
"It typechecks so it works" duh x)
<struktured>
hehe
BitPuffin|osx has joined #ocaml
govg has quit [Ping timeout: 246 seconds]
struktured has quit [Ping timeout: 255 seconds]
sbrouf_ has joined #ocaml
sbrouf_ has quit [Client Quit]
larhat2 has joined #ocaml
larhat1 has quit [Read error: Connection reset by peer]
iosys has quit [Ping timeout: 272 seconds]
ahf has quit [Ping timeout: 272 seconds]
ahf_ has joined #ocaml
iosys has joined #ocaml
ahf_ is now known as ahf
<sbrouf>
How would you deal with cyclic module dependancy ? I have a container module, and a contained module that sometimes need to call some functions on the host
<sbrouf>
Maybe i could use a specific return type, but that seems somewhat overcomplicated
<sbrouf>
is there another way ?
Muzer has quit [Ping timeout: 246 seconds]
<ggole>
Split the bits you need into another module.
<ggole>
(I've found this restriction to be quite annoying.)
<sbrouf>
so I would have a specific module for callback actions ?
<sbrouf>
would it be at the top or the bottom of the dependancies ?
pyx has joined #ocaml
pyx has quit [Client Quit]
ygrek has quit [Ping timeout: 256 seconds]
<ggole>
I dunno about callbacks. What I'm suggesting is that you take the stuff you need to access from both modules (and whatever that depends on), and move it into a third module.
<pierpa>
struk|desk: I see. It's a bit complicated
<gaze__>
Hey guys, what's the best way to replicate the ghci workflow in ocaml? Where I run ghci on some .hs file, edit it, and :r when changes are made?
<pierpa>
use #use instead of :r, IIUC
ril has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<pierpa>
ah, no. :r is automatic. So it's not the same thing as #use
ygrek has joined #ocaml
^elyse^ has joined #ocaml
jbrown has joined #ocaml
<ggole>
I tell ocamlbuild to make a toplevel including all the necessary stuff and (re)start that
<ggole>
I have emacs commands to automate all the fluff away, but setting everything up is quite a pain.
Kakadu has joined #ocaml
jbrown has quit [Ping timeout: 272 seconds]
ggole has quit []
^elyse^ has quit [Quit: Leaving]
ncthom91 has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
kolko has quit [Read error: Connection reset by peer]
jbrown has joined #ocaml
struk|desk is now known as struk|desk|away
ncthom91 has joined #ocaml
ncthom91 has quit [Ping timeout: 240 seconds]
ril has joined #ocaml
jbrown has quit [Ping timeout: 272 seconds]
mcmillhj has joined #ocaml
darkf has quit [Quit: Leaving]
slash^ has quit [Read error: Connection reset by peer]
pierpa has quit [Ping timeout: 240 seconds]
struk|desk|away is now known as struk|desk
contempt has quit [Disconnected by services]
contempt has joined #ocaml
flx_ has joined #ocaml
flux has quit [Ping timeout: 240 seconds]
flx_ is now known as flux
govg has joined #ocaml
^elyse^ has joined #ocaml
struk|desk is now known as struk|desk|away
^elyse^ has quit [Quit: Leaving]
Algebr has joined #ocaml
<Algebr>
why is this a well typed program and not one that gives back a compiler error of ungeneralizable or could not unify? http://pastebin.com/rHxKH1gk Also, I take it then that the smallest possible Lwt timeout is 1 second, no way to do floats? like half a second?
jbrown has joined #ocaml
w1gz has joined #ocaml
palomer has joined #ocaml
sbrouf has quit [Ping timeout: 240 seconds]
<octachron>
Algebr, you mean why program has type 'a Lwt.t rather than '_a Lwt.t?
<Algebr>
yes
<octachron>
The reason is that 'a Lwt.t is covariant in its 'a parameter
<octachron>
this means that if 'a is a subtype of 'b then 'a t is a subtype of 'b t
<octachron>
then the relaxed value restriction kicks in
<Algebr>
and means the program can compile just fine? I don't see that part yet.
<octachron>
yes, the relaxed value restriction says that if a type variable appears in only covariant position then it can be generalized in a sound way
<octachron>
an intuitive explanation is that if you have an '_a t, you could replace '_a with any subtype
<octachron>
so you could replace '_a with the bottom type, i.e. the type with no element
JacobEdelman has joined #ocaml
<Algebr>
right, makes sense. much appreciated explanation. this is PL theory? The covariance stuff?
<octachron>
and thus it means that you don't realize use any value of type 'a and then you can generalize just fine
<octachron>
let me find back jacques guarrigue article
<octachron>
otherwise, a way to remember is that having covariant type parameters imply that you are not mutating stuff behind the back of the user, and so you can relax the value restriction