al-damiri has quit [Quit: Connection closed for inactivity]
randomA has quit [Remote host closed the connection]
tmtwd has joined #ocaml
profmaad has quit [Quit: leaving]
osa1 has joined #ocaml
<osa1>
I'm surprised that RWO doesn't even mention unit testing. what is a good unit testing library?
shinnya has joined #ocaml
<Khady>
osa1: most powerful tool is ounit
<Khady>
Other libs like alcotest are trendy
<Khady>
We need a page on OCaml.org or a section on awesome OCaml about testing
ygrek has joined #ocaml
bruce_r has quit [Ping timeout: 260 seconds]
zv has quit [Ping timeout: 240 seconds]
wu_ng has joined #ocaml
zv has joined #ocaml
seangrove has quit [Ping timeout: 272 seconds]
osa1_ has joined #ocaml
osa1 has quit [Ping timeout: 240 seconds]
wu_ng has quit [Read error: Connection reset by peer]
wu_ng has joined #ocaml
iZsh has quit [Ping timeout: 240 seconds]
cthuluh has quit [Ping timeout: 276 seconds]
iZsh has joined #ocaml
osa1__ has joined #ocaml
osa1_ has quit [Ping timeout: 264 seconds]
bruce_r has joined #ocaml
<osa1__>
I have this interface: http://lpaste.net/204633 I can call `Deque.create` but when I call `Deque.pop_left` I get "Unbound value Deque.pop_left". what's going on?
shinnya has quit [Ping timeout: 244 seconds]
theblatte has quit [Ping timeout: 265 seconds]
<rightfold>
Try a clean build
<rightfold>
And check if you're not using the wrong Deque module
<osa1__>
I tried a clean build 10 times now
<osa1__>
the code is literally just this `let () = let deque = Deque.create () in let left = Deque.pop_left deque in ()`
osa1__ has quit [Quit: Konversation terminated!]
osa1__ has joined #ocaml
<osa1__>
wait, does Core.Std has a module named Deque?
<osa1>
it turns out I wasted time reinventing wheel
<rightfold>
Is sig include M end equivalent to M?
<rightfold>
Because it makes the code easier to format
yegods has quit [Remote host closed the connection]
osa1_ has joined #ocaml
osa1 has quit [Ping timeout: 248 seconds]
Denommus` has joined #ocaml
yegods has joined #ocaml
bruce_r has joined #ocaml
michaeltbaker has joined #ocaml
pierpa has quit [Ping timeout: 264 seconds]
nicholasf has quit [Remote host closed the connection]
phase_ has joined #ocaml
tennix has quit [Quit: WeeChat 1.5]
<bruce_r>
does anyone know how to dynamically update the content of a "Form.input ~input_type:`Text" from the client in Eliom?
<bruce_r>
I usually use To_dom and modify ##.innerHTML to do this, but I can't do it with this one because it needs the ~name:argument parameter to be constructed, so it doesn't work
nicholasf has joined #ocaml
arc- has quit [Ping timeout: 248 seconds]
spion has quit [Ping timeout: 276 seconds]
Denommus` has quit [Quit: sleeping]
clog has quit [Ping timeout: 265 seconds]
clockish has quit [Ping timeout: 265 seconds]
clog has joined #ocaml
arc- has joined #ocaml
clockish has joined #ocaml
spion has joined #ocaml
osa1__ has joined #ocaml
osa1_ has quit [Ping timeout: 248 seconds]
NingaLeaf has quit [Quit: My MacBook has gone to sleep. ZZZzzz…]
struktured has joined #ocaml
MercurialAlchemi has joined #ocaml
AlexDenisov has joined #ocaml
<struk|desk>
anybody know if the bessel function is implemented by some existing ocaml lib? oml, lacaml didn't have it on quick inspection...
nore has quit [Ping timeout: 260 seconds]
nore has joined #ocaml
axiles has quit [Ping timeout: 265 seconds]
axiles has joined #ocaml
AlexDenisov has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
spion has quit [Ping timeout: 272 seconds]
arc- has quit [Ping timeout: 250 seconds]
arc- has joined #ocaml
fds has quit [Ping timeout: 240 seconds]
fds has joined #ocaml
arc- has quit [Ping timeout: 250 seconds]
Mercuria1Alchemi has joined #ocaml
Denommus has quit [Ping timeout: 255 seconds]
jncd has joined #ocaml
arc- has joined #ocaml
rgrinberg has quit [Ping timeout: 255 seconds]
spion has joined #ocaml
p_nathan has joined #ocaml
<p_nathan>
I have an ocaml-build based project with a few dependencies & ocamlfind. I'd like to get into a REPL environment to poke it a few ways, but I havn't been able to connect the dots into doing that. Any advice?
<axiles>
p_nathan: run the ocaml command with -I _build
<axiles>
then, do #use "topfind";; and load the requiered libraries
<axiles>
and then enter #use "some_file.cma";; (assuming you have compiled a library with the project)
<p_nathan>
aight
<p_nathan>
(I actually haven't compiled a library, but I'll see where I can go from here)
CuriousErnestBro has quit [Quit: Leaving]
copy` has quit [Quit: Connection closed for inactivity]
snhmib has joined #ocaml
phase_ has quit [Ping timeout: 255 seconds]
<struk|desk>
re: my question about bessel function. gsl has it, which has bindings
LACampbell has joined #ocaml
FreeBirdLjj has joined #ocaml
<p_nathan>
axiles: that got me rolling, I was able to push forward from there.
igt0 has quit [Quit: Connection closed for inactivity]
nzyuzin has quit [Ping timeout: 244 seconds]
Simn has joined #ocaml
nzyuzin has joined #ocaml
<struk|desk>
p_nathan: you are using utop right?
jstolarek has joined #ocaml
haesbaert has joined #ocaml
valexey has quit [Ping timeout: 260 seconds]
valexey has joined #ocaml
<p_nathan>
struk|desk: nah, I had forgotten. It didn't work well last time I tried it
<p_nathan>
something certainly due to PEBKAC and a lovingly hand-crafted artisanal gentoo laptop. :)
michaeltbaker has quit [Remote host closed the connection]
michaeltbaker has joined #ocaml
arc- has quit [Ping timeout: 272 seconds]
spion has quit [Ping timeout: 240 seconds]
michaeltbaker has quit [Ping timeout: 248 seconds]
jstolarek has quit [Ping timeout: 244 seconds]
arc- has joined #ocaml
cthuluh has joined #ocaml
arc- has quit [Ping timeout: 250 seconds]
jstolarek has joined #ocaml
AlexDenisov has joined #ocaml
Ravana has quit [Quit: Goodbye for now!]
spion has joined #ocaml
freusque has joined #ocaml
nicholasf has quit [Remote host closed the connection]
larhat has joined #ocaml
nopf has quit [Ping timeout: 276 seconds]
nicholasf has joined #ocaml
nicholasf has quit [Read error: Connection reset by peer]
nicholasf has joined #ocaml
rossberg has quit [Ping timeout: 265 seconds]
nicholasf has quit [Ping timeout: 244 seconds]
jwatzman|work has joined #ocaml
<Algebr`>
opam is so much more superior to npm
rossberg has joined #ocaml
<rightfold>
I like Bower
LACampbell has left #ocaml ["WeeChat 1.4"]
<Algebr`>
the whole ecosystem is held together by ducktape
gl has joined #ocaml
mpenet has joined #ocaml
struktured has quit [Ping timeout: 240 seconds]
gl has left #ocaml [#ocaml]
<rightfold>
Duck tape is surprisingly strong ;)
<rightfold>
Lol "ducktape"
<chelfi>
beware of duck taping
<Algebr`>
heh
myst|fon has joined #ocaml
<rightfold>
I want to write a compiler in OCaml
<Algebr`>
okay do it
<struk|desk>
p_nathan: surprised gentoo even matters, especiall if you use opan which you should
<struk|desk>
*opam
zpe has joined #ocaml
yegods has quit [Remote host closed the connection]
yegods has joined #ocaml
jwatzman|work has quit [Quit: jwatzman|work]
mpenet has quit [Remote host closed the connection]
jncd has quit [Ping timeout: 240 seconds]
wxfdglm has joined #ocaml
yegods has quit [Remote host closed the connection]
<brab>
Is ocaml.org down?
<rightfold>
Yes
clockish has quit [Ping timeout: 244 seconds]
<brab>
argh, I need it to finish writing the CWN
clockish has joined #ocaml
<rightfold>
Google cache
orbifx has joined #ocaml
<orbifx>
Why is Opam untrusted by my browser? Anyone else noticed it?
<flux>
The certificate expired on 09/20/2016 02:59 AM. The current time is 09/20/2016 01:04 PM.
<flux>
someone mentioned this issue not a long ago
<flux>
it wasn't for opam, though (?), but I guess some site managed by the same party..
yegods has joined #ocaml
<rightfold>
Real world OCaml has the same issue
<flux>
I guess the ocaml front for letsencrypt is not ready yet ;-)
<rightfold>
Are there linters?
wu_ng has quit [Remote host closed the connection]
<rightfold>
It would be cool to have some kind of warning about polymorphic comparisons
teiresias has quit [Ping timeout: 255 seconds]
<flux>
I don't think so. but you could prevent yourself from doing it with let ( = ) = ()
<flux>
(and same for < etc)
<rightfold>
Oh rad
<flux>
I guess there would be some (but very little..) use for such a linter
copy` has joined #ocaml
<rightfold>
Fun exercise
<flux>
it would be feasible (for some value of feasible) to implement that with a PPX that also reads type information from .cmt :)
<rightfold>
Parse code, resolve names, look for Pervasives.(=)
mfp has joined #ocaml
<rightfold>
I need to read more about build tools
michaeltbaker has joined #ocaml
<flux>
well, there are some other things a linter could warn about
<flux>
for example let y = ref 0 in let x () = incr y; !y in [x (); x ()] can produce different list with ocamlopt and ocamlc
<orbifx>
The example code I'm trying has open Result
ee_ks has joined #ocaml
_andre has joined #ocaml
freehck has joined #ocaml
alpen- has quit [Ping timeout: 255 seconds]
<Bluddy[m]>
I'd like a compiler warning about using polymorphic comparison
<copy`>
orbfix: There's no module, only the new type
<flux>
bluddy[m], great, more packages that break because of -Wall -Werror ;-)
<copy`>
Nevermind, there's actually a new module
alpen has joined #ocaml
<Bluddy[m]>
flux: if you're using generic comparison, you deserve for your packages to break :)
pierpa has joined #ocaml
<Bluddy[m]>
better during compilation, than during runtime, when you compare 2 hashtables, and suddenly 1 hashtable has a slightly differently ordered list inside it
michaeltbaker has joined #ocaml
<flux>
you have tests, right?
<flux>
I bet polymorphic comparison has many more valid uses in existing code than invalid ;)
<rightfold>
you can make it harder to use by giving it a different name
michaeltbaker has quit [Ping timeout: 265 seconds]
<Bluddy[m]>
flux: the tests can easily miss it. Like I said, some hashtable comparisons will be fine because the arrays will compare fine. Then you'll get a false negative because of different lists under certain input patterns.
<Bluddy[m]>
polymorphic comparison is a curse. It's ok if you know exactly what you're comparing, and you know you'll never compare something that could have different notions of structural and semantic equality. But then you'll use that function for something that does, and you'll get wrong behavior with no type warning.
<companion_cube>
proper solution: write a custom comparison (maybe initially an alias to Pervasives.compare), and use it
wxfdglm_ has joined #ocaml
<companion_cube>
this way if your type becomes incompatible with poly comparison, you can change easily
<Bluddy[m]>
correct
<Bluddy[m]>
which is why you need to be aware of your uses of poly comparisons
<rightfold>
adding a compare function to your module makes it suitable for functors that want it
wxfdglm has quit [Ping timeout: 272 seconds]
<osa1__>
I can't believe that ocaml error messages are actually this bad. does anyone have any idea why Bytes.unsafe_to_string is unbound here? isn't that in stdlib? I'm getting "Error: Unbound value Bytes.unsafe_to_string"
<rightfold>
like Map.Make
<osa1__>
I can use Bytes.t, Bytes.length etc. but somehow Bytes.usnafe_to_string is not bound
<osa1__>
wait, are you serious? how is that type actually used?
<osa1__>
s/type/module
<flux>
would be a great april fool's joke to announce a replacement stdlib that has all these modules and operations but you cannot actually do anything useful with it ;)
<reynir>
heh
NingaLeaf has joined #ocaml
<osa1__>
:D ocamlc is pointing at a documentation for an error message. seriously
<flux>
seriously amazing you mean?
<rightfold>
I want single-line error messages, and in reverse order.
<rightfold>
The first error message is the only useful one, and if they're in reverse order then I don't have to scroll up :D
<osa1__>
flux: ocamlc seriously sucks I mean
<copy`>
You can write `module Bytes = Caml.Bytes` after `open Core.Std`
<osa1__>
copy`: at the top level?
<copy`>
Yes
<osa1__>
it worked! thanks copy`
osa1__ is now known as osa1
osa1 has quit [Changing host]
osa1 has joined #ocaml
<lyxia>
what if you hide both Caml and Bytes
mpenet has joined #ocaml
<osa1>
can you qualify imports using package names maybe?
<flux>
take a guess ;)
<flux>
basic solution is: don't..
<rightfold>
lyxia: then you can do `module Foo = Caml` before `open Core.Std`, then `module Bytes = Foo.Bytes` after it
<companion_cube>
yay, no namespaces
<lyxia>
rightfold: Of course! Thanks.
<rightfold>
it's a bit like the programming 101 swap algorithm
<osa1>
why would it be a waste of a pointer? arguments registers are already caller-save, right? you gotta save it anyway.
<osa1>
s/pointer/register
<rightfold>
who cares about a register when you're doing I/O
<osa1>
(not all effects are I/O though)
<osa1>
well if you mean you only add () to I/O then yeah
<osa1>
I'm surprised that all that posix functions that take a byte buffer as an argument would use something like Bytes or Byte_buffer or whatever but they all use strings in Core. you'd expect Core to be better than this.
<osa1>
string implies some encoding of a text, right? or is that actually a byte string?
shinnya has joined #ocaml
<rightfold>
Is there a functor that gives me (>>=) when I give it sig type 'a t; val bind : 'a t -> ('a -> 'b t) -> 'b t end?
cube_bot has quit [Remote host closed the connection]
fddh has quit [Quit: Page closed]
<Bluddy[m]>
companion_cube: the problem is, you don't easily know which types work with structural comparison. Hashtbls in particular appear to work, until they don't. And you have to think about a deep type all the way down to figure out if you have any problematic types there. This is what types are supposed to save us from. How about somebody trying to make a type more efficient by replacing an inner list with a map?
teiresias has joined #ocaml
<companion_cube>
Bluddy[m]: it seems quite clear to me that structural comparison will not work on Hashtbl or Set
<companion_cube>
it works with atomic types, tuples, and lists
<companion_cube>
in general I write a dedicated comparison fun anyway
<Bluddy[m]>
yeah but is it clear to the average user? Is it clear to you at 2 am when you're refactoring code?
jstolarek has quit [Ping timeout: 240 seconds]
<Bluddy[m]>
Hashtbl really is one of the worst offenders, because it only breaks occasionally at runtime.
<mrvn>
companion_cube: I want to have custom blocks with custom operations available from ocaml too. That way Hashtbl could provide a proper compare.
<companion_cube>
mrvn: meh, I'd rather have no poly comparison, and implicits instead
<Bluddy[m]>
this is why we need implicit modules asap
<Bluddy[m]>
jinx
<mrvn>
companion_cube: then = should juts give a compile error
<companion_cube>
eventually, yes
<companion_cube>
I hope so
<Bluddy[m]>
-safe-compare
<companion_cube>
:D
<mrvn>
It would be cool if using a custom block would inline the compare function when the type is known.
<companion_cube>
nothing guarantees that every custom block has the same function?
<mrvn>
companion_cube: "when the type is known"
<flux>
it is going to be very annoing day when 0 = 0 ill cause a compiler warning.
<mrvn>
flux: int = int can work but then bool = bool will give an error
<companion_cube>
mrvn: even then
<companion_cube>
mrvn: hey, no, bool=bool is useful
<mrvn>
companion_cube: don't do that then. if you have different custom ops use different types.
<companion_cube>
hmmm ?
<flux>
Boolean.compare a b :-)))
<companion_cube>
no
<companion_cube>
(=) would just be an implicit
<companion_cube>
overloading
<mrvn>
flux: Pervasives.compare_bool
<flux>
super.
michaeltbaker has joined #ocaml
octachron has joined #ocaml
<companion_cube>
yeah, you'd have monomorphic primitives
<companion_cube>
but (=) would still exist
<companion_cube>
(can't wait for `print`, also)
<flux>
I think if the compiler finds out it needes to use a polymorphic compare, that might be a warning I'd like to see
<companion_cube>
hence the -safe-compare I guess
michaeltbaker has quit [Remote host closed the connection]
michaeltbaker has joined #ocaml
Trou has joined #ocaml
<osa1>
what's the syntax for documenting record fields? I'm getting a warning for (** ... *)
<Trou>
hello, I have a problem with makefiles and ocamldep. Although I have a dependency that updates .depend using ocamldep, that is then included in the makefile
<Trou>
I get make inconsistent assumptions over interface
<Trou>
I get "make inconsistent assumptions over interface" errors
<Trou>
what can I do ?
<flux>
use ocamlmakefile :)
<flux>
basically it means you have .cmi or .cmo files that have been compiled with different versions of a .cmi file
<flux>
when a .cmi file is compiled, it has a checksum that is copied to each file that is compiled that as a dependency
<Trou>
yeah I know but I thought ocamdep was supposed to handle that ?
<Bluddy[m]>
or just use ocamlbuild if you can. easiest solution
<flux>
well, for some value of "easiest"
<flux>
I'm not sure if ocamldep can really handle all the cases by itself..
michaeltbaker has quit [Ping timeout: 255 seconds]
<flux>
if you don't have many files, review the results with some thought and see if they are what you expect
<flux>
and then consider if your makefile rules would work
<Trou>
hmm there're quite a few files
<Trou>
hmm i'm not sure ocamlmakefile is suited, as I need to generate both binaries and .so files
<Trou>
in native code
<octachron>
osa1: type ('a,'b) r = { field: 'a (** doc for field *); field_bis:'b (** doc for field_bis*) } (** doc for r *)
<flux>
can't ocamlmakefile do those?
<Trou>
maybe
<Trou>
i was hoping for a "sane" way to do that though
<flux>
x = .. is what you see at the top of the page?
<Bluddy[m]>
I don't see it either. Browser?
<ggole>
Do you have case matching on?
<flux>
my page begins with Up Module Int = Core_kernel.Core_int ..
<osa1>
no I scrolled down for a while. it starts with Up link
<chelfi>
osa1: sorry if we are bothering you with obvious suggestions, but did you try "Map" rather than "map" ? Also Drup's link points directly to the relevant line
<osa1>
it's not case sensitive and Map isn't working. anyway, thanks
<osa1>
so is there really no way to forward-declare functions without using the awful "and" syntax that makes everything mutually recursive?
<flux>
you can use recursive modules, but that's even worse ;)
<flux>
alternative approach is to pass the forward-depdendency as an argument
<flux>
then redefine the function without the explicit dependency
<osa1>
@_@
<flux>
like: let foo call_bar () = call_bar 42 + call_bar 42 let bar x = x / 2 let foo = foo bar
<osa1>
OK, so no
<flux>
it needs to work as if you wrote the phrases one at a time from top to bottom
<Algebr`>
osa1: why is the and sytanx awful?
<osa1>
it's not awful it just makes things recursive which I don't need and want
apache2 has joined #ocaml
<flux>
if they are not recursive, then perhaps you could define them in another order?-)
<ggole>
ML is pretty opinionated about order of definition.
<osa1>
I tend to organize files such that the reader can read it from top to bottom which is exactly the opposite of what ocamlc is forcing me to do
<rightfold>
why do I have to use named arguments with List.fold?
<Bluddy[m]>
osa1: ocaml is bottom to top. If you don't get used to that, you'll really suffer
<flux>
rightfold, because it returns a polymorphic value
<flux>
the ~f that is
<osa1>
I'm suffering already
<Bluddy[m]>
it's just a mentality switch
<rightfold>
flux interesting
<Bluddy[m]>
C is generally the same way -- you need to define the things you're calling
<osa1>
in C you have headers though
<flux>
but only the fact that it exists
<flux>
in practice you don'tneed to consider at all the order of functions in C
<flux>
whereas with ocaml you may find yourself moving functions around
<flux>
I suppose it's nice to know, when reading the code, that all you see is something that's been actually defined already
<flux>
but sometimes it can be annoying.
<Bluddy[m]>
flux: it's true but the fact that you need prototypes for unknown functions gives the same general order of definition
<Bluddy[m]>
osa1: the limitation of needing to define the function before calling it means that you always know where to go to start reading the file. It's forced by the compiler. Not so in other languages, which can jump around. It has advantages and disadvantages
<ggole>
It can be a real pain when you want things to mutually refer (a type and a module, say) and the language doesn't quite support it properly
<flux>
in C, if you find an error message that something is not defined, you can simply declare it. in ocaml you either move code, write a rec-and of the affected functions or write a recursive module of the affected functions.
<flux>
I guess it means ocaml is three times as good, because it has some many options ;-)
mengu has joined #ocaml
<osa1>
Bluddy[m]: I'd much rather have the flexibility of choosing whatever order I like. for example, I usually move small reusable utility functions to the end of the file and I can't do this in OCaml.
<Bluddy[m]>
you can also use a ref to a function and fill it in later: let foo = ref (fun _ -> failwith "undefined");; let bar = !foo x;; let () = foo := (fun x -> x + 1);;
michaeltbaker has joined #ocaml
<flux>
osa1, at least you can expect that all ocaml code has those utility functions in the beginning ;-)
<Bluddy[m]>
osa1: nope, you can't. Like I said, it's a pretty basic feature of the language. It's because normal definitions aren't recursive. Other languages make different choices based on their mix of features.
<flux>
osa1, in fact, you could just move them to their own module..
AltGr has joined #ocaml
<Bluddy[m]>
btw recursive modules really use the 'ref to a function' trick, except they do it for modules.
ggole has quit []
michaeltbaker has quit [Ping timeout: 255 seconds]
<rightfold>
oh this is really nice
<Bluddy[m]>
given the fact that you can have a full ocaml file with no type annotations, I find it helpful that there's a way to 'slice and dice' it, top to bottom
<Bluddy[m]>
sorry i meant bottom to top
wxfdglm_ has quit [Quit: leaving]
<rightfold>
in type checker signature: module Env : sig type t; val empty : t end, in type checker implementation: module Env = ty StringMap.t
<rightfold>
I love modules
zpe has joined #ocaml
<flux>
companion_cube, pretty amazing stuff. I wonder if it's too ambitious to actually get a) completed and b) into ocaml proper
osa1 has quit [Ping timeout: 255 seconds]
<companion_cube>
here it's good to be ambitious, because it's the only way to have a retrocompatible system
<companion_cube>
the way they deal with arrows is pretty nice (reinjecting row type variables)
<flux>
I wonder what unexpected roads this would open ;)
<flux>
BOOM! now you have a turing complete type system! well maybe not ;)
<companion_cube>
implicits are more worrying in this respect, methinks
<flux>
I wonder if that would/should also be extended to deal with regular exceptions.. or would people just deprecate exceptions in favor of effects. I'm only at 31:00 so I don't know if it answers it ;)
<flux>
I bet new ocamlers are going to love -> ->> ~> ~>> !
<companion_cube>
heh, yeah, this is ugly :/
<companion_cube>
I don't get why compare is effectful
<flux>
hmm, too bad Set needed a pure version
<flux>
companion_cube, it might be?
<flux>
if in case Set you're providing it
<companion_cube>
hmmm, because of custom comparisons?
<companion_cube>
I meant the poly compare
<companion_cube>
ahh, Not_found tracking!!
<flux>
Not_found tracking?
<companion_cube>
in the types
<companion_cube>
that is cool
<flux>
I need to fast forward.. :)
<flux>
if only had I viewed it with mpv and 110% speed
<companion_cube>
there is a "speed" button on YT
<flux>
oh. well I switched to mpv ;)
<companion_cube>
oh wow, async/await
AltGr has left #ocaml [#ocaml]
randomA has joined #ocaml
<randomA>
List.Assoc can be used as a dictionary but does poorly at large number of values
<randomA>
if my Map will only ever have about 150 items, is List.Assoc ok?
<flux>
depends on your performance requirements
<randomA>
I'm mapping a module called Room to an array of the Room's exits
<randomA>
Should I implement an actual dictionary, or is a List.Assocc ok?
<randomA>
is performance actually going to be bad?
<randomA>
flux:
<flux>
how many calls per second do you expect the lookup to get?
<Algebr`>
flux: I wnder how slow is slow with 150 items, still seems reasonable to me
<flux>
it's probably reasonably fast, but much slower than a Map would be
<Algebr`>
yes
<flux>
it depends if you want to do it 10000 times per second or maybe a dozen times per second
<randomA>
i dont really know
<randomA>
im creating a text adventure game
<randomA>
and I'm mapping rooms to their exits
<flux>
so a user presses a key and then perhaps it's called a few hundred times?
<randomA>
so whenever a user types "look" or enters a new room, I'll have to look that up
<randomA>
flux: no, it's called once
<flux>
you do one lookup per one user string input?
<randomA>
everytime the user does soemthing, it should be call about once
<randomA>
proably
<flux>
in that case you could put maybe a million entries to the list
<randomA>
yeah
<randomA>
ok lovely
<randomA>
then i dont need to implement Map
<flux>
well
<flux>
maybe you should hide the fact that you're using either
<flux>
so you can switch later if required
<randomA>
how do i hide that fact?
<flux>
you would make a module Dungeon that has type rooms and then like let find_room dungeon room_name = List.assoc room_name dungeon
<randomA>
yeah soemthing like that
<randomA>
do you know text adventure games?
<flux>
yes. can't say I've played them for 20 years.
<randomA>
lol
<randomA>
can I pm you my assignment spec so i can ask more specific question?
<randomA>
id post here but my prof or ta might be around
<flux>
I think I would prefer if you can express your questsions in more general terms on the channel..
<randomA>
lol i think you are one of them
<randomA>
ok but anyway
<randomA>
can i put a reord inside a record
<flux>
yes..
<randomA>
i mean
<randomA>
like I don't know if somthing should be a module vs if something should be a record
<randomA>
like should my World be a module or a record
<Bluddy[m]>
companion_cube: did you watch the whole lecture?
<companion_cube>
yes
<randomA>
also, how do i test things like if a json file is parsed correctly
<randomA>
by test, i mean unit test
<randomA>
i can of course prettyprint stuff, but that's not very automated
<flux>
randoma, usually you put functions in a module and the data type (record) associated into the same module as well
<companion_cube>
randomA: there are testing libraries, as usual
quesker has joined #ocaml
<companion_cube>
for json, I'd say you can parse foo.json, print into bar.json, parse bar.json and check it's the same JSON value
<randomA>
so i put records into modules?
<flux>
sure
<randomA>
im just kind of confused
<Bluddy[m]>
companion_cube: what did you think of the current limitations? The oneshot continuation problem in particular seems serious, as does the inability to generalize effects
<quesker>
lesson 1 step 3 on try.ocamlpro.com list.rev [1; 2; 3] error unbound value list
<randomA>
say I'm creating a Game, the text adventure game, and I want to put all the game related stuff into a data type called Game. Should Game be a record or a module?
<randomA>
I know Room should be a module and Item should be a module
<randomA>
but what about like the game state, State
<randomA>
is that module or record
<companion_cube>
Bluddy[m]: the oneshot continuation part is fine by me
slash^ has quit [Read error: Connection reset by peer]
<companion_cube>
all effects I'm interested in are linear
<quesker>
oh. List not list
<reynir>
let parse_json _ = `List []
<companion_cube>
the generalization, I don't really know
<flux>
randoma, you probably have some module for the game itself. the state could be inside that.
<Bluddy[m]>
companion_cube: but it's effectful -- that's the problem
octachron has joined #ocaml
<quesker>
ocaml.org down?
<randomA>
flux: why do you say that?
<randomA>
Why can't I just create a list for the rooms and list for the items
<companion_cube>
Bluddy[m]: what is?
groovy2shoes has joined #ocaml
Nahra` has quit [Quit: ERC (IRC client for Emacs 24.5.1)]
<flux>
you can :)
<randomA>
So say I have the module for the Game. Then I have a record for the State? And then I have a module for the World?
zpe has quit [Remote host closed the connection]
<Bluddy[m]>
oneshot continuations
<randomA>
why create modules vs not creating modules?
<randomA>
because in Java, i understand creating classes if you need different versions of it
<flux>
modules in your case means you put different aspects of the program into different source files
<randomA>
flux: so that would be th eonly reason?
<companion_cube>
Bluddy[m]: well yeah, but it doesn't look like too much of a problem to me
<randomA>
what if i cant seperate into different files
<flux>
you can then write explicitly the interface boundaries between them
<randomA>
then i should not use modules
<companion_cube>
implementing your own effects will require expertise anyway
<Bluddy[m]>
companion_cube: no? He suggested adding linear types!
<flux>
modules can be used inside a single file as well, to their full effect
<flux>
but I think it's not a great idea to write files with 20000 lines of code
<randomA>
ok
<companion_cube>
linear types would be nice, sure
<Bluddy[m]>
companion_cube: but the complexity factor will go way up
<flux>
linear types would probably touch everything
<flux>
so they would need to be extremely limited (as he suggested)
<companion_cube>
but apart from backtracking I don't see effects that would really need non-linearity
<companion_cube>
and oneshot makes it much more efficient
Nahra has joined #ocaml
<randomA>
i still really dont understand what is the purpose of the modules
<randomA>
is it only to seperate things into differnt files?
<flux>
randoma, that and hide the implementation details. you get a good overview of what services a module provides, instead of worrying or relying on how it's implemented.
<randomA>
apparently i cant use differnet fiels
<randomA>
they need to all go into one file
<flux>
eventually if you have a large file, you start forgetting how some parts of it work
dmruiz has joined #ocaml
<flux>
the interfaces the modules provide let you check out the essentials of them, not relearning how they were implemented
<companion_cube>
flux: you should see my current project… there is one file with a toplevel functor containing submodules; it's 3,500 lines
<companion_cube>
very funny :D
<flux>
companion_cube, far cry from 20k ;-)
<companion_cube>
(starts with 20 or 30 mutually recursive types)
<companion_cube>
heh
<randomA>
flux: ok i understand, so it's possible to put all modules in same file
<flux>
randoma, yes
<flux>
module ModuleName = struct let code_here x = x + 42 end
<companion_cube>
!effects
<flux>
though that's only making half the use of it
<randomA>
flux: and you're saying that the Game should be a module, and the GameWorld should be a module and State should be a struct
<flux>
module ModuleName : sig val code_here : int -> int end = struct ... end if the real thing.
<flux>
maybe not use the word 'struct' if you mean 'record' in ocaml, because it also has structs ;-)
<randomA>
inside the game.ml file, we are given required funtions that we have to implement including building the world from the json file and looking up things like number of points
<randomA>
i mean recrod
<randomA>
flux: so i also need to create a game loop
cube_bot has joined #ocaml
<randomA>
oh ok
<randomA>
nvm i get why this stuff is here
<rightfold>
Hmm, is M.x a special kind of expression or is it just like M.(x)?
<Bluddy[m]>
companion_cube: i agree. You're not going to replicate the stack -- that would be insane. But Leo seemed to think it was a big problem.
<flux>
rightfold, well in your case it's the same thing
<Bluddy[m]>
companion_cube: or at least big enough to require linear types
<flux>
rightfold, but M.x means: choose symbol x from module M
<companion_cube>
I suppose Leo wants something clean
<rightfold>
flux: ok, so it's not the same kind of expression as the shorthand for let open M in?
<flux>
rightfold, well, M.x came first
<flux>
rightfold, then came the expression let open M in x
<flux>
rightfold, and then someone though how about if we make M.(x) mean the same thing as let open M in x
ousado has joined #ocaml
<dmruiz>
Hi, Does anyone know about a library that supports multiline editing?
<randomA>
flux: so if i use a module called World, do i not put a signature since World is not an abstract type?
Mercuria1Alchemi has quit [Ping timeout: 265 seconds]
<flux>
World would be a module, it's not a type at all
<flux>
the module World might expose a type t, and the better way to do it is to export it as abstract
<rightfold>
dmruiz: utop does it, and it's written in OCaml, so you could look at which library utop uses. which seems to be LTerm_read_line from lambda-term
<flux>
you do it by putting line 'type t' inside world.mli and then in world.ml yuo have 'type t = { record definition }'
<flux>
and then World.t becomes the abstract type (for all files except world.ml, which uses the non-abstract type t)
jeffmo has joined #ocaml
<randomA>
i know how to do abstract but my question is *should* i make it abstract or no
<randomA>
and also if I use List.assoc and have my modules as values, then how would I get an element of the module
<randomA>
are signatures only for abstract modules?
<flux>
if your goal is to write a "good style" ocaml program then I think the type should be left abstract. but there's really no rule, perhaps leaving it public is the right choice for your program.
<flux>
mostly yes, but they can also be used for hiding function definitions (ie. utility functions)
<randomA>
i want to write good style of course
<flux>
if you don't want to worry about those at all, you won't even need to write world.mli
<randomA>
so as a rule, should I always have abstract?
<flux>
perhaps you should first try to make something working and then worry about style
<flux>
:)
<Bluddy[m]>
randomA: functional programs are generally much more open-ended than object-oriented ones
<randomA>
are you a TA in this assignment
<Bluddy[m]>
you don't need as much hand-holding
<flux>
maybe I am!
<randomA>
that's really horrifying
<randomA>
now, i got to change up names
<randomA>
of modules
<rightfold>
Hmm, I'm trying to remember why I got into OCaml again but I forgot
<randomA>
no one uses ocaml, im sure this is the only school that does.
<flux>
not everything needs to be abstract. but usually there's some central data type a module is centered on and provides many functions to operate on the data type. in those cases, there's really no use in publishing the record internals to other modules. well, except debugging.
<octachron>
I wonder what is the proportion of people in this channel that have been a TA at a point or another in time
<dmruiz>
rightfold, Thanks that is just what I need
<randomA>
but the game stte can be a record
<rightfold>
octachron: what's a TA?
<randomA>
and i think he's more likely a prof since he said 20 years and the TAs would have only been around 19-22
<randomA>
in that case, i don't need to change module types
<randomA>
*names
<rightfold>
"teaching assistant"?
<octachron>
rightfold, yes
<rightfold>
ah
<randomA>
so it's module World: sig ..... end = struct ..... end
ee_ks has quit [Ping timeout: 276 seconds]
osa1 has joined #ocaml
osa1_ has joined #ocaml
randomA has quit [Quit: Leaving...]
osa1 has quit [Ping timeout: 260 seconds]
osa1_ has quit [Ping timeout: 265 seconds]
AlexDenisov has joined #ocaml
eni has quit [Remote host closed the connection]
shinnya has quit [Ping timeout: 240 seconds]
<Algebr`>
for anyone doing javascript and wanting to use all these cool new modern features, like async/await, reactjs, jsx, I wrote a post that might be helpful http://hyegar.com/2016/09/20/webdev-setup/
<rightfold>
I want a bicycle with topologically trivial wheels.
dmruiz has quit [Remote host closed the connection]
CuriousErnestBro has quit [Ping timeout: 260 seconds]
CEB has joined #ocaml
pootler_ has quit [Quit: Connection closed for inactivity]
saidinwot has quit [Ping timeout: 265 seconds]
michaeltbaker has joined #ocaml
saidinwot has joined #ocaml
michaeltbaker has quit [Ping timeout: 272 seconds]
jstolarek has quit [Ping timeout: 272 seconds]
octachron has quit [Quit: Leaving]
orbifx has joined #ocaml
<orbifx>
what would you do if you has to open a module inside an expression, which shadows a parameter passed to this expression?
<orbifx>
let foo a b = let open ModA in ... a;;
<orbifx>
say ModA now shadows `a` passed to foo, what are the options?
jeffmo has quit [Quit: jeffmo]
<rightfold>
rename a
<orbifx>
a has a very nice, semantic name just now
<orbifx>
the actual parameter I have is `title` and I'm opening Tyxml.Html which has a function called `title`
<rightfold>
let module H = Tyxml.Html in
<orbifx>
ow yeah, forgot about aliasing
<orbifx>
thanks
<rightfold>
I wrote my first compiler that tracks line numbers lol
jeffmo has joined #ocaml
AlexDenisov has quit [Quit: My Mac has gone to sleep. ZZZzzz…]
<orbifx>
nice rightfold
CEB has quit [Quit: Leaving]
CuriousErnestBro has joined #ocaml
pyon has quit [Quit: Fix config.]
pyon has joined #ocaml
tane has quit [Quit: Leaving]
jeffmo_ has joined #ocaml
jeffmo has quit [Ping timeout: 265 seconds]
jeffmo_ is now known as jeffmo
pootler_ has joined #ocaml
Ravana has joined #ocaml
pootler_ is now known as mrh
jeffmo has quit [Quit: jeffmo]
AltGr has joined #ocaml
mrh is now known as merv
merv is now known as Merv
Simn has quit [Quit: Leaving]
orbifx has quit [Quit: WeeChat 1.5]
Heasummn has joined #ocaml
jeffmo has joined #ocaml
jao has quit [Ping timeout: 240 seconds]
snhmib has quit [Quit: WeeChat 1.3]
nicholasf has joined #ocaml
ee_ks has joined #ocaml
Nahra has quit [Quit: ERC (IRC client for Emacs 24.5.1)]
AltGr has left #ocaml [#ocaml]
michaeltbaker has joined #ocaml
michaeltbaker has quit [Ping timeout: 255 seconds]