companion_cube changed the topic of #ocaml to: Discussion about the OCaml programming language | http://www.ocaml.org | OCaml 4.12 released: https://ocaml.org/releases/4.12.0.html | Try OCaml in your browser: https://try.ocamlpro.com | Public channel logs at https://libera.irclog.whitequark.org/ocaml/
tizoc has quit [Ping timeout: 244 seconds]
hex0punk has quit [Read error: Connection reset by peer]
Haudegen has quit [Ping timeout: 272 seconds]
zodeishi has quit [Ping timeout: 264 seconds]
kluk has joined #ocaml
<kluk> how do I start using DynArray? I tried include DynArray, include Extlib, nothing works
<companion_cube> you need to have it in your dune file, if you use dune
<companion_cube> and to install it in the first place
<kluk> I don't know what dune is yet, I'm still a beginner at OCaml. how do I install DynArray? with opam right?
<companion_cube> hmmm if you're that beginner, maybe take a look at a book
<companion_cube> there's a lot to explain :/
<kluk> I just wanted to play around on the ocaml repl with some arrays... not looking for making a project, folders, dune stuff, any of that, if possible to avoid at this point. Is it possible to just play with the OCaml language to learn it and not worry about how it mixes up with unix?
<companion_cube> ah well, sure, just type `ocaml`
<companion_cube> but Dynarray is a 3rd party library for vectors/resizable arrays
<companion_cube> it's not exactly a central type in OCaml :
<companion_cube> :p
<kluk> yes I can get to the repl, but I wanted to play with arrays first without worrying about packages, does that make sense? I wanted to explore OCaml the language first, like a try.ocaml.org sort of thing if that makes sense... I wanted to have some fun with the language and learn it and not have to think about packages and managing projects for a little
<kluk> I need a stack whose elements can be randomly accessed by an integer so I just happen to have an exact use case for arrays, but I am open to suggestions
Sumera[m] has quit [Read error: Connection reset by peer]
radiopotin[m] has quit [Read error: Connection reset by peer]
fluxm has quit [Write error: Connection reset by peer]
smondet[m] has quit [Read error: Connection reset by peer]
krnkktz has quit [Read error: Connection reset by peer]
labor[m] has quit [Read error: Connection reset by peer]
labor[m] has joined #ocaml
<companion_cube> arrays are in the stdlib
<companion_cube> not dynamic arrays
radiopotin[m] has joined #ocaml
<companion_cube> but yeah, a stack with indexing is a good use case
Sumera[m] has joined #ocaml
krnkktz has joined #ocaml
fluxm has joined #ocaml
<kluk> companion_cube :)
smondet[m] has joined #ocaml
unyu has quit [Quit: WeeChat 3.1]
kluk has quit [Read error: Connection reset by peer]
<d_bot> <Bluddy> IMO vectors should replace arrays as a primary data type in the language
<companion_cube> why "replace"?
<companion_cube> I think it'd be nice to be able to build them safely
<d_bot> <Bluddy> as the *primary* data type
<companion_cube> but otherwise, they have some overhead
<companion_cube> arrays are simpler as they're always fully initialized
<d_bot> <Bluddy> yeah the overhead is very minor though
<d_bot> <Bluddy> very few languages have arrays as their primary data structure
<d_bot> <Bluddy> python's lists are vectors
<companion_cube> I mean… java?
<companion_cube> I think the problem is the GC, because in a vector you need some unitialized space
<companion_cube> even in rust it's quite dirty
<d_bot> <Bluddy> hmm
<companion_cube> it's hard to do well without a bit of Obj currently :/
<d_bot> <Bluddy> ok so I guess python/ruby's bias may be due to their reference counting
<companion_cube> also they're insanely high level and slow :p
<d_bot> <Bluddy> yeah but that's beside the point. java has array, c# has array vs List (really a vector)
<companion_cube> java has ArrayList, but only for boxed types
<companion_cube> the primitive on the JVM is arrays, same as OCaml
<companion_cube> (except with unsound variance)
<d_bot> <Bluddy> right
<d_bot> <Bluddy> ok so yeah I think I'm just using python too much recently
<d_bot> <Bluddy> javascript also has array as its primary type
<companion_cube> remember that in OCaml, an array is *one* word of overhead
<d_bot> <Bluddy> so are python and ruby really the exceptions?
<companion_cube> as far as primitive types go? I'm not sure
<d_bot> <EduardoRFS> JS arrays are dynamic arrays / vectors
<d_bot> <EduardoRFS> and the implementation of it is really all over the place
<d_bot> <Bluddy> perl has dynamic arrays. also reference counted
<companion_cube> _scripting languages_ were primitives are all in C
<d_bot> <Bluddy> interesting. and it's gc'd.
<d_bot> <Bluddy> @companion_cube GC is only an issue if you don't have a bit to tell the GC not to scan the uninitialized memory. If OCaml had it, it wouldn't be an issue.
<companion_cube> sure, if you entirely rewrite the GC so it's not just based on the initial tag… :p
<d_bot> <EduardoRFS> but JS objects nowadays operates like OCaml blocks, adding and removing field is generally a bad idea because of the types, while it is possible that can trigger a whole lot of compiled and optimized code to be invalidated
<d_bot> <Bluddy> hmm.. no I guess you need to build it into the GC process itself so it knows how to process the vector
<d_bot> <Bluddy> so it looks at length vs capacity
<d_bot> <EduardoRFS> well we can extend the object header
<companion_cube> (well for a vector you'd need to fit 2 sizes in one, basically: capacity, and actual size)
<d_bot> <EduardoRFS> I'm looking on it during the shower
<d_bot> <Bluddy> yeah a bit is not enough, you need to teach the GC about a new kind of object
<companion_cube> also remember that vectors are 2 levels of indirection, not one
<companion_cube> one to the {len,capacity,ptr}
<companion_cube> + the pointer itself
<companion_cube> but you've got to have this level of indirection so you can change the underlying array/pointer
<d_bot> <Bluddy> that's true
<companion_cube> so that's non trivial overhead compared to a basic array, when all you need is an array
<d_bot> <EduardoRFS> but that access can be mostly reduced if you know the cell size at compile time
<d_bot> <Bluddy> the problem is that you very rarely need an array
<d_bot> <Bluddy> if your primary type is a list, all an array gives you is mutability + O(1) access to any element. it's good, but the lack of ability to extend it is annoying
<d_bot> <Bluddy> if you're doing mutable stuff, you almost always want to extend it
<companion_cube> idk, it's nice in ASTs for example
<companion_cube> I agree that often a vector is also useful
<d_bot> <EduardoRFS> I wonder if having an unrolled linked list with some tricks wouldn't be enough for almost all cases
<companion_cube> for mutable stuff we just should have a good vector
<d_bot> <EduardoRFS> like couple cells all cache aligned + pointers to additional cells if they were created all together so that you can do O(1) after a List.map
<companion_cube> for immutable stuff, we _could_ use HAMT… but well
<d_bot> <EduardoRFS> copy on write is the solution to all problems
<companion_cube> noooo :D
shawnw has joined #ocaml
<d_bot> <EduardoRFS> computers are fun, nowadays you have an ALU and caching inside of the MMU
<d_bot> <EduardoRFS> lisp machine to rule them all
SquidDev9 has joined #ocaml
conjunctive_ has joined #ocaml
terrorjack2 has joined #ocaml
wagle_ has joined #ocaml
eight has quit [Ping timeout: 264 seconds]
pieguy128_ has quit [Ping timeout: 264 seconds]
dmbaturin has quit [Ping timeout: 264 seconds]
rks` has quit [Ping timeout: 264 seconds]
Johann has quit [Ping timeout: 264 seconds]
conjunctive has quit [Ping timeout: 264 seconds]
sim642 has quit [Ping timeout: 264 seconds]
haesbaert has quit [Ping timeout: 264 seconds]
daimrod has quit [Ping timeout: 264 seconds]
wagle has quit [Ping timeout: 264 seconds]
terrorjack has quit [Ping timeout: 264 seconds]
SquidDev has quit [Ping timeout: 264 seconds]
SquidDev9 is now known as SquidDev
terrorjack2 is now known as terrorjack
daimrod has joined #ocaml
conjunctive_ is now known as conjunctive
eight has joined #ocaml
dmbaturin has joined #ocaml
pieguy128 has joined #ocaml
haesbaert has joined #ocaml
rks` has joined #ocaml
sim642 has joined #ocaml
Johann has joined #ocaml
<d_bot> <Bluddy> companion_cube: what do you do to prevent the GC from scanning the uninitialized vector area?
<d_bot> <EduardoRFS> If it is set to 0x0 the GC should just behave normally, it's a block of tag 0, size 0
<companion_cube> @Bluddy in containers, indeed, I fill the vector with 0
<companion_cube> or 0.0 if it's a float array 🙄
<d_bot> <Bluddy> ugh yeah that's bad
<companion_cube> not like we have a better option, imhp
<companion_cube> imho
<d_bot> <Bluddy> I wonder what other languages do
<d_bot> <Bluddy> ones with GC
<companion_cube> well, java fills with null I imagine
<companion_cube> boxed primitives and all that
<companion_cube> D… probably does ugly stuff?
<companion_cube> Go has 0 values for all types, so that's easy
<companion_cube> and the scripting stuff has nil/None/whatever to fill the blanks
<d_bot> <Bluddy> at the Obj level it would be nice if you could have a contiguous array where the size is the length, and right after that you'd place a string header with the remaining size
<companion_cube> you'd have to move the header every time you push/pop? :/
<d_bot> <Bluddy> not a huge deal. same cache line
<companion_cube> ideally push should be as simple and inlineable as possible :p
<d_bot> <Bluddy> still pretty simple. copy header over, reduce string size
<companion_cube> + code path for possible resize… that's a lot more than just a normal push
<d_bot> <Bluddy> pop doesn't need to do anything because you can just zero data out at that point
<d_bot> <Bluddy> that code path is there regardless
<d_bot> <Bluddy> a multi-push function can be more efficient as it can do the header copy once
<companion_cube> pop still needs to copy the header back
<d_bot> <Bluddy> yeah I guess that's true. the only annoying thing about the header is the size counter
<companion_cube> I'd rather wish OCaml had a primitive for partially initialized arrays, and that's it
<d_bot> <Bluddy> but it should be doable with a couple of instructions
<d_bot> <Bluddy> well that's not going to happen anytime soon
<d_bot> <Bluddy> it can happen in the 64-bit runtime, but the 32-bit cannot handle it
<d_bot> <Bluddy> because you need that extra header space for the size
<companion_cube> not sure how that's related :p
<companion_cube> I just want an API for the array with a valid 0 inside
<companion_cube> that doesn't force me to Obj.magic to see if it's a float array or normal array
<d_bot> <Bluddy> valid 0?
<companion_cube> a valid object for this array
<companion_cube> a valid object for this array, _as seen by the GC_
<d_bot> <Bluddy> is this another wish? to deal more easily with float arrays? or is it related?
<companion_cube> it's related because it's the only reason I have to use Obj in containers :p
<companion_cube> (or one of the few, I can't remember)
<companion_cube> to be able to implement a vector
<d_bot> <Bluddy> but it doesn't deal with this particular issue
<d_bot> <Bluddy> I mean they're phasing out float arrays
<companion_cube> yeah that'll be nice
<companion_cube> without float arrays one could always fill the array with 0
<companion_cube> since the GC doesn't mind 0
<d_bot> <Bluddy> yeah I see that piece of code now
<d_bot> <Bluddy> let fill_with_junk_ (a:_ array) i len : unit =
<companion_cube> yep yep
<companion_cube> always interested in better ideas
<d_bot> <ggole> For 64-bit machine zero (not OCaml zero) is fine for float arrays as well
<d_bot> <ggole> So you might be able to get away with coercing to `float array` and then filling with `0.0`
<d_bot> <ggole> However, the recent `FloatArray` stuff might kill that idea
<d_bot> <ggole> The no naked pointer changes might also be trouble
Tuplanolla has joined #ocaml
smondet[m] has quit [*.net *.split]
radiopotin[m] has quit [*.net *.split]
dwt_ has quit [*.net *.split]
lisq has quit [*.net *.split]
gahr has quit [*.net *.split]
zozozo has quit [*.net *.split]
ski has quit [*.net *.split]
EmoSpice has quit [*.net *.split]
smondet[m] has joined #ocaml
ski has joined #ocaml
dwt_ has joined #ocaml
zozozo has joined #ocaml
lisq has joined #ocaml
gahr has joined #ocaml
radiopotin[m] has joined #ocaml
EmoSpice has joined #ocaml
waleee has joined #ocaml
mbuf has joined #ocaml
wonko has joined #ocaml
waleee has quit [Ping timeout: 268 seconds]
cedric has joined #ocaml
<d_bot> <aotmr> Hi everyone! I'm a 3rd-year CS student making personal explorations into programming languages with an emphasis on functional and concatenative languages, as well as metaprogramming and optimizing compilers.
<d_bot> <aotmr> I'm currently using OCaml to build a functional FORTH interpreter that I hope to shape into a general optimizing FORTH compiler
<d_bot> <aotmr> And right now I'm investigating to what extent I can express FORTH concepts in OCaml
<d_bot> <ggole> Hmm, they're pretty different
<d_bot> <ggole> OCaml code is very variable heavy, which seems to be at odds with the Forth philosophy of communicating between tiny bits with the stack
<d_bot> <aotmr> So, for example, inside my VM state is a list representing the current data stack.
<d_bot> <aotmr> ```ocaml
<d_bot> <aotmr> type state = {
<d_bot> <aotmr> ds : Int.t list;
<d_bot> <aotmr> (* ... *)
<d_bot> <aotmr> }
<d_bot> <aotmr> ```
<d_bot> <aotmr> Stack-based interpreters are excellent matches for programming languages with pattern matching facilities, as it turns out.
<d_bot> <aotmr> ```ocaml
<d_bot> <aotmr> type opcode =
<d_bot> <aotmr> | Lit of Int.t
<d_bot> <aotmr> | Add
<d_bot> <aotmr> | Dot
<d_bot> <aotmr> (* ... *)
<d_bot> <aotmr> ```
<d_bot> <aotmr> Let's define a small opcode set for our VM: push a literal to the stack, add the top two on the stack, and print the top on the stack (`Dot`)
<d_bot> <aotmr> Now, here's where OCaml's list matching becomes very elegant. Let's define a function, `execute`, that takes a state and an opcode and returns a new state that reflects having executed the opcode.
<d_bot> <aotmr> ```ocaml
<d_bot> <aotmr> let execute st = function
<d_bot> <aotmr> | Lit i -> { st with ds = i::st.ds }
<d_bot> <aotmr> | Add -> (* ... *)
<d_bot> <aotmr> | Dot -> (* ... *)
<d_bot> <aotmr> ```
<d_bot> <colin> awaiting the IRC users who'll ask you to read the channel description
<d_bot> <aotmr> Aw shit 🤦‍♂️
<d_bot> <colin> :p
<zozozo> @aotmr : code blocks from discord do not render great on the irc side of this channel, so it'd be best if you could use some paste website to link to code when there are more than a few lines, ^^
<d_bot> <aotmr> There it is
<zozozo> haha, XD
<d_bot> <aotmr> Well all that goes to say
<d_bot> <aotmr> You can express stack operations using pattern matching.
<d_bot> <colin> if you think that's cute, you'll like a similar idea in dependent typing where you can express stack changes (as a list) indexing the opcodes or something similar
<d_bot> <aotmr> For example, to swap the top two items on the stack, you'd use the record update syntax
<d_bot> <aotmr> `{ st with ds = match st.ds with a:🅱️:tl -> b:🅰️:tl | _ -> assert false }`
<d_bot> <aotmr> Last code block for the time being, I promise 😅
<d_bot> <aotmr> (And you can also use `let` matching, I've found, but I can't get ocaml to stop complaining even though I fully understand it'll crash if there aren't enough elements)
<d_bot> <aotmr> Oh, have a paper on that?
<d_bot> <aotmr> I'm wanting to see how high-level I can get with forth and still generate good code for small microprocessors--say, for NES and game boy dev
<d_bot> <colin> no, just thought it was very cute when I studied Agda at university, relevant construction of Hutton's razor can be found at https://github.com/fredrikNordvallForsberg/CS410-20/blob/master/Coursework/Two.agda#L492-L506 what you're saying just reminded me of it, not really relevant just in case you wanted to see cute things
<zozozo> @aotmr : small one-line blocks of code (like your last one) are mostly okay I'd say, ^^
<d_bot> <aotmr> Oh I'll look at it never the less, thanks.
<d_bot> <aotmr> Forth has its own concept of combinators and I want to try to compile those efficiently
<d_bot> <aotmr> Honestly I'd say OCaml is distantly related to FORTH just usagewise, there's a similar concept of "pipelining". Where in FORTH you'd write a series of words, passing state between them implicitly on the stack, you do the same in Ocaml when expressing a `|>` or `@@` pipeline
<d_bot> <aotmr> This is an interesting idea as, while FORTH is typically untyped, I could use this concept to track the entire lifetimes of values throughout a program
<d_bot> <colin> it's just a nice encoding of how the stack ought to change, helps the type system help you implement it correctly (though not a full specification by any means, just a cute stack requirement)
<d_bot> <ggole> There are some interesting typed concatenative langs
<d_bot> <ggole> Kitten and Cat
<d_bot> <aotmr> I've finally taken the forth-pill so to speak because I finally understand how to implement a compiler for the language
<d_bot> <colin> a whole new world.mp3 https://llvm.moe/
<d_bot> <colin> see past stack-based paradigm
<d_bot> <aotmr> Well, once I have a compiler for a stack-based VM that opens the door to using it as an intermediate representation
<d_bot> <colin> would there be any benefit
<d_bot> <colin> I, admittedly, have never seen the appeal of stack-based languages for general programming
<d_bot> <colin> I used to write postscript by hand recreationally
<d_bot> <colin> but that's about it
<d_bot> <aotmr> It's admittedly kind of recreational
<d_bot> <aotmr> I think the real strength is in the way you can build an entire system from the ground up by hand and know every moving part
<d_bot> <aotmr> You could write an optimizing compiler x86 in, oh, a month
<d_bot> <colin> sadly the majority of back-end optimisations for x86 are really just suffering
<d_bot> <aotmr> OCaml's own VM is stack-based so it's kind of circular
<d_bot> <colin> yeah but that's just the bytecode OCaml stuff
<d_bot> <aotmr> Oh yeah no x86 is a horrible architecture to program for
<d_bot> <aotmr> Sure but it's still a neat thought
<d_bot> <aotmr> But I digress
<d_bot> <colin> I used to be confused as to why Xavier Leroy's earlier work seemed to focus rather specifically on bytecode stack machines as the target of Camls
<d_bot> <colin> but then someone said like "it was research into creating a tactic computational kernel for some proof assistant"
<d_bot> <colin> not sure how true that is, perhaps someone here can clarify if that's nonsense
<d_bot> <colin> and Xavier just really likes stack machines
<d_bot> <aotmr> So, it could be that you can take advantage of immutable VM states in unit testing
<d_bot> <aotmr> And using it to accelerate the general process
<d_bot> <aotmr> If you wanted to do an exhaustive search of the program P with inputs a, b, c..., you could run P over every possible value of a, b, c
<d_bot> <aotmr> That is, we're trying to find a, b, c... that causes P to fail
bartholin has joined #ocaml
<d_bot> <ggole> There's actually some tooling for that
<d_bot> <ggole> See Crowbar
<d_bot> <aotmr> One way to speed up that process is to memoize the VM state, I think
<d_bot> <ggole> It's not exhaustive search, but coverage-feedback guided random generation
<d_bot> <aotmr> If we find a "success" set of (a, b, c...), we could maybe remember all of the previous states of the VM and if we ever encounter them again we can stop early
<d_bot> <aotmr> But that would blow up your space requirements for little speedup, I'd think
<d_bot> <colin> can see why that'd help (as a form of concolic execution) but I think the accepted reality in industry is that Google fuzz their own software over billions of instances using AFL on dozens of Google cloud instances and just consider that alright
<d_bot> <aotmr> My other use case is of a rewindable debugger where you can undo all the way back to the start of the program
<d_bot> <colin> time travel debugging is pretty cool
<d_bot> <aotmr> That also brings to mind the idea of a rewindable game engine, I think rewind mechanics are pretty cool in theory
<d_bot> <colin> I always wanted a clean injection mechanism for debugging
<d_bot> <colin> hot reloading debugging stubs, that kinda thing
<d_bot> <aotmr> I'm still not entirely familiar with the mechanics of debuggers
<d_bot> <colin> syscalls and suffering™️
<d_bot> <aotmr> I'm under the impression that, if you can execute from RAM, you can at least single-step on pretty much any CPU
<d_bot> <colin> yeah there's architectural single step stuff provided by most systems; *nix has PTRACE_SINGLESTEP
<d_bot> <aotmr> If you want to single-step the instruction at a given address, then you'd write some kind of "breakpoint" opcode (or, crudely, even just an absolute jump) directly following it, but you'd have to know the length of the opcode beforehand
<d_bot> <aotmr> But I'd hope consumer CPUs can single-step in silicon by now 😅
<d_bot> <colin> variable length encoding is just one part of suffering in writing x86(_64) tooling, yes
<d_bot> <aotmr> Oh yeah I guess debugging has to be infinitely easier on a fixed-length RISC
<d_bot> <aotmr> Imagine if x86 had an instruction that only decoded the length of an instruction at a given address
<d_bot> <colin> I suppose there's other challenges, given the domain where RISC microprocessors are probably most prevalently being debugged
<d_bot> <colin> who knows, they might, Intel has a ton of hidden instructions and their manual doesn't even document some of them accurately
<d_bot> <aotmr> You're right, there probably is.
<d_bot> <ggole> There's tons of hardware support for debugging
<d_bot> <colin> it's common for trampoline hooking code to come with a "variable length decoder" as a form of minimal disassembler
<d_bot> <ggole> Watch registers and that kind of thing
<d_bot> <ggole> Pretty complicated from what I understand
<d_bot> <colin> to know how many bytes to replace w/ their placed `jmp` or `push ...; ret` etc.
<d_bot> <colin> but yeah, can't lie
<d_bot> <colin> confused how we went from stack langs to all this
<d_bot> <colin> what is your ambition, aotmr, to write a forth interpreter/compiler?
<d_bot> <aotmr> Just to do it, I guess. I think it's interesting to build a software stack nearly from the bottom up--or nearly so
<d_bot> <colin> what, in Forth?
<d_bot> <aotmr> I mean, build a Forth itself from the bottom up
<d_bot> <colin> oh alright
<d_bot> <aotmr> In theory it can even be possible to replace the Ocaml parts with Forth themselves
<d_bot> <aotmr> Though "bootstrapping"
<d_bot> <aotmr> First, I'd write a forth compiler in ocaml
<d_bot> <aotmr> Then, translate the compiler to forth
<d_bot> <aotmr> Compile the compiler-in-forth with the compiler-in-ocaml
<d_bot> <aotmr> And then I have a forth compiler, compiled and written in forth
<d_bot> <colin> can graduate to something hacky like JITing the FORTH then using C FFI to map the code and somehow return opaque caml values back to the user as callables within OCaml
<d_bot> <colin> galaxy brain interplay
<d_bot> <aotmr> That sounds terrifying
<d_bot> <colin> -ly based
<d_bot> <aotmr> You got it
<d_bot> <colin> don't actually know if you can do that
<d_bot> <colin> on the conceptual level, you certainly can with enough hacks
<d_bot> <aotmr> Probably the easiest way to "JIT" stack code is just to apply peephole optimization
<d_bot> <colin> can't lie, I hate stacks
<d_bot> <aotmr> The compiler writer writes manual superwords that implement a series of smaller words in a faster way
<d_bot> <aotmr> For example, replacing `>r + r>` with the much shorter machine code for the equivalent sequence that just adds the top element of the stack to the third
unyu has joined #ocaml
<d_bot> <BobbyT> I’m just marinating in all these high level ideas
bartholin has quit [Ping timeout: 272 seconds]
ralu has joined #ocaml
wonko has quit [Ping timeout: 268 seconds]
<ralu> I am trying to build infer, but I keep getting error about failed dune build. So i can not build dune. Has anyone has any pointers?
mro has joined #ocaml
bartholin has joined #ocaml
Anarchos has joined #ocaml
mro has quit [Remote host closed the connection]
Haudegen has joined #ocaml
bartholin has quit [Ping timeout: 264 seconds]
vicfred has quit [Quit: Leaving]
bartholin has joined #ocaml
waleee has joined #ocaml
fluxm has quit [Quit: node-irc says goodbye]
fluxm has joined #ocaml
berberman has quit [Quit: ZNC 1.8.2 - https://znc.in]
berberman has joined #ocaml
mro has joined #ocaml
mro has quit [Ping timeout: 252 seconds]
zodeishi has joined #ocaml
<d_bot> <Bluddy> What if we make it so a proper null pointer inside an array means the end of GC scanning?
afon has joined #ocaml
bartholin has quit [Ping timeout: 245 seconds]
bartholin has joined #ocaml
berberman has quit [Quit: ZNC 1.8.2 - https://znc.in]
berberman has joined #ocaml
mro has joined #ocaml
mbuf has quit [Quit: Leaving]
<d_bot> <Drup> @Bluddy that's not compatible with a bunch of much more interesting representations improvements (like democratizing the Zarith hack, for instance)
<d_bot> <Deadrat> Would lightweight higher kinded types be added to ocaml in the future?
<d_bot> <xvw> With modular immlicits I guess that lightweight higher kinded types will be less useful
tizoc has joined #ocaml
<d_bot> <rbrott> There's a nice chapter on that idea in CPDT: <http://adam.chlipala.net/cpdt/html/Cpdt.StackMachine.html>
<d_bot> <Bluddy> @Drup could you explain the 'zarith hack'?
<d_bot> <Deadrat> But they are still years away as I understand?
<d_bot> <Drup> @Bluddy A value of type `Z.t` in zarith is either a normal ocaml integer (63bits usually, etc) or a GMP "big integers"
<d_bot> <Drup> This is achieved by considering the type morally as `int | Big of gmp`. OCaml integers already have a bit put aside for the GC to differentiate them from pointers, so we don't need an extra tag to differentiate between small integers and pointers to a big integer.
<d_bot> <Drup> This is only possible by going through the C FFI
<d_bot> <ggole> Machine zero isn't an `int` or a block though
<d_bot> <Drup> @ggole I can never remember if the tag for integers is 0 or 1.
<d_bot> <ggole> It's 1
<d_bot> <ggole> But even if it were zero, you could set aside a non-valid pointer value to indicate a truncation spot
<d_bot> <Drup> right, I'm not sure how much I like it, but it could work
<d_bot> <ggole> I guess there would have to be an `Array.unsafe_set_terminator` or something, which would be a bit nasty
<d_bot> <ggole> And I dunno what the interaction with bounds checking would be
<d_bot> <ggole> I suspect they would be more trouble than the terminator value itself though
TheLemonMan has joined #ocaml
mro has quit [Remote host closed the connection]
bartholin has quit [Ping timeout: 264 seconds]
<d_bot> <Bluddy> I need to try it out and see the performance difference.
<d_bot> <Bluddy> it's not automatically clear that setting all the memory is a bad idea
bartholin has joined #ocaml
mro has joined #ocaml
mro has quit [Ping timeout: 264 seconds]
mro has joined #ocaml
mro has quit [Client Quit]
oriba has joined #ocaml
Anarchos has quit [Quit: Vision[0.10.3]: i've been blurred!]
<companion_cube> I'd just like to point out that no one else uses a terminator for vectors, afaik
<companion_cube> it seems like a pretty bad idea :p
<d_bot> <ggole> Most of the other langs with vectors can handle uninitialised memory or keep the bits there without leaks
<companion_cube> and again, it's not that common
<companion_cube> languages that compile to native and have a GC and don't rely on C to implement a ton of datastructures are not plenty
Anarchos has joined #ocaml
salkin has joined #ocaml
Serpent7776 has joined #ocaml
favonia has quit [Ping timeout: 264 seconds]
favonia has joined #ocaml
Haudegen has quit [Quit: No Ping reply in 180 seconds.]
Haudegen has joined #ocaml
zebrag has joined #ocaml
bartholin has quit [Ping timeout: 245 seconds]
Anarchos has quit [Quit: Vision[0.10.3]: i've been blurred!]
<d_bot> <aotmr> I'm still not entirely used to building data structures in any language *but* C, to be honest--it feels strange
<d_bot> <aotmr> I probably just don't have practice because C is the only language that I use that doesn't have a dynamic array, really
wonko has joined #ocaml
<companion_cube> well OCaml is excellent for implementing a lot of data structures
<companion_cube> vectors just happen to be a bit on the low-level, unsafe memory thingie side
<d_bot> <aotmr> What's a good way to map from a discriminated union to successive integers?
<d_bot> <aotmr> And the other way around?
<companion_cube> ppx_deriving.enum maybe?
<companion_cube> if it's an enum, without payload on the variants, that is.
bartholin has joined #ocaml
<d_bot> <aotmr> Hmm
<d_bot> <aotmr> Here's a simpler question: how do I get the "tag" of a sum type?
<companion_cube> you don't :)
zebrag has quit [Quit: Konversation terminated!]
<d_bot> <aotmr> I figure I can quickly map integers to most of the opcodes and then manually handle opcodes with a payload
<companion_cube> it's not really specified in the language.
<d_bot> <aotmr> Oh...
<d_bot> <octachron> The simpler and most forward-compatible way is to write the function.
zebrag has joined #ocaml
<d_bot> <aotmr> True, but then I'd have to write two functions and keep them in sync manually, or generate the code.
<d_bot> <aotmr> *sigh* Okay then
<companion_cube> the function from integers to variants seems impossible to write
<companion_cube> if they have payloads that is
<d_bot> <aotmr> I'd be converting from a packed representation
mro has joined #ocaml
<companion_cube> your best chance is codegen indeed
<companion_cube> variant to int: generate a pattern matching function
<companion_cube> int+payload to variant: well, match on the int I guess
<d_bot> <aotmr> Actually wait, I'm wrong
<d_bot> <aotmr> I shouldn't have written the VM with a discriminated union like this anyways
<d_bot> <aotmr> But, I guess I might as well keep a separate encoded and decoded form
<companion_cube> a VM seems like a good use case for C or C++ or rust, ironically
dhil has joined #ocaml
<d_bot> <aotmr> Oh it's definitely more appropriate, but I'm actually making some headway
<d_bot> <aotmr> I haven't played with ocaml in quite some time (OS issues--it didn't work well on Windows for me until quite recently)
mro has quit [Remote host closed the connection]
<companion_cube> glad to hear it works better now
<d_bot> <aotmr> I mean, it works better now because it's running in WSL 😆
<d_bot> <aotmr> So I'm happy that I remember how to build list to list mappings that produce and consume varying numbers of elements
mro has joined #ocaml
mro has quit [Ping timeout: 264 seconds]
TheLemonMan has quit [Quit: "It's now safe to turn off your computer."]
gareppa has joined #ocaml
<d_bot> <aotmr> Cool, so I've figured out how to build an encoder and decoder for a variable-length instruction stream
kvik has joined #ocaml
Haudegen has quit [Quit: No Ping reply in 180 seconds.]
Haudegen has joined #ocaml
mro has joined #ocaml
vicfred has joined #ocaml
mro has quit [Ping timeout: 268 seconds]
bartholin has quit [Ping timeout: 268 seconds]
shawnw has quit [Ping timeout: 268 seconds]
mro has joined #ocaml
bartholin has joined #ocaml
bartholin has quit [Client Quit]
mro has quit [Ping timeout: 272 seconds]
Techcable has quit [Quit: ZNC - https://znc.in]
Techcable has joined #ocaml
mro has joined #ocaml
shawnw has joined #ocaml
waleee has quit [Ping timeout: 272 seconds]
waleee has joined #ocaml
gareppa has quit [Quit: Leaving]
dhil has quit [Ping timeout: 245 seconds]
gareppa has joined #ocaml
dhil has joined #ocaml
mro has quit [Quit: Leaving...]
kluk has joined #ocaml
<kluk> I get "Error: Unbound module Batteries" after doing open Batteries;; on the ocaml repl after having done opam install batteries. what am I missing?
<companion_cube> #require "batteries";;
<companion_cube> (and possibly, before that, #use "topfind";;)
<kluk> Ahhh.. it wasn't clear to me that #use was needed to bring #require but now that I ran it I can see in its blurb that it does do that. Thank you very much.
<companion_cube> also note that if you use `utop` it does the topfind thing directly
<companion_cube> you can also put the blurb in ~/.ocamlinit
gareppa has quit [Quit: Leaving]
cedric has quit [Quit: Konversation terminated!]
kluk has quit [Read error: Connection reset by peer]
kluk has joined #ocaml
<kluk> companion_cube thank you for the .ocamlinit tip
romildo has joined #ocaml
romildo has quit [Client Quit]
romildo has joined #ocaml
romildo has quit [Client Quit]
romildo has joined #ocaml
<kluk> companion_cube so now I can use DynArray from Batteries just fine :) thanks so much for the help once again.
<companion_cube> heh
dhil has quit [Ping timeout: 245 seconds]
romildo has quit [Quit: Leaving]
oriba has quit [Quit: https://quassel-irc.org - Chat comfortably. Anywhere.]
kluk has quit [Read error: Connection reset by peer]
Haudegen has quit [Ping timeout: 245 seconds]
Tuplanolla has quit [Quit: Leaving.]
zodeishi has quit [Ping timeout: 252 seconds]
zodeishi has joined #ocaml
waleee has quit [Ping timeout: 264 seconds]