Arc Forumnew | comments | leaders | submit | evanrmurphy's commentslogin

Sort of a mixture of ideas from both this thread and the one about automatic list quoting [1]: currently an s-expression that is not itself quoted but whose car is, i.e.

  ('x ...)
is not a valid function call, a valid list or a valid anything else for that matter (that I know of). And if you agree with waterhouse that quote doesn't need to be rebindable [2], then this seems like valuable real estate! What should we use it for?

...

I've been sitting here for about an hour now trying to think of the best use for this form, and I keep coming back to the list. If we let ('a 'b 'c) be equivalent to '(a b c), what we end up with is sort of in-between explicitly calling the list function and quasiquotation that may be the most ergonomic option in some cases. Namely, code of the form

  `(only ,wanted ,to ,quote ,the ,first ,thing)
can now be expressed with

  ('only wanted to quote the first thing)
which is kinda nice. However, I just went through arc.arc looking for cases where this could help and didn't find much. :-/

Thoughts?

---

[1] http://arclanguage.org/item?id=12792

[2] http://arclanguage.org/item?id=12569, http://arclanguage.org/item?id=12612

-----

2 points by rocketnia 5383 days ago | link

...currently an s-expression that is not itself quoted but whose car is ... is not a valid function call...

Sure it's a function call:

  arc> ('(a b) 0)
  a
Moreover, if you consider a symbol to be a function-like value that just raises an error every time it's called, then ('foo 0) is a function call too. In fact, that's how I think of it, and I consider every value to be a "function-like value" this way.

...valuable real estate! What should we use it for?

I've found it generally unfruitful to try to get inspired for a language feature by staring at a syntax. For instance, these two syntaxes have about the same set of potential uses:

  ('foo bar baz)
  (zz foo bar baz)
In fact, everywhere we'd type "('" for the first syntax, we'd type "(zz " for the second, so there wouldn't be much difference in the overall editing experience. We can already explore the second syntax using (mac zz ...), so I'm not worried about exploring the first one too.

For your particular suggestion, we don't even need a macro.

  ('foo bar baz)
  (list 'foo bar baz)
In this case, instead of typing (', we type (list ', and the editing experience is just as similar.

-----

1 point by evanrmurphy 5383 days ago | link

> Sure it's a function call:

  arc> ('(a b) 0)
  a
Guess I shouldn't try to have epiphanies that late at night. Thanks for the sober reply.

---

Update: Then again...

> Moreover, if you consider a symbol to be a function-like value that just raises an error every time it's called, then ('foo 0) is a function call too. In fact, that's how I think of it, and I consider every value to be a "function-like value" this way.

Isn't this a bit of a cop-out? Imagine you were proposing the introduction of first-class functions into our language, trying to conjure the possibilities of returning functions as values. And I were to reply: "Well, you can already return functions as values. They just raise error messages." There are flaws in the analogy, but do you see my point?

Let me phrase my question better: Arc allows you to put many types of things in functional position - lists, strings, hashes, functions, macros - and it offers convenient behavior for each of these cases. But for the case of putting a quoted symbol in functional position, it just throws an error. Is there some convenient behavior we could be doing here instead?

> We can already explore the second syntax using (mac zz ...), so I'm not worried about exploring the first one too.

This is a good point. I've run into something like this in arc.js, where I want to use the form (. a b c). I could hack the reader to pieces to make this possible, or I could not break dotted lists and settle temporarily for (\. a b c), making sure I actually like using the construct before going to so much trouble.

-----

2 points by rocketnia 5382 days ago | link

Imagine you were proposing the introduction of first-class functions into our language, trying to conjure the possibilities of returning functions as values. And I were to reply: "Well, you can already return functions as values. They just raise error messages." There are flaws in the analogy, but do you see my point?

In that case, I'd be promoting the ability to return interesting functions. Along the way I'd probably say something like, "See, you can already return functions as values. They just raise error messages. Imagine what else they could do!"

I'm not sure that's your point, though. Maybe this is more relevant:

With the way I like to think of everything as being a function, with some just being more interesting functions than others, the term "function-like value" is pretty meaningless. If we were having a different conversation, I might say "function-like value" to mean just those values that don't throw "we couldn't think of any sensible use for calling this" errors.

---

Arc allows you to put many types of things in functional position - lists, strings, hashes, functions, macros - and it offers convenient behavior for each of these cases.

This isn't important to your point, but I think you're dividing it up the wrong way.

During compile time, there are four kinds of things in functional position: Expressions, macro names, special form names, and another category to handle metafns (essentially parameterized special forms).

The "expressions" category encompasses all run time invocations of lists, strings, tables, and closures, and since the result of the expression is only determined when we run it, not when we compile it, other kinds of values can (try to) be invoked too. By the time that happens, it's ambiguous whether the error-raising behavior belongs to the language runtime, the value itself, or something intermediate like a 'defcall framework. I blame the behavior on the value because I think it makes the language and frameworks sound like they have fewer special cases.

---

Meanwhile, your suggested syntax isn't a new category, so don't worry about me crying inconsistency here. ^_^ You just have 'quote joining the ranks of 'andf, 'complement, and 'compose as a metafn: ((quote a) b c).

Alternately, maybe you'd be content with just using (defcall sym self-and-args self-and-args) instead, so that symbols are useful as functions. (That's equivalent to a certain case of having 'quote be a metafn, though; it can just be an uninteresting metafn that acts like it isn't a metafn at all.)

---

Is there some convenient behavior we could be doing here instead?

The question hasn't changed, and my answer hasn't either: Whatever the syntax does, it'll only be a few characters more convenient than a macro.

That being said, I've thought about it a bit more deeply, and here are six criteria I've come up with for a good ('a b c) syntax, some criteria being more important than others:

-

(1) It should be a form you desperately want to stuff onto one line. Otherwise (zz a b c) will be good enough despite being two characters longer. This sort of desperation makes 'do and 'fn much more convenient names than 'begin and 'lambda.

(2) It should be a form that takes at least one symbol rather than a complicated expression, since otherwise the symbol 'a in ('a b c) is wasted. Existing forms similar to what we're looking for include (let ...), (fn ...), (assign ...), and (def ...).

(3) It should be a form you never need to combine with ssyntax. Otherwise (?a b c) will probably be better, since it allows for ?a.b, (z:?a b c), and so on. This means it probably needs to be something you always use with two or more arguments (so you don't mind losing a.b and a!b) and as usually as a standalone imperative command (so you don't mind losing a&b and a:b). Existing forms that fit this profile include (assign ...), (def ...), (zap ...), and (push ...).

(4) It should ideally have something to do with the usual meaning of 'quote, just so people don't wonder why we didn't use (`a ...), (#'a ...), or a custom read macro instead.

(5) It should ideally be better than any use we can come up with for symbols as functions. For instance, it should be better than having ('abcdefg 3) behave similarly to ("abcdefg" 3), and it should be better than Jarc's usage, which is to invoke the JVM method of that name if possible. (This is less of a criterion and more like food for thought.)

(6) We should be comfortable with the meaning of ('nil 0), whether it's consistent with list accesses like ('(a b) 0) and ('(a) 0), consistent with the new syntax, consistent with both, or consistent with neither. (This is more of a gotcha than a criterion.)

-

I think (assign ...) and (def ...) are pretty good options for satisfying both the second and third criteria. How about having ('a x y z) mean (assign a (let _ (errsafe a) (x y z)))? The code ends up looking like this:

  (zap sym:string foo)  ; old
  ('foo sym:string _)   ; new
  
  (zap [* _ 10] foo)  ; old
  ('foo * _ 10)       ; new
  
  (def idfn (x) x)  ; old
  ('idfn fn (x) x)  ; new (but without redefinition warnings)
  
  ; old
  (let _ idfn
    (def idfn (x)
      (prn "traced!")
      _.x))
  
  ; new (but without redefinition warnings)
  ('idfn fn (x)
    (prn "traced!")
    _.x)
  
  (= setter (table))  ; old
  ('setter table)     ; new
  
  (= total 0)    ; old
  ('total do 0)  ; new (but you'd still use the old version, of course)
As for the first of the criteria, it's probably just a matter of how desperate someone is to 'zap things. I use 'zap all the time, so there's a good chance I'd put it to good use, even if it does look a bit weird to me at first.

The sixth criterion is handled somewhat nicely, 'cause ('nil 0) still results in a runtime error for trying to evaluate (0), and even a usage that escapes that error, like ('nil table), stumbles upon a different runtime error for attempting to rebind 'nil. These approximate the errors that would be generated if ('nil 0) and ('nil table) were list accesses.

The rest of the criteria aren't very important. The fourth is totally betrayed here--but it doesn't matter 'cause it's just an apostrophe we're talking about--and the fifth isn't something that can't be betrayed at all unless there's clearly a better idea available.

-----

1 point by evanrmurphy 5384 days ago | link | parent | on: Tips on implementing arc

> but sadly I have nothing useful to say here since it's built atop lisp

Maybe your exploration of nil vs '() could be useful here. [1]

---

[1] http://arclanguage.org/item?id=11723

-----

1 point by shader 5384 days ago | link

That's true. Any decisions affecting the core and the reasoning behind them would be useful at this point.

In fact, it would be really interesting to hear more from pg explaining some of the cryptic comments in the original source and some of the deviations of the current arc from the designs that he outlined in his earlier essays. If the explanation for most of them turns out to be "it was easier" or "it looked better" that's ok, I just wonder some times whether shortcuts and aesthetics explain the difference, or whether there were some deeper, hard-earned insights involved.

-----

1 point by akkartik 5384 days ago | link

At least for nil vs () and a couple of other issues, I've tramped up and down over the territory and reassured myself that there aren't any huge subtleties. I've also tried to ensure (github, unit tests) that any subtleties I find are exposed to anybody following.

Arc really is that simple :)

-----

1 point by akkartik 5384 days ago | link

Ah, good point, thanks for the suggestion. Here's a more recent snapshot: http://arclanguage.org/item?id=12661

-----

1 point by evanrmurphy 5385 days ago | link | parent | on: Tips on implementing arc

The first things that come to my mind are t/nil, conses and tail-call optimization.

Ah, I actually have to come back and finish this response later. Sorry for only leaving a teaser!

-----

3 points by evanrmurphy 5388 days ago | link | parent | on: Share your useful functions/macros

> Macro: (thunk body). It's simple enough. Just like the square bracket syntax covers one-argument functions, this can cover zero-argument functions.

A side effect of making all function arguments optional [1] is that the square bracket syntax can then cover zero-argument functions too, so we get this additional (shorter) way to express your thunk example:

  [err "Ack! You called me!"]
---

[1] http://arclanguage.org/item?id=13030

-----

1 point by akkartik 5388 days ago | link

Nice. So you can use [] if it saves you a set of parens, and thunk to sidestep the implicit function call:

  (thunk 34)

-----

1 point by rocketnia 5388 days ago | link

Actually, I don't use 'thunk when it doesn't save me parens. Both "thunk" and "fn ()" take up the same number of characters (albeit not the same number of tokens), and I figure Arc programmers will have to look up what 'thunk means more often than they look up 'fn. :-p

Incidentally, it actually does save parens in that case:

  thunk.34

-----


> It has a very uniform syntax that embraces the sequence-of-characters nature of code

How would you say these Penknife utilities that focus on character streams and a read macro system? Is there a big difference?

> In Penknife, you can locally bind . and use it right away for a.b syntax.

I'm certainly attracted to the idea of locally bound syntax. This makes me want to try and write a locally binding version of aw's extend-readtable [1].

> In general, I think the conveniences homoiconicity provides can be regained through the accumulation of enough parsing utilities.

Interesting conclusion. Maybe a focus on character streams is actually homoiconic in its own right, only with a finer granularity than lisp symbols? (Or am I butchering the concept of homoiconicity to suggest this?)

> (The tf operator is the most bare-bones kind of lambda.)

Why did you name it `tf`, and in which ways is it more bare-bones than other lambdas?

You made this remark about Penknife in a different thread [2]:

> It's a language much like Arc, but what's important here is that its expressions are compiled and macro-expanded to an intermediate format first--i.e. parsed into an AST--and it's easy to make closures whose ASTs can be inspected. My plan is for the Penknife AST itself to be extensible using user-defined types, and my goal is for non-Penknife ASTs to be made using the same syntax technology used elsewhere in Penknife, right down to using the same compiler.

I thought that one of the special things about lisp-family languages was that they essentially were ASTs. That is, unlike in most languages where the syntax is so complex that you're quite far removed from the parsing layer of compilation, in lisp using s-expressions you're essentially programming in parse trees. Can you help me understand the difference between this idea and what you're describing?

Last question: do you have an in-progress implementation of Penknife, or have you been designing it on paper so far?

Thanks for sharing!

---

[1] http://awwx.ws/extend-readtable0

[2] http://arclanguage.org/item?id=12947

-----

2 points by rocketnia 5389 days ago | link

> How would you say these Penknife utilities that focus on character streams and a read macro system [compare]? Is there a big difference?

Read macros are probably a more capable system in general, if only 'cause you can make a read macro that turns your language into Penknife. :-p In fact, Racket has Scribble, which is very similar to Penknife's syntax. (http://docs.racket-lang.org/scribble/reader.html#(part._.The...)

I don't dislike read macros. I'm just optimistic about having things like #hash(...), #rx"...", and `... be unnecessary, thanks to putting operators like hash[...], rx[...], and `[...] in the global namespace where they're treated consistently with other custom syntaxes. There's no room left for read macros in Penknife's syntax, but that's just how optimistic I am. :-p

I eventually intend for certain Penknife commands to be able to replace the reader/parser, though. That's not the same as a read macro since it spans multiple subsequent commands, but it's in a similar spirit, letting syntaxes interpret the code as a stream of characters rather than a stream of self-contained commands or expressions.

> Maybe a focus on character streams is actually homoiconic in its own right, only with a finer granularity than lisp symbols?

I don't know. I don't think so. Penknife generally treats syntax (textual, abstract, or whatnot) as a domain with its own type needs. I'm not making any conscious effort to have its syntax double as a convenient way to input common data types.

Indeed, there's no notion of an "external representation" for a Penknife value either, and I'm not sure how to approach that topic. That being said, once there's even one text-serialized form for Penknife values, it's trivial to make a Penknife syntax like "literal[...]" that deserializes its body. I don't know if that counts as homoiconic either.

> Why did you name it `tf`, and in which ways is it more bare-bones than other lambdas?

There are currently two kinds of closures in Penknife: thin-fns and hefty-fns.

A thin-fn (tf) is for when all you care to do with the value is call it. Their implementation doesn't bother doing more than it has to for that purpose; right now thin-fns are just represented by Arc 'fn values.

A hefty-fn (hf) is for when you might want to reflect on the contents of the closure, including its code and the variables it captures. I'm considering having most Penknife code use hefty-fns, just in case someone finds a use for that reflection, like rewriting a library to remove bugs or compiling certain Penknife functions to JavaScript. (The latter probably won't be an entirely faithful translation, 'cause [hf ...] itself doesn't have a good JavaScript equivalent.)

> I thought that one of the special things about lisp-family languages was that they essentially were ASTs.

They're like ASTs, but they're a little bit hackish. You typically only know an s-expression is a function call once you've determined it isn't a special form. If instead every list is a special form, then basically the car of the list tells you its type, and it's equivalent to what I'm doing. (Macro forms have no equivalent in Penknife ASTs, so I'm not comparing those.)

Still, rather than just using lists, I do expect AST nodes to have completely distinct Penknife types. This is so that extending Penknife functions for different AST nodes is exactly the same experience as extending them for custom types.

> Last question: do you have an in-progress implementation of Penknife, or have you been designing it on paper so far?

Whatever I've been talking about in the future tense is still on paper, but the present tense stuff is all here: https://github.com/rocketnia/penknife

First you have to load Lathe. Follow the instructions here: https://github.com/rocketnia/lathe

Also, if you can, I recommend using Rainbow for your Arc implementation, since it gives a noticeable speed boost, but I occasionally run it on Arc 3.1 and Anarki too. Jarc is almost supported, but I broke Jarc compatibility in a recent change because the speed was worst on Jarc anyway.

Penknife's broken up into multiple files, but they're not Lathe modules, and I don't have an all-in-one loader file for them yet either, so you sort of have to manage a dependency hell right now:

  ; pk-hefty-fn.arc
  ...
  ; This is a plugin for Penknife. To use it, load it just after you
  ; load penknife.arc and pk-thin-fn.arc.

  ; pk-thin-fn.arc
  ...
  ; This is a plugin for Penknife. To use it, load it just after you
  ; load penknife.arc and pk-util.arc.
Altogether, I think the load order should be Lathe first of all, then penknife.arc, pk-util.arc, pk-thin-fn.arc, pk-hefty-fn.arc, then pk-qq.arc. Then run (pkload pk-replenv* "your/path/to/pk-util.pk") to load some utilities written in Penknife--the slowest part--and run (pkrepl) to get a REPL. You'll have to look at the code to see what utilities are available at the REPL, but if you type "drop." or "[drop]", that'll at least get you back to Arc.

I haven't actually tried Penknife on the latest versions of Rainbow and Lathe, or Anarki for that matter. If it's buggy right now, or if you hack on it and introduce bugs, then entering "[drop]" may itself cause errors. Fortunately, you may be able to recover to Arc anyway by entering an EOF, using whatever control sequence your terminal has for that. If even that doesn't work, you're stuck. ^^

-----

1 point by evanrmurphy 5389 days ago | link

> How would you say these Penknife utilities that focus on character streams and a read macro system?

That wasn't a sentence. I meant to write: How would you say these Penknife utilities that focus on character streams and a read macro system compare?

-----


From a comment on Stack Overflow [1]:

> A simple way to simulate keyword args in clojure is using hash-map on rest parameters

I had never considered this before. Maybe some variation on the idea could give us keyword args in Arc. Some sketches (making use of curly braces for dictionary literals):

  (def foo (a b . {c 1 d 2})
    (list a b c d))

  (def bar {a 1 b 2}
    (list a b))

  arc> (foo 1 2)
  (1 2 1 2)
  arc> (foo 1 2 3 4)
  (1 2 3 4)
  arc> (bar)
  (1 2)
  arc> (bar 3)
  (3 2)
  arc> (bar 3 4)
  (3 4)
hasenj posted a similar idea in the original thread [2].

---

[1] http://stackoverflow.com/questions/717963/clojure-keyword-ar...

[2] http://arclanguage.org/item?id=12566

-----

1 point by akkartik 5390 days ago | link

Yeah it also sounds similar to ruby's approach.

-----

1 point by evanrmurphy 5390 days ago | link

Well what do you think of it?

I like how this approach dodges the controversy about having special characters like `o`, `?` and `&` in the arg list. The main thing that bothers me is giving dictionaries more of the spotlight. Wasn't arc supposed to be about alists, or have we cooled off on that idea?

-----

2 points by akkartik 5390 days ago | link

The only reason lisp is about lists is that it gets us homoiconicity. I think you could include more than lists without losing homoiconicity. I've thought about that in the past.

I'm not sure the benefit of {} is lack of syntax controversy, though. You still need some syntax, whether it's {} or &, and punctuation chars will still be precious, and there'll be disputes about whether this use is worth using up this char.

Well what do you think of it?

If it existed I would totally try such an approach out to see how I liked it. In general I think I'd like more ssyntax-like infrastructure, the ability to use {} for different things to see how it fits.

The big drawback of {} vs a delimiter in this specific case is more typing (and more shift-key presses). Hmm, hey how about if we just allowed rest args to be more than a symbol, and implicitly converted to a hash table?

  (fn(a b . c 1 d 2) ..)
Implicit hash-tables like ruby would be totally awesome.

-----


For what it's worth, I think your `?` looks much nicer than `&o`, and it elegantly fits into the language so long as we continue to have no ssyntactic use for the question mark.

-----

2 points by akkartik 5390 days ago | link

Yeah, the & is just a superficial point. But I've been thinking more about &key in common lisp. I thought it was pretty redundant if you get pervasive keyword args, but there's one case it doesn't cover: if you want your rest args to take priority over the optionals.

Consider the final versioning of updating that I came up with at http://arclanguage.org/item?id=12974:

  (mac updating(place ? expr t iff 'is . body)
    (w/uniq rhs
      `(let ,rhs ,expr
         (unless (,iff ,place ,rhs)
           (= ,place ,rhs)
           ,@body))))
It's nice to have the optional args when I need them, but I need to either specify both or say :body to begin the rest args:

  (mac firsttime(place . body)
    `(updating ,place
        :body
          ,@body))
If I had 'greedy rest args' or 'lazy optionals' I could make the rest args take precedence instead. Hmm.

Update: But it looks like I can't allow both these formulations at once:

  ; A
  (updating (uvar u last-login) (date)
    (++ karma.u))

  ; B
  (ret max 0
    (each elem '(1 3 2 6 5)
      (updating max :iff > elem
        (prn "max now: " max))))
Perhaps I can use ?? for lazy optionals:

  (mac updating(place ? expr t ?? iff 'is . body)
    (w/uniq rhs
      `(let ,rhs ,expr
         (unless (,iff ,place ,rhs)
           (= ,place ,rhs)
           ,@body))))
Now I can say both A and B above, but must have :body in:

  ; C
  (mac firsttime(place . body)
    `(updating ,place
        :body
          ,@body))
What do you think? Am I over-optimizing? :)

Update 2: Hmm, perhaps I should get rid of required args (your suggestion) and have eager optionals (default), lazy optionals after '?', and rest.

-----

2 points by rocketnia 5390 days ago | link

IMO, as long as we don't have ? ssyntax, ? should be usable as a local variable name, which a special parameter list meaning defeats. Conversely, &o is already impractical as a variable name thanks to & ssyntax, so it can have a special meaning in parameter lists without introducing any warts. (I consider it a wart that in official Arc 3.1, 'o can only be used as a variable name when not destructuring.)

-----

2 points by akkartik 5390 days ago | link

I think I disagree. o is certainly a wart, but ? seems unlikely to be a variable name anyway. Have you actually used ? as a variable name before?

There's nothing special about ssyntax. If we would consider using ? as ssyntax, it's fair game to use for other syntactic purposes as well.

Update: A second rationale. As waterhouse found out (http://arclanguage.org/item?id=12612) arc is extremely permissive about letting us override things, so there's no point focusing on what is legal in this arbitrary implementation.

A third rationale. Right now you want to disallow ? because it's not ssyntax. When it becomes ssyntax won't it still be unusable in arglists for the same reason & is unusable now? :) At that rate we'd never get syntax inside arglists. Which may be a plausible position, but then we should be arguing about whether arglists can benefit from syntax.

-----

1 point by rocketnia 5390 days ago | link

Have you actually used ? as a variable name before?

I agree with you that it's unlikely. I'm mainly just a consistency nut. :) I'd like for every symbol to be seen as either special everywhere, maximizing its potential power, or else special nowhere, maximizing the number of macros that'll know what to do with it.

At least, I like this kind of consistency as long as the language/utility is going for ease of customization ('cause of fewer cases to cover) and minimalism. When it comes to making code readable and writable, consistency can be less important.

---

A second rationale. As waterhouse found out (http://arclanguage.org/item?id=12612) arc is extremely permissive about letting us override things, so there's no point focusing on what is legal in this arbitrary implementation.

For a language people are eager to make breaking changes to for their own purposes, that's true. But several programmers trying to make interoperable code won't each make breaking changes independently, right? Arc may promote a philosophy of fluidity, but any particular version of Arc is still made immovable by the community that uses it.

---

A third rationale. Right now you want to disallow ? because it's not ssyntax. When it becomes ssyntax won't it still be unusable in arglists for the same reason & is unusable now? :) At that rate we'd never get syntax inside arglists. Which may be a plausible position, but then we should be arguing about whether arglists can benefit from syntax.

Hmm? You've got what I'm saying completely backwards. I think we should commit to having ? be completely special (a kind of ssyntax, for instance) as long as we want it to be special in parameter lists. Meanwhile, & is totally usable for special behavior in parameter lists, since it's already useless for normal behavior (variable names).

-----

1 point by akkartik 5390 days ago | link

I think I'm ok with us as a community saying "this version of arc treats ? as ssyntax" without necessarily having any code to do so :) expand-ssyntax for ? is the identity until we come up with a use for it. "Use ? as a variable at your own risk."

(Probably a strawman.) What I don't want is to start reserving tokens or characters 'for later use' and enforcing that they can't be variables and so on. Common Lisp does this and it's stupid. Did you know you can't declare a function called type even though it doesn't do anything, hasn't done anything for the past 15 years? What a colossal waste of a great token! https://github.com/akkartik/wart/blob/master/009core.lisp#L1

---

You've got what I'm saying completely backwards.

Ah yes, I did. You said &o is ok.

It does raise the question of the right way to setup ssyntax. Either we're making changes to expand-ssyntax everytime we want a special case to turn off ssyntax expansion or we're saying "leave & as is when it begins or ends a symbol."

But then you could argue that &o is still impinging on a potential variable name. It's starting to feel like arguing about angels and pinheads; why is it ok to pun + and & and : so they do different things in different contexts, but not use ? because of some speculative fear of potentially punning variable names?

-----

1 point by rocketnia 5390 days ago | link

Those are all questions I worry about. ^_^ I'm really itching to post about Penknife's syntax, since I think it does a good job of dissolving these issues.

-----

1 point by evanrmurphy 5390 days ago | link

> I'm really itching to post about Penknife's syntax, since I think it does a good job of dissolving these issues.

I'd like to know more about this.

-----

1 point by rocketnia 5390 days ago | link

Ye sorta receive. ^_^ http://arclanguage.org/item?id=13071

-----

1 point by evanrmurphy 5390 days ago | link

I see what you mean. So what are some ideas for an eventual `?` ssyntax? (I realize this is kind of changing the subject...)

-----

1 point by rocketnia 5390 days ago | link

Well, one thing I've occasionally considered is having string?b become [isa b 'string]. :-p That would only do so much though, since you can just define (def a- (type) [isa _ type]) and say a-!string.b.

A while ago I was thinking of using a?b to mean (b a), with the question mark acting as sort of a backwards-pointing period. Now, for Penknife, I'm using a'b for that purpose, since it's sorta an upside-down period and it doesn't require the shift key (or even reaching off of the home row). However, a'b is parsed as two expressions in Arc, so using a`b or a?b for this purpose would probably be easier.

-----

1 point by akkartik 5390 days ago | link

I'm starting to see the reason for your fears around ? :)

-----


So when you said "lisp-1 lisp", that second "lisp" was referring to Common Lisp, not the general lisp family of programming languages?

I was just confused by that phrase. In any case, now I understand your point.

-----

1 point by akkartik 5391 days ago | link

Yeah I wasn't clear. I've been thinking about lisp-1 vs lisp-2 ever since http://arclanguage.org/item?id=12814

-----

1 point by evanrmurphy 5391 days ago | link | parent | on: Ask: what does annotate do?

> So it's just me and waterhouse against +?

IIRC, pg found himself against it too, but rtm was for it.

> what other one-character name can we use besides +?

One feature I like in PHP is the use of the dot (.) for concatenation. We've already loaded up that character quite a bit here in Arc, with its use in conses, rest parameters and for the ssyntax `a.b` => `(a b)`. But concatentation is at least vaguely isomorphic to consing. I wonder...

Probably not. `+` is your best bet, IMHO.

-----

1 point by akkartik 5391 days ago | link

I should mention, just for completeness, that haskell uses ++.

-----

1 point by evanrmurphy 5391 days ago | link

Didn't know that. Could you give a quick example?

-----

2 points by akkartik 5391 days ago | link

In haskell you can designate any sequence of characters as an infix operator. Here's the definition of ++ from the prelude (http://www.haskell.org/onlinereport/standard-prelude.html):

  (++) :: [a] -> [a] -> [a]
  []     ++ ys = ys
  (x:xs) ++ ys = x : (xs ++ ys)
so [1, 2, 3] ++ [4, 5] = [1, 2, 3, 4, 5]

-----


In another part of that thread, aw brings up his experimental table literal syntax [1]:

> I've since realized that I don't like the {a 1 b 2} syntax; I find the key value pairs aren't grouped together well enough visually for me, and the curly brackets don't stand out enough themselves.

I really liked this syntax for table literals. It's what I'm using in my lispy JavaScript project [2]. Do you find the grouping isn't clear enough even when you use strategic whitespace?

  {a 1  b 2}

  {a 1
   b 2}
Arc is the only language I know to rely so heavily on implicit paired grouping:

  (if a b
      c d
        e)

  (= x 1 y 2)

  (let x 1
    ...)

  (with (x 1 y 2)
    ...)

  ; And, of course:

  (obj a 1 b 2)
And I'm a big fan of this theme. It seems to me that whatever techniques you're employing to help keep the pairs straight in all of these contexts should work in the table literal context as well.

Update: Here's another example of implicit pairs in Arc (although it's somewhat esoteric and debatable):

  (list 1 2 3)
Since lists are made up of cons pairs, of course:

  (1 . (2 . (3 . nil)))
---

[1] http://arclanguage.org/item?id=12573

[2] https://github.com/evanrmurphy/sibilant

-----

2 points by aw 5391 days ago | link

To clarify: my comment was about my experiment with having tables print with "{a 1 b 2}":

  arc> (list (obj a 1 b 2))
  ({b 2 a 1})
it was this that I found hard to match key value pairs in a long table output and the curly brackets weren't standing out enough by themselves for me when I was scanning a large amount of debugging output.

For input, when I'm the one doing the typing :) -- and anyway the number of key value pairs is usually small anyway -- I'm all for typing fewer parentheses ^_^

-----

1 point by evanrmurphy 5391 days ago | link

Thanks for clarifying, I was being careless about the distinction.

  {glad-to  'hear
   you-like 'writing
   this-way 'though!}
:P

-----

More