<discocaml>
<softwaresirppi> it has a big wall of operators saying something like "Following characters, at least one if the first character is ? or ~, optional otherwise: "
<discocaml>
<softwaresirppi> i wish they gave me a regex to test valid operators
<discocaml>
<yawaramin> you can test operators with the REPL (toplevel)
<discocaml>
<softwaresirppi> what lisp is this!!?
<discocaml>
<qrpnxz> some of these are special characters in regex. That'd be even harder to read
<discocaml>
<qrpnxz> R7RS scheme
<discocaml>
<yawaramin> `let ( MYOP ) = ()`
<discocaml>
<softwaresirppi> yeah
<discocaml>
<softwaresirppi> ```
<discocaml>
<softwaresirppi> ? ~
<discocaml>
<softwaresirppi> !
<discocaml>
<softwaresirppi>
<discocaml>
<softwaresirppi> Following characters, at least one if the first character is ? or ~, optional otherwise:
<discocaml>
<softwaresirppi> it says starting prefix char can have ? - or ! but the following characters should be $ & * + - / = > @ ^ | % <
<discocaml>
<softwaresirppi>
<discocaml>
<softwaresirppi> BUT i could still define (??)
<discocaml>
<softwaresirppi> maybe i dont understand what they mean?
<discocaml>
<softwaresirppi> cooooool
<discocaml>
<yawaramin> i think trial and error exploration with the REPL would be helpful
<discocaml>
<qrpnxz> you rarely want to be defining operators anyway
YuGiOhJCJ has joined #ocaml
bartholin has joined #ocaml
toastal has left #ocaml [Disconnected: Hibernating too long]
<discocaml>
<softwaresirppi> me want operators
<discocaml>
<softwaresirppi> its a cool thing not found in most other languagess
<discocaml>
<softwaresirppi> alrightt
euphores has quit [Quit: Leaving.]
euphores has joined #ocaml
masterbuilder has quit [Ping timeout: 255 seconds]
<discocaml>
<softwaresirppi> yo ocamlers
<discocaml>
<softwaresirppi> you can anotate a definition like `let (x : int) = 69`
<discocaml>
<softwaresirppi> but what if you wanna annotate a function definition? `let (f x : int -> int) = x + 1`
<discocaml>
<softwaresirppi> this aint workin
<discocaml>
<softwaresirppi> you can annotate a definition like `let (x : int) = 69`
<discocaml>
<softwaresirppi> but of course i can do `let f : int -> int = fun x : int -> x + 1`
<discocaml>
<softwaresirppi> any other juicyy syntax>
<discocaml>
<softwaresirppi> any other juicyy syntax?
<discocaml>
<yawaramin> `let f (x : int) : int = x + 1` - kinda clunky though. imho the best place to put the type annotations is the interface file. it would look like `val f : int -> int`
<discocaml>
<softwaresirppi> alrightttt
<discocaml>
<softwaresirppi> thats a good thing
<discocaml>
<softwaresirppi> also the `not equal to` operator is cool in ocaml lol `( <> )`
<discocaml>
<softwaresirppi> = has two same lines... <> has two bent ones
<discocaml>
<softwaresirppi> haha
toastal has joined #ocaml
<discocaml>
<yawaramin> same as SQL
<discocaml>
<softwaresirppi> oh is that so im used to using != in sql
<discocaml>
<softwaresirppi> maybe im not respecting traditions there
<discocaml>
<qrpnxz> after `let f : int -> int` there's no reason to annotate `x` you can just
<discocaml>
<qrpnxz> `let f : int -> int = fun x -> x + 1`
<discocaml>
<qrpnxz> >kinda clunky though
<discocaml>
<qrpnxz> crazy
<discocaml>
<softwaresirppi> lol yeah this is called hindley milner type inference right?
<discocaml>
<qrpnxz> no inference here
<discocaml>
<softwaresirppi> thats what my friends call me
<discocaml>
<qrpnxz> you are telling it the type
<discocaml>
<softwaresirppi> but i havent told the type of x
<discocaml>
<softwaresirppi> it knows it by function def int -> int
<discocaml>
<qrpnxz> yes you did
<discocaml>
<softwaresirppi> lol okay
<discocaml>
<softwaresirppi> smart camel
<discocaml>
<qrpnxz> oh i see what you mean. I guess it technically does infer the type of `x`, but since you are practically spelling that out when you specify the type of the function, I don't see why make a distinction
<discocaml>
<softwaresirppi> russell im kinda embarrassed but i have this type `?x:int -> int` how do you not pass a param and skip??
<discocaml>
<softwaresirppi> and eval it with default?
<discocaml>
<qrpnxz> can't
<discocaml>
<softwaresirppi> ughh then whats the point of default args?
<discocaml>
<softwaresirppi> understandable
<discocaml>
<qrpnxz> you need non-optional arguments here, otherwise it's hella ambiguous
<discocaml>
<softwaresirppi> alrightt
<discocaml>
<softwaresirppi> i added a unit parameter and it works
<discocaml>
<softwaresirppi> kinda clunky
<discocaml>
<softwaresirppi> but im not blaming
<discocaml>
<softwaresirppi> its a tricky thing to do
Serpent7776 has joined #ocaml
<discocaml>
<softwaresirppi> and tail call recursion is coooooool
<discocaml>
<softwaresirppi> guys what does ocaml stand for?
<discocaml>
<softwaresirppi> oops sorry i shouldve checked wikipedia first
<discocaml>
<softwaresirppi> abstract machine?!
<discocaml>
<softwaresirppi> sounds cool
toastal has left #ocaml [Error from remote client]
alexherbo2 has joined #ocaml
toastal has joined #ocaml
YuGiOhJCJ has quit [Quit: YuGiOhJCJ]
<discocaml>
<softwaresirppi> guys guys is there a function that is `('a -> ()) -> 'a -> 'a` and performs f x?
<discocaml>
<softwaresirppi> im looking for a way to peek through expressions when debugging? like a `tee` function?
<discocaml>
<softwaresirppi> `let tee f x = f x; x;;` this works im just asking for anything more idiomatic
<discocaml>
<._null._> OCaml doesn't define many operators in its standard library. Also, `unit` as a type is called `unit`, `()` is its value
<discocaml>
<softwaresirppi> alright
<discocaml>
<softwaresirppi> is there any way to indent `#trace` output?
<discocaml>
<softwaresirppi> goated feature by the way
<discocaml>
<softwaresirppi> would be more useful if its indented
gentauro has quit [Ping timeout: 252 seconds]
gentauro has joined #ocaml
gentauro has quit [Ping timeout: 264 seconds]
gentauro has joined #ocaml
malte has quit [Remote host closed the connection]
malte has joined #ocaml
raskol has joined #ocaml
<discocaml>
<gooby_clown> This originates from Pascal I believe
<discocaml>
<softwaresirppi> cool one
<discocaml>
<softwaresirppi> guys till now all the infix operators could be wrapped in parens and could be used as prefix operator.
<discocaml>
<softwaresirppi> `69 :: []` works BUT `( :: ) 69 []` doesnt work 11/
<discocaml>
<softwaresirppi> guys till now all the infix operators could be wrapped in parens and could be used as prefix operator.
<discocaml>
<softwaresirppi> `69 :: []` works BUT `( :: ) 69 []` doesnt work !!?
<discocaml>
<softwaresirppi> i need reasons
<discocaml>
<softwaresirppi> wtfff
<discocaml>
<._null._> It's a constructor, it takes its arguments as a comma-separated list
<discocaml>
<._null._> Constructors are not functions
<discocaml>
<deepspacejohn> (i.e. a tuple)
<discocaml>
<._null._> "Tuple" is confusing, because a constructor takes in a "tuple of arguments", but not always a tuple as argument
<discocaml>
<._null._> (if you understand tuple as value of a product type)
<discocaml>
<octachron> In other words, `(::)(1,[])` works.
<discocaml>
<softwaresirppi> damnn
<discocaml>
<softwaresirppi> so infix operators did some pattern match!!
<discocaml>
<octachron> `::` is an infix variant constructor rather than an infix operator.
<discocaml>
<softwaresirppi> if thats the case, when calling this `let (<!>) (x, y) = x + y` like `1 <!> 2` it aint workingg
<discocaml>
<softwaresirppi> oh so its not an operator. alright i dont even know what a variant constructor is... ill lookup wait a min!
<discocaml>
<octachron> In `type num = Int of int | Float of float`, `Int` and `Float` are variant constructors, because they construct values of variant type `num`.
<discocaml>
<softwaresirppi> i shouldnt be quoting stack overflow 😭 but here i am
<discocaml>
<softwaresirppi> ```
<discocaml>
<softwaresirppi>
<discocaml>
<softwaresirppi>
<discocaml>
<softwaresirppi> Parametric polymorphism (...), allows a single piece of code to be typed “generically,” using variables in place of actual types, and then instantiated with particular types as needed. Parametric definitions are uniform: all of their instances behave the same. (...)
<discocaml>
<softwaresirppi>
<discocaml>
<softwaresirppi> Ad-hoc polymorphism, by contrast, allows a polymorphic value to exhibit different behaviors when “viewed” at different types. The most common example of ad-hoc polymorphism is overloading, which associates a single function symbol with many implementations; the compiler (or the runtime system, depending on whether overloading resolution is static or dynamic) chooses an appropriate implementation for each application of the funct
<discocaml>
<softwaresirppi> ```
<discocaml>
<softwaresirppi> Parametric polymorphism =? same code on many tupes
<discocaml>
<softwaresirppi> Ad-hoc polymorphism =? different code on many types
<discocaml>
<softwaresirppi> ??
<discocaml>
<._null._> Yes, so where did you get that this snippet showed ad-hoc polymorphism ?
<discocaml>
<softwaresirppi> `type num = Int of int | Float of float` different ways of construction
<discocaml>
<softwaresirppi> making an int is different from making a float?
<discocaml>
<octachron> OCaml intentionally doesn't have adhoc polymorphism
<discocaml>
<octachron> `Int 0` is making a `num`, not an `int`.
<discocaml>
<softwaresirppi> what is `type num = Int of int | Float of float` then?
<discocaml>
<softwaresirppi> OH symbols
<discocaml>
<softwaresirppi> alright makes sense lisp-ish
<discocaml>
<._null._> Constructors in our lingo
<discocaml>
<softwaresirppi> alrightttt
<discocaml>
<softwaresirppi> so a list is a linked list??
<discocaml>
<contificate> I also think constant data tends to just be relocated
<discocaml>
<softwaresirppi> it compiles from source or something?
<discocaml>
<contificate> yes, it's a source based package manager
<discocaml>
<contificate> that builds things into your switch's subdirectory or something
<discocaml>
<contificate> like if you actually had `let xs = [1;2;3]` in a program, the resultant assembly will probably encode that as constant data using labels - I think
<discocaml>
<softwaresirppi> damn freebsd source tree kinda package manager
<discocaml>
<softwaresirppi> THATS HARDCORE
<discocaml>
<softwaresirppi> why is ocaml good at everything
<discocaml>
<softwaresirppi> god dammit
<discocaml>
<contificate> good ideas done well
<discocaml>
<softwaresirppi> i wish i found it sooner
<discocaml>
<softwaresirppi> so they compile down and then optimize?
<discocaml>
<softwaresirppi> i thought the other way around
<discocaml>
<contificate> yes, an approximation of interference: you generally can't use the same register for two temporaries if those temporaries interfere (are live at the same time)
<discocaml>
<softwaresirppi> such a marvel
<discocaml>
<contificate> generally, compilers will have some optimisation at every stage - I don't think OCaml does anything after emission of assembly
<discocaml>
<contificate> whereas GCC, LLVM, etc. have peephole passes over a representation of machine instructions, like LLVM's machineoutliner or whatever
<dh`>
those peephole passes are for cleaning up stuff that upstream logic did wrong, so... if you do things right you don't really need them
<discocaml>
<govindrajpurohit_12689> Hi everone. I'm Govind. I am an outreachy applicant. I don't much experience working with OCaml but I am very happy to learn and make some good contributions and hopefully be good enough to be an intern.
<discocaml>
<govindrajpurohit_12689> I am interested in the project Structural diffing algorithm for OCaml libraries API
spew has joined #ocaml
<discocaml>
<contificate> which, dh?
euphores has quit [Quit: Leaving.]
Haudegen has joined #ocaml
<discocaml>
<softwaresirppi> interning with Ocaml?
<discocaml>
<softwaresirppi> wtf is STRUCTURAL DIFFING
<discocaml>
<softwaresirppi> ima google
<discocaml>
<softwaresirppi> (-) operator but for trees?
<discocaml>
<softwaresirppi> cool
<discocaml>
<govindrajpurohit_12689> yeah , please help how to start ...
<discocaml>
<softwaresirppi> i have no authority to tell anything
<discocaml>
<softwaresirppi> i have no authority to tell anything (i have the IQ of a bottlecap)
<discocaml>
<._null._> Ask around in #outreachy I think
<discocaml>
<._null._> Ask around in #outreachy I think (Ok you already did, then idk)
euphores has joined #ocaml
kakadu has joined #ocaml
<discocaml>
<._null._> companion_cube: it's back up
<companion_cube>
yep, thx
mbuf has quit [Quit: Leaving]
raskol has quit [Ping timeout: 246 seconds]
toastal has quit [Ping timeout: 264 seconds]
toastal has joined #ocaml
dh` has quit [Ping timeout: 252 seconds]
toastal has quit [Quit: Gateway shutdown]
toastal has joined #ocaml
masterbuilder has joined #ocaml
olle_ has joined #ocaml
spew has quit [Ping timeout: 248 seconds]
spew has joined #ocaml
Anarchos has joined #ocaml
olle_ has quit [Ping timeout: 276 seconds]
toastal has left #ocaml [Disconnected: Received SIGTERM]
dstein64- has joined #ocaml
dstein64 has quit [Ping timeout: 248 seconds]
dstein64- is now known as dstein64
dh` has joined #ocaml
<discocaml>
<qrpnxz> seriously 😆
<discocaml>
<qrpnxz> ocaml lists are unbelievably optimized
<discocaml>
<deepspacejohn> why wouldn't immutable linked lists run fast? AFAIK, lists specifically aren't optimized more than any other data structure.
dh` has quit [Changing host]
dh` has joined #ocaml
<dh`>
linked lists are inherently slow because in general you incur a cache miss on every step
<discocaml>
<qrpnxz> cache-locality, for example, wreck them, but OCaml has good allocation patterns
<discocaml>
<qrpnxz> cache-locality, for example, but OCaml has good allocation patterns
<dh`>
as opposed to iterating an array where you both stay in the same cache line for a while and the hardware prefetcher might be able to pull up the next line for you ahead of time
<dh`>
this only becomes the dominant effect if you aren't doing anything else expensive like allocating though
bartholin has quit [Quit: Leaving]
alexherbo2 has joined #ocaml
Serpent7776 has quit [Quit: leaving]
ygrek has quit [Remote host closed the connection]
alexherbo2 has quit [Remote host closed the connection]
Tuplanolla has joined #ocaml
<masterbuilder>
what do you mean inherently? in practice, right? because theoretically one can imagine hardware optimized for graphs, there have even been such machines developed on a small scale
<masterbuilder>
it's a bit unfair when people talk about how imperative programming patterns are inherently faster when it's because the hardware is biased
<masterbuilder>
but imperative is still inherently faster even in theory because the lower complexity bound tends to be lower when you have ephemeral data structures
<masterbuilder>
but it's not a landslide
<companion_cube>
It's also because it's easier to make fast imperative hardware, it seems
<masterbuilder>
definitely
kakadu has quit [Remote host closed the connection]
<discocaml>
<contificate> still, have to factor in environmental nuance: for pretty reasonable `n`, avoiding the write barrier when maintaining some persistent list-like thing is no doubt a good option in OCaml
<discocaml>
<contificate> there's a neat paper where they use zipped lists to represent basic blocks in their compiler and got a 10% speedup over their imperative versions which do mutations (https://www.cs.tufts.edu/~nr/pubs/zipcfg.pdf)
<companion_cube>
Yeah it's a bit yikes
Anarchos has quit [Quit: Vision[]: i've been blurred!]