Re: [Readable-discuss] wisp literal array syntax for Guile, a good idea?

2017-12-12 Thread Alan Manuel Gloria
This is arguably NOT a Guile-specific issue, but rather a general issue.
Clojure uses its array syntax for parts of its syntax, for example.

The ## seems OK, but how about just plain # ?

So like (using only (read) and not (eval (read))):

' a b
=> (quote (a b))
'(a b)
=> (quote (a b))
# a b
=> #(a b)
#(a b)
=> #(a b)

Sincerely,
AmkG


On Mon, Nov 13, 2017 at 6:38 AM, Arne Babenhauserheide 
wrote:

>
> Matt Wette  writes:
>
> > Do you have a syntax for vector literals?  If not, why can't you just
> write
>
> I don’t, but while
>
> (vector '(a b))
> ⇒ #((a b))
>
> (define (f)
>   (vector '(a b)) #f)
> (procedure-properties f)
> ⇒ ((name . f))
>
> But
> (define (f)
>   #((a b)) #f)
> (procedure-properties f)
> ⇒ ((name . f) (a b))
>
> So this is a purely Guile-specific issue: I want Guile to recognize the
> vector as function-property. If it recognized (vector ...), I could use
> the simple syntax
>
> define : hello who
> . "Say hello to WHO"
> vector
>   ' tests
> test-equal "Hello World!\n"
>hello "World"
> format #f "Hello ~a!\n"
>. who
>
> (this would be my preferred approach, but I did not find any way to get
> this working)
>
> Best wishes,
> Arne
> --
> Unpolitisch sein
> heißt politisch sein
> ohne es zu merken
>
> 
> --
> Check out the vibrant tech community on one of the world's most
> engaging tech sites, Slashdot.org! http://sdm.link/slashdot
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>
>
--
Check out the vibrant tech community on one of the world's most
engaging tech sites, Slashdot.org! http://sdm.link/slashdot___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Readable Lisp 2.0, brainstorming

2017-02-28 Thread Alan Manuel Gloria
Re: "Usage:" comment, I suppose the text editor would have to correctly
parse the below?

(define-syntax simple-define-syntax ; Usage: (simple-define-syntax (
 ...) )
  (syntax-rules ()
((simple-define-syntax (  ...) )
 (define-syntax 
   (syntax-rules ()
 ((  ...) ))

(simple-define-syntax
  (delay #| Usage: (delay ) - Delay execution of |#
)
  (delay-force (make-promise )))

(simple-define-syntax
  (define-stream ; Usage: (define-stream (  ...)  ...) -
define a function that returns a stream, and may tail-call a function that
returns a stream
 (  )
 ...)
  (define  (stream-lambda ( ...)  ...)))

or, I don't know, can you be more precise about the rules for where the
Usage: comment is placed?  Given a ; Usage: comment, where does it get
attached in the text form of the program?


Lisps allow new definitional forms, which themselves may have a different
syntax for indicating the symbol that is to be defined.  That said, a good
rule for where a ;Usage: comment ought to go might possibly be definable.

Sincerely,
AmkG


On Tue, Feb 21, 2017 at 10:49 AM, luke wallace 
wrote:

> I went to great pains to explain that what symbols mean would have to be
> explained by the symbol/function creator in a comment inside the
> symbol/function definition. The editor would pull the explanation from that
> comment. The comment would have some identifier, such as "Usage:" or
> "Tooltip:" to prefix the comment, so that the editor knew it was a special
> comment. Each function/symbol would have to be manually commented in this
> way before the editor knew about it - after all, we can't expect an editor
> to speak to humans in an understandable way about what a function does
> without telling it so - because if it could we probably wouldn't need human
> programmers any more.
>
--
Check out the vibrant tech community on one of the world's most
engaging tech sites, SlashDot.org! http://sdm.link/slashdot___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] using sweeten with newlisp

2016-09-21 Thread Alan Manuel Gloria
On Thu, Sep 22, 2016 at 4:08 AM, David Walther <
da...@clearbrookdistillery.com> wrote:

> On Wed, Sep 21, 2016 at 08:11:09AM -0400, David A. Wheeler wrote:
> >Okay.  Clojure uses {...} for hashes, so newLisp isn't the only Lisp
> where {}
> >has another meaning.  The question is, how should infix be handled?
> >It really needs some paired characters, and (...) are spoken for.
> >Does newLisp already assign [...] a meaning?
>
> newLisp uses [...] for the tag pairs previous mentioned [cmd] and [text],
> and
> the parser doesn't allow [ to be used as first character of a symbol.
>

Well, if currently the only place where [...] is allowed used are the tags
[cmd], [/cmd], [text], [/text], then I don't see a reason why we can't
automatically convert [a + [b * c]] to (+ a (* b c)) at the unsweeten level.

(but if you need readable lisp in your parser directly instead of via the
unsweeten converter, well, maybe it'll need to get overhauled...)



>If so, the best approach may be to use
> >«x + 1» : Left/right-pointing double-angle quotation mark, U+AB/U+BB.
> These are very well-supported (e.g., they are used for French quotations
> and are in Latin-1), and in many cases are the easiest to enter. There is a
> risk of them being too similar to the comparison operators < and >, but
> this doesn't seem too bad. Nested example: fact«n * «n - 1»»
> >
> >I discuss this here:
> >https://sourceforge.net/p/readable/wiki/Clojure/
>
> I suppose I could define a function that swaps the first 2 arguments then
> evaluates.  In newlisp, this won't cause any slowdown.  Then infix would
> look
> like this (similar to bourne shell [ function)
>
> > (define-macro (infix a b) (eval (extend (list b a) (args
> (lambda-macro (a b) (eval (extend (list b a) (args
> > (if (infix 1 = 2) 5 10)
> 10
> > (if (infix 1 = 1) 5 10)
> 5
>
> ColorForth distinguishes between immediate and compiled words... be nice to
> have that distinction in Lisp.  Then a symbol could behave like this at
> compile stage:
>
> (a = b) => (apply = (a b))
>
> (a = b or c > d) => (apply or (apply = (a b)) (apply > (c d)))
>
> Then we get into C style precedence rules.
>
> Since infix notation is really useful mostly for mathematical and logical
> comparisons, perhaps defining "m" for "math" would have to do the job for
> infix.  Where "m" is a full interpreter with precedence rules etc.
>
> (if (m a = b or c > d) e f)
>

I built an infix macro for Common Lisp before (it's what got me invited on
this list).  With precedence even.

Overall, we've found precedence to be less useful; see
https://sourceforge.net/p/readable/wiki/Precedence/

Also, depending on how newlisp handles macros, an infix macro might not be
as powerful as you think.  Classical motivating example for why we should
have infix handled at the reader rather than at the macro level:

{a + b} ; add the number a to the number b, yielding a number
(map . {a + b}) ; add the list of numbers a to the list of numbers b,
yielding a list of numbers.

The latter gets translated at the reader level to (map . (+ a b)),
equivalent to (map + a b), which fits how map is often used in Lisplikes.

If you use an infix macro, (map . (m a + b)), that probably will not work -
it's (map m a + b).  Even if you can run macros dynamically, consider that
typically + will be a function, not a list of functions.

SRFI-26 also provides a nice "cut" macro that also works well with
reader-level infix:

(cut - a <>) ; -> (lambda (<>) (- a <>)), a function that subtracts its
argument from a
(cut . {a - <>}) ; as above, a function that subtracts its argument from a


>
> >> Also, newlisp source code is in UTF-8.  Is sweeten UTF-8 compatible?
> >
> >It's *supposed* to be, as long as the underlying Scheme is.  It probably
> >hasn't been adequately tested that way, but if it's not, it's a bug and
> needs
> >to be fixed.
>
> I have some source code I can test it on.  UTF-8 lets me use mathematical
> symbols like "delta" and "differential" and theta, phi, and pi from high
> school
> trigonometry
>
> David
>
> 
> --
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>
--
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Readable Lisp 2.0, brainstorming

2016-09-17 Thread Alan Manuel Gloria
Well, backquotes are already used in Haskell to convert prefix symbols to
infix, so I decided to reuse backquotes to convert infox symbols to prefix
^^

"let" and "where" syntax is always a problem...

data (List a)
. `:` :: a -> List a -> List a
. Nil :: List a
codata (Stream a)
. head :: Stream a -> a
. tail :: Stream a -> Stream a

The main point is really just to implement syntax extensions in a non-Lisp
language. ^^ In the 80's Scheme macrologists would discuss a little about
using Scheme-style macros in C (!), but in the late 80's and 90's such
mentions in the Scheme macro papers grew less and less until they just
mention Scheme.

Some more examples:

codata (Rec a)
. stepRec :: Rec a -> Either (Rec a) a
instance (Monad Rec)
. -- codata types (Rec a) use copatterns
. stepRec (return a) = Right a
. stepRec (ma >>= fmb) = case (stepRec ma)
. . Left ma' -> Left (ma' >>= fmb)
. . Right a -> fmb a
-- Fix point operator
fixRec :: ((a -> Rec b) -> (a -> Rec b)) -> (a -> Rec b)
stepRec (fixRec ff a) = value
. ff subcall a
. where
. . stepRec (subcall a') = fixxRec ff a'
--
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Readable Lisp 2.0, brainstorming

2016-09-13 Thread Alan Manuel Gloria
On Tue, Sep 13, 2016 at 8:11 AM, David A. Wheeler 
wrote:

>
> >4.  Backquotes "invert" the use of a symbol: foo is a prefix symbol,
> >`foo`
> >is an infix symbol; while + is an infix symbol while `+` is a prefix
> >symbol.
>
> How will you identify quasi quoting? Or do users simply have to use the
> full name quasiquote ?
>

Full name, sadly ^^

The target I'm planning for these rules is not, technically speaking, a
Lisp (a dynamically-typed language whose primary data type is used to
represent its code) but rather a Haskell-like language.

The point of this is to allow a Scheme macro processor to be used on a
Haskell-like language.  So, quasiquote is a lot less needed.

syntax `<-`
syntax do
. transform
. . do
. . . p <- x
. to $ syntaxError "do: last form cannot be `p <- x'" p
. transform
. . do
. . . x
. to
. . x
. transform
. . do
. . . p <- x
. . . y
. . . ...
. to
. . . x >>= \ p -> do y ...
. transform
. . do
. . . x
. . . y
. . . ...
. to
. . x >>= \ _ -> do y ...

(well, "\" would also have to be prefix-defaulted, and the "function"
syntax would be `->` rather than \ here, with \ being a dummy stand in)

Still, let (or "where", which is a more common idiom in Haskell-like
languages, although "let" does still exist) is difficult to express in a
good indentation form

fix :: ((a -> b) -> (a -> b)) -> (a -> b)
map = value
. fix rec
. where
. . rec map f (a:as) = f a:map f as
. . rec map f Nil = Nil
{-
(map = (value
  (fix rec)
  (where
((rec map f (a:as)) = ((f a):(map f as)))
((rec map f NIl) = Nil
-}

blech!

Sincerely,
AmkG
--
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Readable Lisp 2.0, brainstorming

2016-09-11 Thread Alan Manuel Gloria
A set of rules I'm planning out, which would break with most lisp
conventions but preserve the essence of allowing redefinitions of
everything are:

1.  Symbols are of two types:

1.1.  Normally-prefix: /[A-Za-z_][A-Za-z0-9_]*/ or /[.][.]+/

1.2.  Normally-infix: /[+-*/\!@#$%^&:?<>~]+/

2.  Other datums as in typical Lisp.

3.  An out-of-line declaration indicates infix precedence levels and types
(well, at least out-of-line for "normal" datums).

4.  Backquotes "invert" the use of a symbol: foo is a prefix symbol, `foo`
is an infix symbol; while + is an infix symbol while `+` is a prefix symbol.

Processing proceeds as follows:

1.  Use "intuitive" parenthesis insertion based on indentation (in the
example below, the "." are just used to indicate indentation:

map f (a:as) =
. f a:map f as

=>

(map f (a : as) =
  (f a:map f as))


select b t f =
. if b
. . then t
. . else f

=>

(select b t f =
  (if b
(then t)
(else f)))

Handle $ SUBLIST at this stage too.

2.  Process infixes.  This involves converting infix forms to prefix forms
and handling precedence.  An infix symbol will cause () to be added to its
left and right hand sides, unless the left/right hand side is composed of
single datums; lower precedence is handled first. Example:

(1 + 2 * 3) => (`+` 1 (2 * 3)) => (`+` 1 (`*` 2 3))

(map f (a : as) = (f a : map f as))
=>
(`=` (map f (a : as)) (f a : map f as))
=>
(`=` (map f (a : as)) (`:` (f a) (map f as)))
=>
(`=` (map f (`:` a as)) (`:` (f a) (map f as)))

The final form is the one used internally, and is a Lisp.

Sincerely,
AmkG
--
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Clojure supports UTF-8 (thus, easy Unicode support)

2014-11-08 Thread Alan Manuel Gloria
Ugh.  Non-ASCII is hard to type on a majority of keyboards unless you
add special stuff.  I don't think that'll increase acceptance.

On Thu, Oct 30, 2014 at 12:58 AM, David A. Wheeler
 wrote:
> It appears that Clojure normally loads source files assuming they are UTF-8,
> which makes supporting Unicode much easier.  This suggests that using a 
> non-ASCII
> character might not be too hard for them to support.
>
> Source file src/jvm/clojure/lang/Compiler.java routine "loadFile" has this 
> Java line,
> which I believe forces reading of source code as UTF-8:
>   return load(new InputStreamReader(f, RT.UTF8), new 
> File(file).getAbsolutePath(), (new File(file)).getName());
>
> It's possible to do indirect loading where additional magic is necessary to 
> force
> configuration of the encoding, as discussed here:
>   
> https://stackoverflow.com/questions/1431008/enabling-utf-8-encoding-for-clojure-source-files
>
> --- David A. Wheeler
>
> --
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss

--
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Using readable with clojure

2014-11-08 Thread Alan Manuel Gloria
In Clojure [...] is lexically read as a vector (similar to Scheme
#(..)).  The Clojure eval then requires lambda arguments to be in a
vector rather than in a list.


>From what I notice, Clojure uses [ ] rather sparingly, so I think
indent should be ( )

On Wed, Oct 29, 2014 at 7:18 AM, David A. Wheeler  wrote:
> On Mon, 27 Oct 2014 02:04:42 +0100, martijn brekelmans  
> wrote:
>> Hello everybody,
>>
>>
>> I'm fiddling around with clojure, and I'd like to use readable with clojure.
>
> I've looked a little more at implementing "readable" (at least some tiers) in 
> Clojure, beyond http://clojure.org/reader.
>
> Without changing the core code you could implement basic curly infix with a 
> somewhat different syntax and Clojure's tagged literals.  Tagged literals let 
> you do "#my/tag element" - the reader then reads element, and passes through 
> my/tag.  Reader tags without namespace qualifiers are reserved for Clojure, 
> however, so the tag will be multiple characters. So the best you could do 
> without changing the reader, as far as I can tell, would be something like 
> #n/fx (i >= 0), where "#n/fx" is an infix processor for curly-infix.  That's 
> ugly, especially if they are embedded: #n/fx (i >= #n/fx (a + b)).
>
> Clojure has nothing user-accessible like the Common Lisp readtable.
>
> Implementing any of the readable tiers with a nicer-looking syntax will 
> require modifying the Clojure reader's source code. I took a quick peek at 
> src/jvm/clojure/lang/LispReader.java - that appears to be where the key 
> reader functionality is implemented.  It doesn't look like it'd be hard to 
> add a variation of curly-infix or neoteric expressions, but getting those 
> changes *accepted* might be another matter.
>
> I'm sure backwards-compatibility is critical for them, so using #[...] 
> instead of {...} is probably the only practical approach for them.
>
> It might be sensible to start simple, just try to get #[...] accepted for as 
> a notation for basic curly-infix (with NO neoteric support).  That has NO 
> possibility of conflict with existing code.  We could warn users to NOT 
> include syntax in there of the form a(b) with the assumption that it would be 
> interpreted as "a (b)".  The next step would be to get neoteric supported 
> inside #[...], at least in the sense of supporting a() as a synonym for 
> (a ...).  Maybe that version of neoteric could be supported at all times; the 
> problem is not writing the code, it's getting such a change *accepted*.  It 
> would be possible to also interpret "x[y...]" as "(x #[y...])", which would 
> be full neoteric with a slightly different syntax.  Note that unprefixed 
> [...] would continue to have its current meaning.
>
> Any indentation-sensitive syntax would be a much bigger step - again, not 
> because it's hard to implement, but because it has to be *accepted*.
>
> Example of infix notation in this situation:
>   #[#[a + b] > #[c * d]]
> That is not as nice as {{a + b} > {c * d}}, but I don't see a nicer 
> alternative unless they're willing to use non-ASCII pairing characters (!).
>
> In Clojure [...] and (...) have a different meaning, but it seems to me that 
> we should just leave [...] as-is.  Parens are way more common for enclosing 
> larger scopes, as far as I can tell.
>
> --- David A. Wheeler
>
> --
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss

--
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Sweetening code with #'

2014-10-04 Thread Alan Manuel Gloria
#' means different things in Scheme and in Common Lisp.

In Scheme, #'foo means (syntax foo).  It allows for #'(foo bar) to
mean (syntax (foo bar))

In Common Lisp, #'foo means "get the function binding of foo, not the
value binding".  I'm not sure but I think Common Lisp does not specify
what the s-expression it should translate to.

As you can see, out of the box the current readable-lisp interprets #'
using the Scheme meaning.

Note that you may find it easier to learn Scheme than Common Lisp; for
one, Common Lisp is a Lisp-2, which means that symbols have a function
binding and a value binding.

For quote, both lisps uses the same symbol, so you can sweeten something like:

'(foo
  (bar quux)
  (nitz meow))
==>
' foo
!   bar quux
!   nitz meow

Note the space after the quote symbol in the sweetened version.
Without the space it will be interpreted as attaching to just the foo
symbol, not the entire sub-expression.

On 10/4/14, martijn brekelmans  wrote:
> I'm new to lisp and I thought using readable would be a great bridge for
> learning lisp. So far it's been pretty good, except for one time :(
> I'm following practical lisp and there's a little bit of code using a #', I
> can't figure out how to sweeten this piece of code. Using the sweeten tool
> replaces #' with syntax, (the result is also in the pastebin link below),
> but it doesn't work when running, clisp tells me syntax is undefined.
>
> Here's the piece of code that I'd like to sweeten.
>
> It would be great if the docs contained examples on sweetening expressions
> that use #' (and probably also for similar symbols, like ').
>

--
Meet PCI DSS 3.0 Compliance Requirements with EventLog Analyzer
Achieve PCI DSS 3.0 Compliant Status with Out-of-the-box PCI DSS Reports
Are you Audit-Ready for PCI DSS 3.0 Compliance? Download White paper
Comply to PCI DSS 3.0 Requirement 10 and 11.5 with EventLog Analyzer
http://pubads.g.doubleclick.net/gampad/clk?id=154622311&iu=/4140/ostg.clktrk
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Readable version 1.0.2 released!

2014-06-27 Thread Alan Manuel Gloria
On Thu, Jun 26, 2014 at 10:33 AM, David A. Wheeler
 wrote:
> On Wed, 25 Jun 2014 05:28:39 +0800, Alan Manuel Gloria  
> wrote:
>> (cond ... else) doesn't work in Guile 1.6 (it's why I coded them as
>> (cond .. #t) in the first place).
>
> Drat. As noted in the ChangeLog, (cond... #t) causes warnings in chicken 
> Scheme.
>
> Hmm.  We already do some text processing of kernel.scm in the final build.
> Perhaps we could detect if (cond ... else) is rejected in configure, and if 
> it is,
> then substitute the relevant "(else ..." into "(#t ...".
>
> Does replacing all "(else " with "(#t " in kernel.scm work in guile 1.6?
> That would also affect some cond-expand and case statements, as well as cond 
> statements.
> If we have to only substitute some & not others, we could insert some comments
> to enable or inhibit text substitution.  That might be the simplest solution.
> That way most people just see "standard modern Scheme" while users of the
> old guile version 1.6 get working code.

*shrug* I am personally not bothered with (else ..).  I already do
have the working old code that works on 1.6, and I don't really
foresee any significant increase in the core functionality (viz.
INDENTED SCHEME) any time soon, and my code mostly works anyway, since
I copied the old version into my program (I run it as the program's
"compile" step from .sscm to .scm).

Since I'm pretty much the only one who wants Guile 1.6 support, and
I'm pretty satisfied with the perfectly working old version, feel free
to drop Guile 1.6 support.  I just wanted to make clear the reason for
why #t was used in the first place ^^.

>
> --- David A. Wheeler

--
Open source business process management suite built on Java and Eclipse
Turn processes into business applications with Bonita BPM Community Edition
Quickly connect people, data, and systems into organized workflows
Winner of BOSSIE, CODIE, OW2 and Gartner awards
http://p.sf.net/sfu/Bonitasoft
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Readable version 1.0.2 released!

2014-06-24 Thread Alan Manuel Gloria
On Mon, Jun 23, 2014 at 3:41 AM, David A. Wheeler  wrote:
> Version 1.0.2 of the "readable" package is now available!!
>
> It's a collection of small tweaks and improvements, primarily in the 
> documentation and Scheme implementation.  Having many small improvements is a 
> *good* thing.  In particular, there are no incompatible interface/language 
> changes; I view avoiding incompatible language changes as critically 
> important.
>
> Below is the ChangeLog entry for this version, which describes the 
> highlights.  If you want more detail, "git log -p" will tell all.
>
> --- David A. Wheeler
>
>
> ChangeLog for version 1.0.2:
> * Various minor Scheme bug fixes, e.g., improve EOF handling during
>   symbol reading, fix detection of unsupported #.
> * Many portability improvements, especially for Chicken Scheme and
>   rscheme.  E.G., remove all "#:" in source,
>   change "throw" to "raise", rename internal "body" to "read-body".
>   Modify sweet-run so it works unchanged on Mac OS Darwin.
> * Many changes to eliminate warnings in various Schemes, e.g.,
>   change (cond .. #t) to (cond .. else); either is legal Scheme,
>   but chicken Scheme emits warnings on the former.

(cond ... else) doesn't work in Guile 1.6 (it's why I coded them as
(cond .. #t) in the first place).

> * Add the following as delimiters: #\' and #\` and #\.
>   These are not required to be delimiters in Scheme, but
>   they can be, and doing so means that we can detect syntax errors
>   of very dodgy constructs.  This means that x'y will be
>   considered an error, not a 3-char symbol.  We can already express
>   that as |x'y|, and (x 'y) or x('y) work for making a list.
> * Optimize read-digits.
> * Improve Scheme error reporting when giving "Unexpected text
>   after n-expression" by reporting the next (peeked) character.
> * Add #!keyword-prefix and #!keyword-suffix support so can handle
>   syntax like STUFF: and :STUFF.
> * Modify Scheme sweet-run so that it returns the program exit code.
> * Add type annotations in chicken format, and ensure it does not
>   interfere with other Schemes like guile.
>
>
> --
> HPCC Systems Open Source Big Data Platform from LexisNexis Risk Solutions
> Find What Matters Most in Your Big Data with HPCC Systems
> Open Source. Fast. Scalable. Simple. Ideal for Dirty Data.
> Leverages Graph Analysis for Fast Processing & Easy Data Exploration
> http://p.sf.net/sfu/hpccsystems
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss

--
Open source business process management suite built on Java and Eclipse
Turn processes into business applications with Bonita BPM Community Edition
Quickly connect people, data, and systems into organized workflows
Winner of BOSSIE, CODIE, OW2 and Gartner awards
http://p.sf.net/sfu/Bonitasoft
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] spinoff wisp srfi

2014-06-08 Thread Alan Manuel Gloria
The specifications do not indicate what the supported elements are.
What happens if I input the C string "(define foo\n  bar)\n"? (or in
short, is parentheses supported?)  You reference SRFI-105, but only as
an indirect reference from SRFI-110.  I'd assume you want each "token"
in your syntax to actually be neoteric but it's not spelled out.  Or
is each "token" just a Lisp atom?  How about vector literals?

On Mon, Jun 9, 2014 at 1:50 AM, Arne Babenhauserheide  wrote:
> Hi Alan,
>
> Am Sonntag, 1. Juni 2014, 08:35:58 schrieb Alan Manuel Gloria:
>> It might be better to extend your clarification section a little.  I
>> think your intent here is that : at the beginning of a line adds an
>> extra open parentheses that gets closed at end-of-line (rule 4.2.7)
>> *and* defines an indentation level.
>
> Thank you for spotting that - and thanks for checking the SRFI!
>
> Thank to your commetn, I also found another point where I wasn’t spelling the 
> intent exactly enough: it defines an indentation level *at the position of 
> the colon*.
>
> I now added your note to the clarifications. How should I reference you?
>
> Best wishes,
> Arne
>
>> On Thu, May 8, 2014 at 4:31 AM, Arne Babenhauserheide  
>> wrote:
>> > Hi,
>> >
>> > I worked quite a bit on my simplified readable-spinoff wisp, and since it 
>> > now works pretty well, I drafted a SRFI. It is still quite rough, but the 
>> > basics should be in.
>> >
>> > In the rationale I contrast it to readable, and it would be nice if you 
>> > could check whether I’m fair towards readable in that.
>> >
>> > Also despite the different focus we chose, I consider you folks to be the 
>> > experts on indentation-sensitive lisp, so I would be very happy to get 
>> > your opinion.
>> >
>> >
>> > http://draketo.de/proj/wisp/srfi.html
>> >
>> >
>> > Best wishes,
>> > Arne
>> > --
>> > A man in the streets faces a knife.
>> > Two policemen are there it once. They raise a sign:
>> >
>> > “Illegal Scene! Noone may watch this!”
>> >
>> > The man gets robbed and stabbed and bleeds to death.
>> > The police had to hold the sign.
>> >
>> > …Welcome to Europe, citizen. Censorship is beautiful.
>> >
>> >( http://draketo.de/stichwort/censorship )
>> >
>> >
>> >
>> >
>> > --
>> > Is your legacy SCM system holding you back? Join Perforce May 7 to find 
>> > out:
>> > • 3 signs your SCM is hindering your productivity
>> > • Requirements for releasing software faster
>> > • Expert tips and advice for migrating your SCM now
>> > http://p.sf.net/sfu/perforce
>> > ___
>> > Readable-discuss mailing list
>> > Readable-discuss@lists.sourceforge.net
>> > https://lists.sourceforge.net/lists/listinfo/readable-discuss
>
> --
> singing a part of the history of free software:
>
> - http://infinite-hands.draketo.de
>

--
Learn Graph Databases - Download FREE O'Reilly Book
"Graph Databases" is the definitive new guide to graph databases and their 
applications. Written by three acclaimed leaders in the field, 
this first edition is now available. Download your free book today!
http://p.sf.net/sfu/NeoTech
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] spinoff wisp srfi

2014-06-08 Thread Alan Manuel Gloria
On Mon, Jun 9, 2014 at 1:50 AM, Arne Babenhauserheide  wrote:
> Hi Alan,
>
> Am Sonntag, 1. Juni 2014, 08:35:58 schrieb Alan Manuel Gloria:
>> It might be better to extend your clarification section a little.  I
>> think your intent here is that : at the beginning of a line adds an
>> extra open parentheses that gets closed at end-of-line (rule 4.2.7)
>> *and* defines an indentation level.
>
> Thank you for spotting that - and thanks for checking the SRFI!
>
> Thank to your commetn, I also found another point where I wasn’t spelling the 
> intent exactly enough: it defines an indentation level *at the position of 
> the colon*.
>
> I now added your note to the clarifications. How should I reference you?
>

Hmm?  A name in the acknowledgements section maybe?  As "Alan Manuel K. Gloria".

Sincerely,
AmkG

--
Learn Graph Databases - Download FREE O'Reilly Book
"Graph Databases" is the definitive new guide to graph databases and their 
applications. Written by three acclaimed leaders in the field, 
this first edition is now available. Download your free book today!
http://p.sf.net/sfu/NeoTech
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Damage done.

2014-05-31 Thread Alan Manuel Gloria
On Sun, May 11, 2014 at 12:45 AM, John Cowan  wrote:
> Jörg F. Wittenberger scripsit:
>
>> With cdata we'd need to watch that no ]]> is in sweet lisp.
>
> Sweet-expressions don't use square brackets for anything.
>

Not quite.  Neoteric defines "[ x ]" to mean exactly the same thing in
your base Lisp as it normally does (e.g. "( x )" in R6RS, "(fn (_) x)"
in Arc).  Also, Neoteric redefines "foo[ x ]" to mean
"($bracket-apply$ foo x)".

Still, the character sequence "]]>" is highly unlikely in Sweet.

--
Time is money. Stop wasting it! Get your web API in 5 minutes.
www.restlet.com/download
http://p.sf.net/sfu/restlet
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] spinoff wisp srfi

2014-05-31 Thread Alan Manuel Gloria
In section 4.2.7:

A colon sourrounded by whitespace (" : ") starts a bracket which gets
closed at the end of the line.

However, in your earlier set of examples 4.1.3:

let
  : x 1
y 2
z 3
  body

It's not entirely clear how your example interacts with rule 4.2.7.

It might be better to extend your clarification section a little.  I
think your intent here is that : at the beginning of a line adds an
extra open parentheses that gets closed at end-of-line (rule 4.2.7)
*and* defines an indentation level.


On Thu, May 8, 2014 at 4:31 AM, Arne Babenhauserheide  wrote:
> Hi,
>
> I worked quite a bit on my simplified readable-spinoff wisp, and since it now 
> works pretty well, I drafted a SRFI. It is still quite rough, but the basics 
> should be in.
>
> In the rationale I contrast it to readable, and it would be nice if you could 
> check whether I’m fair towards readable in that.
>
> Also despite the different focus we chose, I consider you folks to be the 
> experts on indentation-sensitive lisp, so I would be very happy to get your 
> opinion.
>
>
> http://draketo.de/proj/wisp/srfi.html
>
>
> Best wishes,
> Arne
> --
> A man in the streets faces a knife.
> Two policemen are there it once. They raise a sign:
>
> “Illegal Scene! Noone may watch this!”
>
> The man gets robbed and stabbed and bleeds to death.
> The police had to hold the sign.
>
> …Welcome to Europe, citizen. Censorship is beautiful.
>
>( http://draketo.de/stichwort/censorship )
>
>
>
>
> --
> Is your legacy SCM system holding you back? Join Perforce May 7 to find out:
> • 3 signs your SCM is hindering your productivity
> • Requirements for releasing software faster
> • Expert tips and advice for migrating your SCM now
> http://p.sf.net/sfu/perforce
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss

--
Time is money. Stop wasting it! Get your web API in 5 minutes.
www.restlet.com/download
http://p.sf.net/sfu/restlet
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] New Release?

2014-02-13 Thread Alan Manuel Gloria
On 2/13/14, "Jörg F. Wittenberger"  wrote:
>
> Am 13.02.2014 09:50, schrieb Alan Manuel Gloria:
>> I'm kinda sorta vaguely planning on a Scheme implementation which has
>> STM at its core (basically, all non-transactional mutations are
>> implicitly considered to be inside tiny transactions containing only
>> that mutation).
>
> Have you seen http://ball.askemos.org ?

Err. not really, and it's a bit more large-scale than what I had in mind.

>
> Your idea reminds me so much to our reasoning.  Just because our
> transactional memory was known to be horribly slow, we decided to have
> two complementary Scheme-alike languages: one without any side effects
> (no effects to be handled in STM, zero overhead) and one sub-language
> having only the effects.  ((Though to distinguish them we chose to
> express the latter in "long-wielded-s-expressions" a.k.a. "XML".))
>
> I'm pretty interested in your plans and progess.  Please keep me posted.

It strikes me that the separation of purity and impurity here is
almost precisely what Haskell does with the separation of the "actual"
language and the IO data type.  Truly pure functions return an IO
object, which can be combined in specific ways with other IO objects
(and with pure functions that return an IO object - for example, a
"read character" IO object can be combined with a pure function that
accepts a character and returns another IO object, forming a larger IO
object that reads a character and then does some other IO action in
response to that character).

Which is a rather big digression from readable lisps, haha.

In any case, my (vague) plan is a relatively simple R7RS compiler,
with everything as a transaction (both mutations and reads), and the
possibility to combine multiple transactions into a larger
transaction.  I/O is a bit mind-bending, so I'll go with "not a
transaction, and will throw an error if you put in a transaction,"
which is the default handling in pretty much every STM implementation
I've seen.

Sincerely,
AmkG

>
> /Jörg
>
>>If ever, it will of course have SRFI-105 by default
>> and SRFI-110 on #!sweet.
>>
>
>
> --
> Android apps run on BlackBerry 10
> Introducing the new BlackBerry 10.2.1 Runtime for Android apps.
> Now with support for Jelly Bean, Bluetooth, Mapview and more.
> Get your Android app in front of a whole new audience.  Start now.
> http://pubads.g.doubleclick.net/gampad/clk?id=124407151&iu=/4140/ostg.clktrk
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
Android apps run on BlackBerry 10
Introducing the new BlackBerry 10.2.1 Runtime for Android apps.
Now with support for Jelly Bean, Bluetooth, Mapview and more.
Get your Android app in front of a whole new audience.  Start now.
http://pubads.g.doubleclick.net/gampad/clk?id=124407151&iu=/4140/ostg.clktrk
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] New Release?

2014-02-13 Thread Alan Manuel Gloria
On 2/13/14, "Jörg F. Wittenberger"  wrote:
>
> Am 13.02.2014 09:50, schrieb Alan Manuel Gloria:
>> I'm kinda sorta vaguely planning on a Scheme implementation which has
>> STM at its core (basically, all non-transactional mutations are
>> implicitly considered to be inside tiny transactions containing only
>> that mutation).
>
> Have you seen http://ball.askemos.org ?

Err. not really, and it's a bit more large-scale than what I had in mind.

>
> Your idea reminds me so much to our reasoning.  Just because our
> transactional memory was known to be horribly slow, we decided to have
> two complementary Scheme-alike languages: one without any side effects
> (no effects to be handled in STM, zero overhead) and one sub-language
> having only the effects.  ((Though to distinguish them we chose to
> express the latter in "long-wielded-s-expressions" a.k.a. "XML".))
>
> I'm pretty interested in your plans and progess.  Please keep me posted.

It strikes me that the separation of purity and impurity here is
almost precisely what Haskell does with the separation of the "actual"
language and the IO data type.  Truly pure functions return an IO
object, which can be combined in specific ways with other IO objects
(and with pure functions that return an IO object - for example, a
"read character" IO object can be combined with a pure function that
accepts a character and returns another IO object, forming a larger IO
object that reads a character and then does some other IO action in
response to that character).

Which is a rather big digression from readable lisps, haha.

In any case, my (vague) plan is a relatively simple R7RS compiler,
with everything as a transaction (both mutations and reads), and the
possibility to combine multiple transactions into a larger
transaction.  I/O is a bit mind-bending, so I'll go with "not a
transaction, and will throw an error if you put in a transaction,"
which is the default handling in pretty much every STM implementation
I've seen.

Sincerely,
AmkG

>
> /Jörg
>
>>If ever, it will of course have SRFI-105 by default
>> and SRFI-110 on #!sweet.
>>
>
>
> --
> Android apps run on BlackBerry 10
> Introducing the new BlackBerry 10.2.1 Runtime for Android apps.
> Now with support for Jelly Bean, Bluetooth, Mapview and more.
> Get your Android app in front of a whole new audience.  Start now.
> http://pubads.g.doubleclick.net/gampad/clk?id=124407151&iu=/4140/ostg.clktrk
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
Android apps run on BlackBerry 10
Introducing the new BlackBerry 10.2.1 Runtime for Android apps.
Now with support for Jelly Bean, Bluetooth, Mapview and more.
Get your Android app in front of a whole new audience.  Start now.
http://pubads.g.doubleclick.net/gampad/clk?id=124407151&iu=/4140/ostg.clktrk
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


[Readable-discuss] New Release?

2014-02-13 Thread Alan Manuel Gloria
So... Sourceforge just now sent me an e-mail about Readable Lisp
having a new release... that was released last year October.

Is this just Sourceforge being weird or what?

So, anything new?

I'm kinda sorta vaguely planning on a Scheme implementation which has
STM at its core (basically, all non-transactional mutations are
implicitly considered to be inside tiny transactions containing only
that mutation).  If ever, it will of course have SRFI-105 by default
and SRFI-110 on #!sweet.

--
Android apps run on BlackBerry 10
Introducing the new BlackBerry 10.2.1 Runtime for Android apps.
Now with support for Jelly Bean, Bluetooth, Mapview and more.
Get your Android app in front of a whole new audience.  Start now.
http://pubads.g.doubleclick.net/gampad/clk?id=124407151&iu=/4140/ostg.clktrk
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] My first attempt: a process manager

2014-01-10 Thread Alan Manuel Gloria
On Sat, Jan 4, 2014 at 12:07 AM, Mike Gran  wrote:
> Hi.  I thought I'd take a stab at using your readable project
>
> Result is attached.  It is a process manager: a structure holds
> a list of functions and data and call the functions as a unit.
> Functions that return #f are removed from the manager, and
> functions that return #t are kept.
>
>
> My impressions are pretty favorable.  I didn't love the
>
> let block syntax, so I used defines instead.

Yes, let syntax is a big drawback with the "indentation implies
parentheses" strategy.

As a complete aside, in Haskell, there's a special "fallback" rule
where an error due to indentation matching will cause the parser to
attempt to close a group.  This rule usually triggers in Haskell's
let...in syntax (basically, the "in" keyword is generally a syntax
error except after a let group, so the parser usually errors here when
indentation is used), which seems to imply to me that even Haskell has
some trouble with let syntax, which was simply "fixed" with this
hackish solution.

xref http://www.haskell.org/onlinereport/syntax-iso.html#sect9.3 ,
particularly Note 5.

>  Also, I used
> 'cond' in lieu of 'if' because I liked the look of having
> an 'else'.

Yes, the "old" syntaxes like that tend to be very pretty in indentation syntax.

>
> It works for me with Guile 2.0.9 and Readable 1.0.
> Thanks,
>
> Mike Gran
>
> --
> Rapidly troubleshoot problems before they affect your business. Most IT
> organizations don't have a clear picture of how application performance
> affects their revenue. With AppDynamics, you get 100% visibility into your
> Java,.NET, & PHP application. Start your 15-day FREE TRIAL of AppDynamics Pro!
> http://pubads.g.doubleclick.net/gampad/clk?id=84349831&iu=/4140/ostg.clktrk
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
CenturyLink Cloud: The Leader in Enterprise Cloud Services.
Learn Why More Businesses Are Choosing CenturyLink Cloud For
Critical Workloads, Development Environments & Everything In Between.
Get a Quote or Start a Free Trial Today. 
http://pubads.g.doubleclick.net/gampad/clk?id=119420431&iu=/4140/ostg.clktrk
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Reorganize to reduce namespace pollution and maximally create library

2013-12-06 Thread Alan Manuel Gloria
> Hmm.  Generating code is reasonable of course.
> One problem with the "shar" approach is that common code will be
> copied into different separate files, and eventually not consistently
> maintained.
> I'd like to say "one thing once" as much as possible (for maintenance).
>
> A variation would be to create ONE shell script that can generate (to
> stdout)
> Scheme code for the variant identified in a parameter;
> it could "cat" the main code at the right time.
> Something like:
> =
> #!/bin/env sh
> # $1 is the type to generate.
> case "$1" in
> GUILE)
>   echo "..." ;;
> *) echo "..." ;;
> esac
> cat kernel.scm
> =
>
> A completely different approach is a cpp-like tool.
> I've cobbled together an awk implementation of cpp-like syntax so
> you can do this:
> #ifdef GUILE
> ...
> #elseifdef RSCHEME
> ...
> #else
> ...
> #endif
>
> Either one would mean that we only need to say something ONCE
> if it can be used in multiple circumstances.

I *think* awk can be more portable.

The nice thing with the separate-processors approach is that we can
solicit just the bits we need to concatenate from the various Scheme
islands.  If we have one file that makes everything, it will
eventually become a single large monster that no one likes to touch
(assuming widespread usage of this particular implementation of
SRFI-110, at least).

Separate generators for each implementation-version we claim to
support strikes as more maintainable in the long run.  I don't expect
a lot of code duplication, if we could have a "good enough" set of
"things I assume the compatibility layer can do".

Oh, and source annotation is a er.  The style used assumes Guile
idioms.  In Racket a reader is supposed to return "syntax objects",
which wrap a datum and the source location and top-level lexical
environment.  Syntax objects are either a datum+source loc, or a
syntax-cons on syntax objects (or a syntax-vector or a
syntax-whatever).

It's theoretically possible to use a eq?-key hash table for
attach-source-info (key is the datum, value is the source info), wrap
sweet-read, and when sweet-read returns a datum, to convert the datum
and its sub-datums to syntax objects, attaching the source info to
each datum.  Instead of exporting sweet-read directly, we just wrap it
into an extra layer of (let () ..) that returns sweet-read and
friends, then wraps the returned sweet-read into an actual sweet-read
that makes the hash table and does the whatever whatever needed to
turn them into syntax objects.  The hash table does not need to be
weak-keyed, since it lives only within the sweet-read invocation.

Sincerely,
AmkG

--
Sponsored by Intel(R) XDK 
Develop, test and display web and hybrid apps with a single code base.
Download it for free now!
http://pubads.g.doubleclick.net/gampad/clk?id=111408631&iu=/4140/ostg.clktrk
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Reorganize to reduce namespace pollution and maximally create library

2013-12-05 Thread Alan Manuel Gloria
On Mon, Nov 25, 2013 at 10:10 PM, David A. Wheeler
 wrote:
> John Cowan:
>> Dude, you have a hold of the Tar Baby here. R6RS and R7RS libraries
>> can't be the result of a macro, neither as a whole nor in part. All
>> you've done is trade off one set of portability breakers for another.
>
> Ugh.  In that case, maybe we should just drop the 
> "readable-kernel-module-contents"
> macro altogether, and just write straight code with weird names to
> reduce possible namespace problems.
> We can include cond-expand guile magic so that it works as-is as a guile 
> module.
>
> Alan: Any objections?

None whatsoever.

I think Jorg's proposal to make a file (the "shar") that makes the
output based on the detected Scheme implementation is good.  We could
even run the file multiple times to generate different outputs, one
for each Scheme supported and detected.

I propose this system:

1.  We write as if we own the namespace.  Select some suitable soup of
features from R4RS through R7RS, and define it in comments well in the
core implementation file.  The core implementation file is then just a
bunch of (define ...) forms, possibly with some hooks on options like
"CL mode" or "Scheme mode".

2.  Write a bunch of "shar"s, which take the original file and
transform it to code that a particular Scheme implementation-version
accepts.  Basically, it just prepends and appends some additional
code, probably just plain text, to the core implementation file.  The
shar can put the entire core implementation file within some sort of
(define-library... ) form, if needed.

3.  If a particular Scheme implementation-version supports parameters,
then the "CL mode" option can be made into a parameter.  If not, it
can be a global instead.  We document this in, say, a USAGE.Chicken or
USAGE.Guile-1.8 or whatever file.

For example, a "standard R5RS shar" would just wrap the implementation
file in something like:

#! /bin/sh

IN=$1
OUT=$2

cat > $OUT <> $OUT
cat > $OUT 

Re: [Readable-discuss] Portability tweaks to kernel.scm (our Scheme implementation)

2013-12-05 Thread Alan Manuel Gloria
On Sun, Nov 17, 2013 at 10:02 AM, David A. Wheeler
 wrote:
> Alan: This redefines raise/guard for all guiles, even if it's already 
> available.
> It should probably only do that for guile < 1.8, and should otherwise yank in
> the real R6RS handler.  Do you agree?  If so, could you add that magic, to
> minimize futzing low-level functionality... or any other cleaning up you see?
> Also... does it work on your guile 1.6?

Hello, sorry, been doing stuff unrelated to Scheme lately, so I
haven't been checking my e-mails, haha.

I'll see this soon if possible.

Sincerely,
AmkG

--
Sponsored by Intel(R) XDK 
Develop, test and display web and hybrid apps with a single code base.
Download it for free now!
http://pubads.g.doubleclick.net/gampad/clk?id=111408631&iu=/4140/ostg.clktrk
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] New release of "readable" - version 0.9.4

2013-10-08 Thread Alan Manuel Gloria
Tried on a Debian 7.1 system with very few backports, guile 1.8, NO
clisp, NO sbcl, and got:

checking for a BSD-compatible install... /usr/bin/install -c
checking whether build environment is sane... yes
checking for a thread-safe mkdir -p... /bin/mkdir -p
checking for gawk... no
checking for mawk... mawk
checking whether make sets $(MAKE)... yes
checking for a sed that does not truncate output... /bin/sed
checking for env... /usr/bin/env
checking for guile... /usr/bin/guile
checking final decision HAVE_GUILE... yes
configure: No GUILE_SITE value has been forceably set.
checking asking guile for its site directory... /usr/share/guile/site
checking Guile site directory (GUILE_SITE)  ... /usr/share/guile/site
checking if (ice-9 readline) is available... yes
checking for scsh... no
checking final decision HAVE_SCSH... no

configure: WARNING: Prefix is not /usr; ensure ASDF is configured to
look at this Common Lisp dir.
checking Common Lisp lib dir (COMMON_LISP_LIB_DIR)... $(datadir)/common-lisp
checking for register-common-lisp-source... no
checking for unregister-common-lisp-source... no
checking whether ln -s works... yes
checking final decision HAVE_COMMON_LISP... yes
checking final decision HAVE_REGISTER_COMMON_LISP_SOURCE... no
checking final decision HAVE_UNREGISTER_COMMON_LISP_SOURCE... no
checking for clisp... no
checking final decision HAVE_CLISP... no
checking for sbcl... no
checking final decision HAVE_SBCL... no

checking default markdown command... python "$(srcdir)/markdown2.py"
-x link-patterns --link-patterns-file markdown-urls
checking for a Python interpreter with version >= 2.4... python
checking for python... /usr/bin/python
checking for python version... 2.7
checking for python platform... linux2
checking for python script directory... ${prefix}/lib/python2.7/dist-packages
checking for python extension module directory...
${exec_prefix}/lib/python2.7/dist-packages
checking final decision HAVE_MARKDOWN... yes
checking for expect... /usr/bin/expect

configure: creating ./config.status
config.status: creating Makefile

Looks fine, except for "checking final decision HAVE_COMMON_LISP...
yes", when I have neither clisp nor sbcl installed... I don't remember
installing any common lisp implementations (it's a pretty fresh
reinstall), so that part looks strange.  Not breakingly strange, just
strange.

On Tue, Oct 8, 2013 at 11:35 AM, David A. Wheeler  wrote:
> On Mon, 7 Oct 2013 15:17:12 -0400, Dale Visser  wrote:
>
>> It worked nicely for me. The new, more verbose, warnings, are very helpful.
>
> Awesome!!  That's fantastic.
>
> If anyone else could give the updated version 0.9.4 a try, that'd be great.
>
>
> --- David A. Wheeler
>
> --
> October Webinars: Code for Performance
> Free Intel webinars can help you accelerate application performance.
> Explore tips for MPI, OpenMP, advanced profiling, and more. Get the most from
> the latest Intel processors and coprocessors. See abstracts and register >
> http://pubads.g.doubleclick.net/gampad/clk?id=60134071&iu=/4140/ostg.clktrk
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss

--
October Webinars: Code for Performance
Free Intel webinars can help you accelerate application performance.
Explore tips for MPI, OpenMP, advanced profiling, and more. Get the most from 
the latest Intel processors and coprocessors. See abstracts and register >
http://pubads.g.doubleclick.net/gampad/clk?id=60134071&iu=/4140/ostg.clktrk
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] More automagic for configure?

2013-09-29 Thread Alan Manuel Gloria
Eh, I think that's potentially dangerous - a user with multiple boxes
(or multiple distros on a box) might have lost track of what stuff is
on what box/distro (yeah, I'm that sloppy), and the automagic might
bite them (since most typical configures will complain loudly of
missing items, they might depend on such things).

At the minimum, such automagic should probably use BIG SHOUTING WORDS
to warn the user that something was not found and so some part will
not be built/installed.  I think.

(IIRC we require Guile and expect, but do not require CLISP).

On 9/30/13, David A. Wheeler  wrote:
> I'm thinking that "configure" should figure out what works, and then just
> ignore things that don't work.  Currently users have to add options
> to disable stuff, but that doesn't really make sense.
>
> E.G., if there's no clisp, just don't install it.
>
> Please let me know ASAP of any complaints.
>
> --- David A. Wheeler
>
> --
> October Webinars: Code for Performance
> Free Intel webinars can help you accelerate application performance.
> Explore tips for MPI, OpenMP, advanced profiling, and more. Get the most
> from
> the latest Intel processors and coprocessors. See abstracts and register >
> http://pubads.g.doubleclick.net/gampad/clk?id=60133471&iu=/4140/ostg.clktrk
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
October Webinars: Code for Performance
Free Intel webinars can help you accelerate application performance.
Explore tips for MPI, OpenMP, advanced profiling, and more. Get the most from 
the latest Intel processors and coprocessors. See abstracts and register >
http://pubads.g.doubleclick.net/gampad/clk?id=60133471&iu=/4140/ostg.clktrk
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Version 1.0.0?

2013-09-10 Thread Alan Manuel Gloria
Second the motion

On 9/11/13, David A. Wheeler  wrote:
> I propose officially releasing a version 1.0.0 of the readable work.
>
> We published version 0.9.2 recently, and I've seen no reports
> of serious bugs.  We now have a final SRFI-110, so I fully
> intend for there to be no backwards-incompatible changes
> into the future.
>
> Thoughts?   Comments?  Are there any important changes
> that would hold back a version 1.0.0 release?
>
> --- David A. Wheeler
>
> --
> How ServiceNow helps IT people transform IT departments:
> 1. Consolidate legacy IT systems to a single system of record for IT
> 2. Standardize and globalize service processes across IT
> 3. Implement zero-touch automation to replace manual, redundant tasks
> http://pubads.g.doubleclick.net/gampad/clk?id=5127&iu=/4140/ostg.clktrk
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
How ServiceNow helps IT people transform IT departments:
1. Consolidate legacy IT systems to a single system of record for IT
2. Standardize and globalize service processes across IT
3. Implement zero-touch automation to replace manual, redundant tasks
http://pubads.g.doubleclick.net/gampad/clk?id=5127&iu=/4140/ostg.clktrk
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Thoughts on sweet-expression editor modes (including ParEdit operations)

2013-08-13 Thread Alan Manuel Gloria
On 8/12/13, David A. Wheeler  wrote:
> On Sun, 11 Aug 2013 09:33:35 +0300, Beni Cherniavsky-Paskin
>  wrote:
>> A natural keystroke would be M-C-d / M-C-u (down/up-list) as if you were
>> really moving across a "(".
>> There should be visual feedback, a-la match-parens.  With feedback I
>> think
>> you also want Right/Left to move across the virtual "(".
>
> Sounds sensible.
>
>> The deeper you go into the rabbit hole of pretending there is a paren,
>> the
>> harder it is to implement consistently - e.g. saving & restoring point
>> should preserve this state (including via save-excursions!) - except by
>> actually having an invisible char in the buffer.
>
> I don't think that's all that necessary, as long as there's visual feedback
> of the scope.  In particular, invisible chars are nothing but trouble
> (you could store that info in a separate file without problems).
>
>> n-exprs present another ambiguity:
>>   |foo(bar)
>> moves over foo or foo(bar)?
>
> Ah, excellent point.  Basically, there are *two* ambiguities:
> * At the beginning of a t-expr that isn't a mono n-expr,
>do we mean the first n-expr or the whole t-expr?
> * At the beginning of an n-expr that has a tail,
>do we mean the prefix, the whole n-expr, or in between (partial tail)?
>
> I think a plausible default would be, if you're at the *very* first char
> of the expression, choose the longer one, and have a keystroke that
> can progressively change the scope (narrowing until you can't narrow more,
> and then cycling back).

Sounds good, but I doubt "cycle back" is a good idea; suppose that the
user has a sequence like so:

cond
! foo(bar)  $ do-on-foo()
! qux(bar)  $ do-on-qux()
! meow(bar) $ do-on-meow()
! bar   $ do-on-non-false()

Now suppose the user wants to do some text editing on each of the
conditions in each clause, and it so happens that this editing
requires use of the scope-narrowing key a certain number of times.

This works on the first two cases (the user is able to correctly
select the whatever he or she wanted to select and to perform whatever
he or she wanted to transform) so the user "programs" his or her hands
to do tap the scope-narrowing key automatically the required number of
times on each clause.

However, the last clause fails because the scope-narrowing key cycles
back to (say) the full clause, which isn't what the user wanted.
User: Damn You Muscle Memory!

So, I think it's best for the scope-narrowing key to *not* cycle, but
instead, will saturate to the narrowest possible.  The narrowing then
gets canceled on a cursor-movement command (is that possible in
emacs?) or escape key.  The last possibility is a "unnarrow" key which
cancels all scope-narrowing (but I think it's best to allow cursor
movement to automatically unnarrow).

Sincerely,
AmkG

--
Get 100% visibility into Java/.NET code with AppDynamics Lite!
It's a free troubleshooting tool designed for production.
Get down to code-level detail for bottlenecks, with <2% overhead. 
Download for free and get started troubleshooting in minutes. 
http://pubads.g.doubleclick.net/gampad/clk?id=48897031&iu=/4140/ostg.clktrk
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] datum comments of sweet-expressions

2013-07-11 Thread Alan Manuel Gloria
On 7/11/13, David A. Wheeler  wrote:
> On 29 May 2013 02:31:25 -0400, Mark H Weaver posted a long set of comments.
> One recommendation was to supporting datum comments of sweet-expressions
> (#; + whitespace).  The idea makes sense, and I did anticipate this.
> However, the obvious ways imply some additional trickiness in grammar
> and implementation.  Here's how I'm thinking about tackling this, but
> if anyone has a better idea, *please* speak up!!
>
>
> The current SRFI-110 says:
> "Scheme’s datum comments (#;datum) comment out the next neoteric
> expression, not the next sweet expression (and please don’t follow the
> semicolon with whitespace)."
>
> Mark H Weaver recommends:
> "I often put "#;" on the preceeding line, which you're now asking me
> not to do. What is the purpose of this request? Also, "#;" becomes
> much less useful if it cannot comment out an entire sweet expression.
> Perhaps "#;" should have a similar rule as the traditional
> abbreviations: if it is followed by whitespace, then the following
> /sweet expression/ is ignored, otherwise the following /neoteric
> expression/ is ignored. What do you think?"
>
> I have *definitely* thought about this.  Indeed, I wrote the text
> "don't follow the semicolon with whitespace" so that supporting
> datum comments of sweet-expressions could be added as a future addition.
>
> But if we add this as a *requirement*
> to SRFI-110, then the grammar rules and sample implementation
> have to be modified to handle it.  For example:
> a b
>   c
>   #; e
>  f
>   g
> => (a b c g)
>
>
> THE CHALLENGE: Properly supporting this requires properly supporting
> datum comments of a sweet-expression if it is the *last* item, e.g.:
> fee fie
>   foe
>   fum
>   #; blood
> Englishman
> => (fee fie foe fum)
>
> Handling *last* items turns out to be trickier to do, and I think
> that trickiness has nothing to do with whether or not the grammar is LL(1).
> Currently there isn't a good way to handle lines that produce no value.
> In particular, the "it_expr" rule *must* return a datum.
> In the case of lines that begin with "#!sweet", the grammar rules
> recurse so they can have something to return.  This recursion
> is why the GROUP_SPLIT rule is so complicated.  That approach
> won't work here, because the datum comment might be the last group
> at that indent level.
>
> So for the moment, let's say that we'll try to fix up the existing
> LL(1) rules instead of rewriting the grammar rules in a completely
> different notation.  Even if we do that, I want to do that as a separate
> stage, and I think we should explore simplification further first.
> So...  how could we do this?
>
> One approach would be to fiddle with all the grammar rules that
> invoke it_expr.  However, I think that would be really ugly and involve
> a lot of repetition in the rules.  The problem is that the calling
> rules each have to handle identification of the situation AND
> invoke a different action rule for that case.  Ugh.
>
> I think a better approach would be to modify the
> key production "it_expr" so that it can return an "EMPTY" value,
> distinct from a valid datum like (), that indicates
> "no value at all".  This would require some the action rules
> to handle "EMPTY" values.  I think that could be handled by
> a few tweaked procedures, e.g., some "cons" can be replaced with "econs"
> (aka "empty-handling cons"):
> (define (econs x y)
>   (cond
> ((eq? y EMPTY) x)
> ((eq? x EMPTY) y)
> (#t (cons x y
>
> If we do this, one side-effect is that the GROUP_SPLIT rules could
> probably become much simpler.  We'd no longer need to recurse deeply,
> because there'd be a way to signal that we saw an empty result.
>
> Thoughts?  Comments?  Is there a better way I'm not seeing?

Haha more nasty tagging values hahahaha!  We never seem to get rid of them!

; unique tagging value
(define EMPTY (cons '() '()))

Basically, our previous (before SRFI-110) implementations made use of
lots of these objects.  There's even a dangling "special tag to denote
comment return from hash-processing" which no longer comments anything
at all, the special tag having been removed.

This is problematic for Scheme implementations that support some kind
of extension for dispatching on "#".  Although I guess that's the
problem of the implementation.  Such # extensions are cute but make
life hard for us indentation-formatting guys.

That said our old implementations of sweet-expressions used such
unique nasty tagging values, so I don't see why we can't use them
again if it greatly simplifies our code.


Sincerely,
AmkG

--
See everything from the browser to the database with AppDynamics
Get end-to-end visibility with application monitoring from AppDynamics
Isolate bottlenecks and diagnose root cause in seconds.
Start your free trial of AppDynamics Pro today!
http://pubads.g.doubleclick.net/gampad/clk?id=48808831&iu=/4140/

Re: [Readable-discuss] "The ANTLR code is too complex"

2013-06-12 Thread Alan Manuel Gloria
P.S. I think assuming an "unlimited unread" would work and keep the
implementation reasonably "simple".  While RnRS doesn't have unlimited
unread, most production Schemes in practice support unlimited unread
on at least some of their ports.  Plus unlimited unread can be
emulated if you don't have to worry about compatibility with future
accesses on the port:

define (make-unreadable-port port)
! cons '() port

define (unreadable-port-read-char port)
! if (null? (car port))
! !  read-char $ cdr port
! !  let <* c $ car (car port) *>
! !  ! set-car! port $ cdr (car port)
! !  ! c

define (unreadable-port-unread-char port c)
! set-car! port $ cons c (car port)
! '()

Sincerely,
AmkG

On 6/13/13, Alan Manuel Gloria  wrote:
> Mark has just sent another e-mail on the SRFI-110 mailinglist:
>
> http://srfi.schemers.org/srfi-110/mail-archive/msg00186.html
>
> Basically, our options (I think) are:
>
> 1.  Drop ANTLR and use a simpler BNF.
>
> 2.  Create a "simpler" third implementation that calls to an SRFI-105
> implementation.
>
> Other things we could do, based on Mark's suggestions?
>
> On 6/5/13, David A. Wheeler  wrote:
>> On Mon, 3 Jun 2013 19:40:26 +0800, Alan Manuel Gloria
>> 
>> wrote:
>>
>>> Mark H Weaver (one of the Guile devs who is open to implementing our
>>> notation) complains that the ANTLR code is too complex.
>>>
>>> Is there anything we can do to make it simpler?
>>
>> Thanks for posting; I'd definitely like to hear others' thoughts.
>> I'm confident that we can make it simpler if we put our heads together.
>>
>> I'll probably be inactive for the next few days, due to
>> pressing work and visiting family.
>>
>> --- David A. Wheeler
>>
>

--
This SF.net email is sponsored by Windows:

Build for Windows Store.

http://p.sf.net/sfu/windows-dev2dev
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] "The ANTLR code is too complex"

2013-06-12 Thread Alan Manuel Gloria
Mark has just sent another e-mail on the SRFI-110 mailinglist:

http://srfi.schemers.org/srfi-110/mail-archive/msg00186.html

Basically, our options (I think) are:

1.  Drop ANTLR and use a simpler BNF.

2.  Create a "simpler" third implementation that calls to an SRFI-105
implementation.

Other things we could do, based on Mark's suggestions?

On 6/5/13, David A. Wheeler  wrote:
> On Mon, 3 Jun 2013 19:40:26 +0800, Alan Manuel Gloria 
> wrote:
>
>> Mark H Weaver (one of the Guile devs who is open to implementing our
>> notation) complains that the ANTLR code is too complex.
>>
>> Is there anything we can do to make it simpler?
>
> Thanks for posting; I'd definitely like to hear others' thoughts.
> I'm confident that we can make it simpler if we put our heads together.
>
> I'll probably be inactive for the next few days, due to
> pressing work and visiting family.
>
> --- David A. Wheeler
>

--
This SF.net email is sponsored by Windows:

Build for Windows Store.

http://p.sf.net/sfu/windows-dev2dev
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


[Readable-discuss] "The ANTLR code is too complex"

2013-06-03 Thread Alan Manuel Gloria
Mark H Weaver (one of the Guile devs who is open to implementing our
notation) complains that the ANTLR code is too complex.

Is there anything we can do to make it simpler?
--
Get 100% visibility into Java/.NET code with AppDynamics Lite
It's a free troubleshooting tool designed for production
Get down to code-level detail for bottlenecks, with <2% overhead.
Download for free and get started troubleshooting in minutes.
http://p.sf.net/sfu/appdyn_d2d_ap2___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Suggestions for improving readability of this code?

2013-05-11 Thread Alan Manuel Gloria
I suggest keeping it as close to the original code as possible:

defclass formatting-stream
(trivial-gray-streams:fundamental-character-input-stream)
 \\
   understream
:initarg \\ :understream
:reader \\ understream
   width
  :initarg \\ :width
  :initform \\ error "missing :width argument to formatting-stream
creation"
  :reader width
   column
   :initform \\ 0
   :accessor column
   word-wrap-p
:initform \\ t
:accessor \\ word-wrap-p
   word-buffer
:initform \\ make-array 1000
  :element-type \\ 'character
  :adjustable \\ t
  :fill-pointer \\ 0
:reader \\ word-buffer

Sincerely,
AmkG



On Sun, May 12, 2013 at 9:03 AM, David A. Wheeler 
wrote:
>
> I took this code:
>   http://paste.lisp.org/display/137116
>
> and sweetened it into:
>   http://paste.lisp.org/display/137111
>
> Any suggestions on how to make it even better, especially around the
defclass formatting-stream?  Per comp.lang.lisp, "This forms defines a
class formatting-stream inherited from
trivial-gray-streams:fundamental-character-input-stream and having 5 slots:
understream, width, column, word-wrap-p, word-buffer. The sweet-expression
variant reflects this not very clearly."  I'll take a crack at it later,
but suggestions from others welcome.
>
> --- David A. Wheeler
>
>
>
>
--
> Learn Graph Databases - Download FREE O'Reilly Book
> "Graph Databases" is the definitive new guide to graph databases and
> their applications. This 200-page book is written by three acclaimed
> leaders in the field. The early access version is available now.
> Download your free book today! http://p.sf.net/sfu/neotech_d2d_may
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
--
Learn Graph Databases - Download FREE O'Reilly Book
"Graph Databases" is the definitive new guide to graph databases and 
their applications. This 200-page book is written by three acclaimed 
leaders in the field. The early access version is available now. 
Download your free book today! http://p.sf.net/sfu/neotech_d2d_may___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Advice on implementing backquote/comma

2013-04-29 Thread Alan Manuel Gloria
You could use a dynamically-scoped variable (don't remember what they're
called in CL) to pass back the "reason for stopping" return value, and
return the read-in datum from the read implementation.  Dynamically-scoped
variables are even run-time-stack lifetimes, so they're highly appropriate
for simulating return values.


On Tue, Apr 30, 2013 at 5:31 AM, David A. Wheeler wrote:

> I'd earlier said:
> > I'm looking for advice on how to implement, in Common Lisp, the
> sweet-expression semantics for {backquote,comma,comma-at}+whitespace.
>
> Just to document my research...
>
> Common Lisp can't unget multiple characters, but it does have the ability
> "make-concatenated-stream".  You can create a stream out of a string and
> park that in front of another stream, resulting in a somewhat similar
> result:
>   http://www.lispworks.com/documentation/HyperSpec/Body/f_mk_con.htm
>
> That lets me control what goes *into* read... but *not* the results that
> come *out* of read.  Sigh.  The fundamental problem is that "read" has a
> fixed interface, and I need read to *also* return any new indentation, if I
> want to be able to use backquote with indentation-sensitive constructs.
>  And I do.
>
> So it looks like I'll have to re-implement backquote and comma in Common
> Lisp if I want a portable thread-safe Common Lisp implementation.  The good
> news is that there is such an implementation:
> >   http://www.cs.cmu.edu/Groups/AI/html/cltl/clm/node367.html
>
> On second glance it doesn't look *too* bad.  Thankfully, this
> implementation can be in its own file.
>
> --- David A. Wheeler
>
>
> --
> Try New Relic Now & We'll Send You this Cool Shirt
> New Relic is the only SaaS-based application performance monitoring service
> that delivers powerful full stack analytics. Optimize and monitor your
> browser, app, & servers with just a few lines of code. Try New Relic
> and get this awesome Nerd Life shirt! http://p.sf.net/sfu/newrelic_d2d_apr
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>
--
Try New Relic Now & We'll Send You this Cool Shirt
New Relic is the only SaaS-based application performance monitoring service 
that delivers powerful full stack analytics. Optimize and monitor your
browser, app, & servers with just a few lines of code. Try New Relic
and get this awesome Nerd Life shirt! http://p.sf.net/sfu/newrelic_d2d_apr___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] sweet processing inside brackets

2013-04-22 Thread Alan Manuel Gloria
I considered proposing this before, but one of sweet's goals is to make it
easy to use classic s-expression code while using a sweet reader.

Having the rule "everything added by sweet indentation processing is
disabled within ()" helps that tremendously.

Not to say that this idea has been explicitly rejected already, though; it
hasn't been discussed.  It really depends on a tradeoff: you lose some
amount of back-compatibility to gain expressibility.


On Mon, Apr 22, 2013 at 3:01 PM, Beni Cherniavsky-Paskin
wrote:

>
> On Apr 21, 2013 12:39 AM, "Arne Babenhauserheide"  wrote:
> >
> > Hi,
> >
> > I’m currently writing real code with wisp, and while thinking about ways
> to make non-tail-call functions as elegant as tail-called ones, I found a
> form which should work with sweet, too:
> >
> > let : : origfile ( open-file : nth 1 : command-line ) "r"
> >
> In a sense, this already exists in lisps that allow mixed parens/brackets
> automatically closing omitted ones:
>
> ( let [ ( origfile [ open-file ( nth 1 ( command-line ] "r" ]
> ... )
>
> Though that's uglier due to the asymmetry.
>
>
> --
> Precog is a next-generation analytics platform capable of advanced
> analytics on semi-structured data. The platform includes APIs for building
> apps and a phenomenal toolset for data science. Developers can use
> our toolset for easy data analysis & visualization. Get a free account!
> http://www2.precog.com/precogplatform/slashdotnewsletter
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>
>
--
Precog is a next-generation analytics platform capable of advanced
analytics on semi-structured data. The platform includes APIs for building
apps and a phenomenal toolset for data science. Developers can use
our toolset for easy data analysis & visualization. Get a free account!
http://www2.precog.com/precogplatform/slashdotnewsletter___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Comparision to wisp in SRFI; Was: Re: wisp: Whitespace to Lisp: An indentation to brackets preprocessor

2013-04-18 Thread Alan Manuel Gloria
On Thu, Apr 18, 2013 at 6:03 AM, Arne Babenhauserheide wrote:

> Am Mittwoch, 17. April 2013, 21:58:28 schrieb Alan Manuel Gloria:
> > On Wed, Apr 17, 2013 at 8:06 PM, Arne Babenhauserheide  >wrote:
> >
> > > At Wed, 17 Apr 2013 06:39:37 +0800,
> > > almkglor wrote:
> > > > Macros were not standard until R4RS, either (although most Scheme
> systems
> > > > pre-R4RS did have a Common Lisp-like unhygienic macro system).  A
> better
> > >
> > > I did not know that… I had thought that lisps had macros from very
> early
> > > on.
> > >
> >
> > Going seriously off-topic, but well...
>
> I don’t consider the history of Lisp to be off-topic when we’re discussion
> what will hopefully be part of its future :)
>
> > (define-macro (example x)
> >   `(foo ,x))
> >
> > and consider what happens when it's used in a context where 'foo is bound
> > locally:
> >
> > (let ((foo #t))
> >   (example foo))
> > ==>
> > (let ((foo #t))
> >   (foo foo))
>
> > On a Lisp-2, (foo foo) means "call the globally-bound function named 'foo
> > with the current value of the variable 'foo".  Common Lisp augments this
> > further with an excellent package system that essentially changes (?) a
> > symbol's identity - 'foo in one package does not evaluate to the same
> > symbol as 'foo in another package unless it's been imported (if I
> > understood Common Lisp correctly, LOL).  In a Lisp-1 like Scheme, it
> means
> > "call the current value of the variable 'foo with itself."  Schemers also
> > prefer not to use Common Lisp's package system, often using lexical
> binding
> > to provide some kind of package system.
> >
> > This lead to a lot of research into "hygienic macro expanders", which I
> > *think* is not yet *quite* resolved today (there are two main branches of
> > hygienic macro expanders, the syntax-case branch and the
> > syntactic-closures/explicit-renaming branches, the syntax-rules system
> can
> > be implemented on top of either, Andre van Tonder did an implementation
> > that supposedly implements both syntax-case and explicit-renaming (but
> not
> > syntactic-closures, I think)
>
> It’s strange to see that many problems in what I consider as one of the
> most powerful feature of Lisp.
>
>
Anything with a lot of power has the risk of being horribly abused and
misused.  Much of the research seems to be how to put proper safety locks
on a very powerful weapon so you don't accidentally shoot your foot, and
the *proper* shape of the safety lock.  Everyone agrees a safety lock is
good (i.e. syntax-rules).  People are (still?) arguing about the shape of
the lock (syntax-case or explicit-renaming/syntactic-closures).


> > Most coders would put a single module's code inside a single file, with
> > one-file-per-module.  So it's not an issue, if it's in the file, it's
> part
> > of the module, indentation or no indentation
>
> Is there some automatism for that?
>

Not sure, it's just a habit based on the simplest way to write a Scheme
interpreter (i.e. load all the defines in this file), so most Scheme
implementations will just build up their module systems on top of that.


>
> > > Can the module reuse defines outside the module to avoid that?
> > >
> > >
> > Most module systems allow importing another module's exported bindings,
> and
> > few might be able to import "global" bindings, whatever "global" might
> mean
> > for your Scheme system's module system.
>
> Is “top-level in the file” global?
>

Depends.  In Guile if there's a module declaration then anything in the
top-level is part of the module.  Otherwise, it depends: earlier versions
had a "global" namespace, Guile-2 (maybe?) I think has a separate namespace
for REPL.  Again, it depends on the exact implementation.  The only thing
you can rely on is that a series of defines in a file will usually be
loadable/compileable in any Scheme; whether it's "global", or put in some
kind of module implicitly, or something else, depends on the Scheme.


>
> For example in Python you have to jump through some hoops if you want to
> use a function as method, but it is possible for most cases (there is the
> module functools dedicated to that and related hackery…).
>
> Thanks for your background info!
>
> Best wishes,
> Arne
> --
> singing a part of the history of free software:
>
> - http://infinite-hands.draketo.de
>
>
--
Precog is a next-generation analytics platform capable of advanced
analytics on semi-structured data. The platform includes APIs for building
apps and a phenomenal toolset for data science. Developers can use
our toolset for easy data analysis & visualization. Get a free account!
http://www2.precog.com/precogplatform/slashdotnewsletter___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Comparision to wisp in SRFI; Was: Re: wisp: Whitespace to Lisp: An indentation to brackets preprocessor

2013-04-17 Thread Alan Manuel Gloria
On Wed, Apr 17, 2013 at 8:06 PM, Arne Babenhauserheide wrote:

> At Wed, 17 Apr 2013 06:39:37 +0800,
> almkglor wrote:
> > Macros were not standard until R4RS, either (although most Scheme systems
> > pre-R4RS did have a Common Lisp-like unhygienic macro system).  A better
>
> I did not know that… I had thought that lisps had macros from very early
> on.
>

Going seriously off-topic, but well... Lisp was originally just 'eval (in
fact, the first Lisp implementation was just an eval implementation in a
single page of code by John McCarthy).  Very soon after that, macros were
invented.  At Lisp spread, scoping was some sort of dynamic rather than
lexical, and people were not really concerned with large-scale programming,
and most Lisp's were Lisp-2's (function/macro/special form names were
separate from variables, so you could, say, have a 'if special form and an
'if variable binding).

Fast forward a couple decades and Sussman and Steele start dabbling on a
language called Schemer.  It had lexical scope and was a Lisp-1, meaning
that function names were in the same namespace as values.  This started
causing problems with the "ordinary" macros of most Lisp's available at the
time.  In particular, consider a macro that expands to a function call to a
function named 'foo:

(define-macro (example x)
  `(foo ,x))

and consider what happens when it's used in a context where 'foo is bound
locally:

(let ((foo #t))
  (example foo))
==>
(let ((foo #t))
  (foo foo))

On a Lisp-2, (foo foo) means "call the globally-bound function named 'foo
with the current value of the variable 'foo".  Common Lisp augments this
further with an excellent package system that essentially changes (?) a
symbol's identity - 'foo in one package does not evaluate to the same
symbol as 'foo in another package unless it's been imported (if I
understood Common Lisp correctly, LOL).  In a Lisp-1 like Scheme, it means
"call the current value of the variable 'foo with itself."  Schemers also
prefer not to use Common Lisp's package system, often using lexical binding
to provide some kind of package system.

This lead to a lot of research into "hygienic macro expanders", which I
*think* is not yet *quite* resolved today (there are two main branches of
hygienic macro expanders, the syntax-case branch and the
syntactic-closures/explicit-renaming branches, the syntax-rules system can
be implemented on top of either, Andre van Tonder did an implementation
that supposedly implements both syntax-case and explicit-renaming (but not
syntactic-closures, I think) but I don't see (?) it used often), except
that most users seem to prefer the syntax-case branch, but the Scheme
implementers (?) seem to prefer syntactic-closures/explicit-renaming (which
makes sense because syntax-case needs some integration into your
compiler/interpreter, and it's somewhat harder to get a *simple*
s-expression that is the macro-expansion of the syntax-case output,
syntax-case output has to be a somewhat richer AST; van Tonder's attempt I
think restricts the special annotations only to symbols, whereas
syntax-case as originally conceived had annotations infecting all nodes to
prevent the O(n^2) behavior of a similar but simpler ancestor of
syntax-case).  In fact, the inclusion of syntax-case in the R6RS branch
seems to be a minor contributor to its de facto rejection.



>
> > > Can’t they simply use the “ignore whitespace change” options to diff?
> > >
> >
> > Err, that would have to be in *patch*, not in diff.  But it would mess up
> > the indentation afterwards if you applied an indented patch into an
> > unindented source (entirely new lines in the code would be indented more
> > than their surroundings) or vice versa.  So it's less ideal for the
> > maintainer, since applying patches becomes more complex.  Simpler to just
> > start all defines at indent 0, and for code in a module-is-one-datum
> > system, just wrap all the defines in the module annotation without
> > disturbing their indentations.
>
> That’s right, yes… I think it hurts clarity (you cannot see at one
> glance whether the define is part of the module or not), but I can see
> the convenience advantage for maintaining the code.
>

Most coders would put a single module's code inside a single file, with
one-file-per-module.  So it's not an issue, if it's in the file, it's part
of the module, indentation or no indentation


>
> Can the module reuse defines outside the module to avoid that?
>
>
Most module systems allow importing another module's exported bindings, and
few might be able to import "global" bindings, whatever "global" might mean
for your Scheme system's module system.

Sincerely,
AmkG
--
Precog is a next-generation analytics platform capable of advanced
analytics on semi-structured data. The platform includes APIs for building
apps and a phenomenal toolset for data science. Developers can use
our toolset for easy data analysis 

Re: [Readable-discuss] Comparision to wisp in SRFI; Was: Re: wisp: Whitespace to Lisp: An indentation to brackets preprocessor

2013-04-16 Thread Alan Manuel Gloria
On Wed, Apr 17, 2013 at 6:18 AM, Arne Babenhauserheide wrote:

> Hi Alan,
>
> Thank you for your answer!
>
> Am Dienstag, 16. April 2013, 06:27:21 schrieb Alan Manuel Gloria:
> > > old: would not be written like that (though you can)…
> > >
> > > begin
> > >   . (display "Welcome, ") (display player) (display ", to
> Chicago!")
> > > (newline)
> > >
> > > but rather like this:
> > >
> > > begin
> > >   display "Welcome, "
> > >   display player
> > >   display ", to Chicago!"
> > >   newline
> > >
> > >
> > Actually, some Lisp programmers may prefer the former; (display
> something)
> > (newline) is idiomatic in Scheme since (format ) was not standardized
> until
> > an SRFI, and may not be available (and so displaying something on a line
> by
> > itself is better put in a single physical line in code, hence the
> (display
> > foo) (newline) all-on-a-line idiom.  Also note that because (format ...)
> > was late in standardization, many would prefer to put a sequence of
> > (display ...) forms on a single physical line).
>
> That feels pretty strange for me. The first thing I though there was to
> write a macro which displays multiple values…
>

Macros were not standard until R4RS, either (although most Scheme systems
pre-R4RS did have a Common Lisp-like unhygienic macro system).  A better
way would be to make a function that displays multiple values, but if you
start doing that, you'll start wanting the full (format ...) anyway, so you
either choose to write out a bunch of (display x) ... forms, or
re-implementing (format ...)


>
> So I did not think about that, but it’s quite possible, that this will
> disturb some. I hope that others will appreciate the clarity…
>
> What I would do in Emacs Lisp:
>
> defmacro show : &rest args
>   cons 'progn
> loop for arg in args collect
>   list 'message : list 'number-to-string arg
>
> > In Scheme, usually you just put a bunch of definitions (unindented) in a
> > file, then load them in your favorite Scheme system.  After you've hacked
> > on the definitions on the file a bit, *then* you put the module
> > annotations.  This is largely the rationale for (include ...) in R7RS
> > (define-library ...) forms: the expected Scheme workflow is to start
> with a
> > bunch of top-level, non-module definitions, hack on them until they work,
> > then put them in a module.  Hence, support for a bunch of unindented
> > definitions inside a module would be nice.
>
> To me statically indenting a block of code seems quite simple - at least
> Emacs does it in a blink, and I assume vim likewise.
>
> Yes, indeed, but :


> > different segments of their users - including patches.  By keeping their
> > published code unindented, such a maintainer could apply the same patch,
> > from say a primarily-Guile user, to both the official Guile and MzScheme
> > code.
>
> Can’t they simply use the “ignore whitespace change” options to diff?
>

Err, that would have to be in *patch*, not in diff.  But it would mess up
the indentation afterwards if you applied an indented patch into an
unindented source (entirely new lines in the code would be indented more
than their surroundings) or vice versa.  So it's less ideal for the
maintainer, since applying patches becomes more complex.  Simpler to just
start all defines at indent 0, and for code in a module-is-one-datum
system, just wrap all the defines in the module annotation without
disturbing their indentations.


>
> Best wishes,
> Arne
> --
> 1w6 sie zu achten,
> sie alle zu finden,
> in Spiele zu leiten
> und sacht zu verbinden.
> → http://1w6.org
>
--
Precog is a next-generation analytics platform capable of advanced
analytics on semi-structured data. The platform includes APIs for building
apps and a phenomenal toolset for data science. Developers can use
our toolset for easy data analysis & visualization. Get a free account!
http://www2.precog.com/precogplatform/slashdotnewsletter___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Comparision to wisp in SRFI; Was: Re: wisp: Whitespace to Lisp: An indentation to brackets preprocessor

2013-04-15 Thread Alan Manuel Gloria
On Mon, Apr 15, 2013 at 11:00 PM, Arne Babenhauserheide wrote:

> Hi,
>
> Could you change the comparision in the SRFI¹ from my first email to the
> real implementation in Wisp?
>
> ¹: http://srfi.schemers.org/srfi-110/srfi-110.html#arne
>
> Changes:
>
> - the sublist with inline : always ends at the end of the line (thanks to
> Alan)
> - inconsistent dedents produce broken code (they *should* throw an error).
> - the name is wisp :)
>
> This means that some examples change:
>
> first: should not use double colons:
>
> let : : x : compute 'x
>   : y : compute 'y
> use x y
>
> new:
>
> let
> :
> x : compute 'x
> y : compute 'y
> use x y
>
>
> SUBLIST comparison:
>
> old: would not be written like that (though you can)…
>
> begin
>   . (display "Welcome, ") (display player) (display ", to Chicago!")
> (newline)
>
> but rather like this:
>
> begin
>   display "Welcome, "
>   display player
>   display ", to Chicago!"
>   newline
>
>
Actually, some Lisp programmers may prefer the former; (display something)
(newline) is idiomatic in Scheme since (format ) was not standardized until
an SRFI, and may not be available (and so displaying something on a line by
itself is better put in a single physical line in code, hence the (display
foo) (newline) all-on-a-line idiom.  Also note that because (format ...)
was late in standardization, many would prefer to put a sequence of
(display ...) forms on a single physical line).


> or like this, if you want more complex expressions:
>
> begin
> display
> concat "Welcome, " player
>  . ", to Chicago!"
> newline
>
>
> This uses more vertical space - and I don’t mind (so it is a design
> choice not to try very hard to minimize vertical space).
>
>
> For the single gigantic top-level datum, you just indent the rest (as in
> class definitions in Python):
>
> library : example
> import : scheme base
> export .
> example-init example-open example-close
> begin
> define : example-init
> whatever ...
> ...
>
> define : example-open x
> whatever ...
> ...
>
> define : example-close y
> whatever ...
> ...
>
>
In Scheme, usually you just put a bunch of definitions (unindented) in a
file, then load them in your favorite Scheme system.  After you've hacked
on the definitions on the file a bit, *then* you put the module
annotations.  This is largely the rationale for (include ...) in R7RS
(define-library ...) forms: the expected Scheme workflow is to start with a
bunch of top-level, non-module definitions, hack on them until they work,
then put them in a module.  Hence, support for a bunch of unindented
definitions inside a module would be nice.

This is largely due to history: Scheme did not have cross-system standard
modules.  Most coders will have two or so Scheme systems they work in, and
they might want to hack on their code first on one, then on the other(s).
A flat file of definitions would usually work portably across Scheme
systems.  So Schemers generally have the habit of putting module
annotations as the last step just prior to publishing their code.  Those
interested in cross-Scheme compatibility for their published code might
very well keep the definitions unindented - some Schemes require modules to
be a single large datum (MzScheme, R6RS, R7RS) others require module
annotations as a separate datum(s) before definitions (Guile), and a
Schemer maintaining a cross-platform library might get bug reports from
different segments of their users - including patches.  By keeping their
published code unindented, such a maintainer could apply the same patch,
from say a primarily-Guile user, to both the official Guile and MzScheme
code.


> I’m used to pythen, and to me this looks completely natural. Compare:
>
> class example:
> def __init__():
> import base
> print base.stuff
> def localfunc():
> whatever …
> …
>
> Best wishes,
> Arne
>
> At Mon, 01 Apr 2013 23:53:57 +0200,
> Arne Babenhauserheide wrote:
> >
> > [1  ]
> > [1.1  ]
> > Am Donnerstag, 28. März 2013, 18:31:04 schrieb David A. Wheeler:
> > > Arne Babenhauserheide:
> > > > I finally managed to get the simple indentation to lisp preprocessor
> into a working state and thought you might be interested.
> > >
> > > Absolutely!!
> >
> > Glad to hear that! :)
> >
> > > ...
> > > > But at least I managed to write a real release text with an
> explanation of the syntax and code-examples:
> > > > http://draketo.de/light/english/wisp-lisp-indentation-preprocessor
> > >
> > > Thanks! I just added that URL link to the SRFI Alan and I are
> developing.  That way, anyone who might be interested can jump straight to
> your stuff.
> >
> > Cool - thanks!
> >
> > > > PS: @David: I just realized that I had missed quite a few of your
> ans

Re: [Readable-discuss] wisp: Whitespace to Lisp: An indentation to brackets preprocessor

2013-04-15 Thread Alan Manuel Gloria
On Mon, Apr 15, 2013 at 11:12 PM, Arne Babenhauserheide wrote:

> Just to also state it explicitely: By making inline : close at the end
> of the line, the width-of-characters problem disappears: The only
> thing which can come before a colon that defines an indentation level
> which is relevant to later lines are spaces and space-equivalents
> (blocks of underscores starting at the beginning of the line).
>
> I did not see a drop in readability due to limiting inline : to the
> present line - rather the opposite, as it prompts me to do more tail
> calls. And clarity definitely increased. Just compare those two:
>
> let : : x : compute 'x
>   : y : compute 'y
> use x y
>
>
> let
> :
> x : compute 'x
> y : compute 'y
> use x y
>
> I would not be sure at first glance myself what the first block
> does. For the second it’s clear to me.
>

In Scheme (and probably most other Lisp's) let is idiomatically formatted
as follows:

(let ((x  (compute 'x))
  (xy (compute 'xy))
  (y  (compute 'y)))
  (use x y))

This is why the original Arne formulation was attractive to me, as the let
: : part means that things are formatted closer to how Lisp let
s-expressions are typically rendered by most Lisp programmers.

Personally, I think Wisp is separate from the original Arne formulation,
due to the significant change in : semantics, and I honestly think that it
might be better to have a separate section for Wisp vs. the original Arne.


>
> Best wishes,
> Arne
>
> At Mon, 01 Apr 2013 23:53:57 +0200,
> Arne Babenhauserheide wrote:
> >
> > [1  ]
> > [1.1  ]
> > Am Donnerstag, 28. März 2013, 18:31:04 schrieb David A. Wheeler:
> > > Arne Babenhauserheide:
> > > > I finally managed to get the simple indentation to lisp preprocessor
> into a working state and thought you might be interested.
> > >
> > > Absolutely!!
> >
> > Glad to hear that! :)
> >
> > > ...
> > > > But at least I managed to write a real release text with an
> explanation of the syntax and code-examples:
> > > > http://draketo.de/light/english/wisp-lisp-indentation-preprocessor
> > >
> > > Thanks! I just added that URL link to the SRFI Alan and I are
> developing.  That way, anyone who might be interested can jump straight to
> your stuff.
> >
> > Cool - thanks!
> >
> > > > PS: @David: I just realized that I had missed quite a few of your
> answers because they were sent only to the list while Alans answers were
> also addressed to me… sorry for that.
> > >
> > > Sigh, I specifically do that so people won't get doubled emails all
> the time; some people complain when I send them both ways.  I just can't
> win :-).
> >
> > :)
> >
> > At least I found your messages after some time :)
> > (I know that my workflow can cause me to miss some messages so I *try*
> to check the ignored messages from time to time to see if any new ones are
> still relevant)
> >
> > Best wishes,
> > Arne
> > --
> > Unpolitisch sein
> > heißt politisch sein,
> > ohne es zu merken.
> > - Arne (http://draketo.de)
> >
> >
> > [1.2 This is a digitally signed message part.  (7bit)>]
> >
> > [2  ]
> >
> --
> > Own the Future-Intel® Level Up Game Demo Contest 2013
> > Rise to greatness in Intel's independent game demo contest.
> > Compete for recognition, cash, and the chance to get your game
> > on Steam. $5K grand prize plus 10 genre and skill prizes.
> > Submit your demo by 6/6/13. http://p.sf.net/sfu/intel_levelupd2d
> > [3  ]
> > ___
> > Readable-discuss mailing list
> > Readable-discuss@lists.sourceforge.net
> > https://lists.sourceforge.net/lists/listinfo/readable-discuss
>
>
> --
> Precog is a next-generation analytics platform capable of advanced
> analytics on semi-structured data. The platform includes APIs for building
> apps and a phenomenal toolset for data science. Developers can use
> our toolset for easy data analysis & visualization. Get a free account!
> http://www2.precog.com/precogplatform/slashdotnewsletter
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>
--
Precog is a next-generation analytics platform capable of advanced
analytics on semi-structured data. The platform includes APIs for building
apps and a phenomenal toolset for data science. Developers can use
our toolset for easy data analysis & visualization. Get a free account!
http://www2.precog.com/precogplatform/slashdotnewsletter___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Shoudl I add antlrworks-1.4.3.jar to the git repo?

2013-03-19 Thread Alan Manuel Gloria
I suggest putting it in the readable project's files directory, and
just put a link in the README.

On 3/20/13, David A. Wheeler  wrote:
> Alan Manuel Gloria:
>> Shouldn't dependencies be declared in a README rather than be put in
>> the actual repo?
>
> As I mentioned earlier, I worry people will have trouble finding it.
>
> One alternative would be to put the file here:
>   http://sourceforge.net/projects/readable/files/
> then it can't get lost, no matter what.
>
> --- David A. Wheeler
>
>
> --
> Everyone hates slow websites. So do we.
> Make your web apps faster with AppDynamics
> Download AppDynamics Lite for free today:
> http://p.sf.net/sfu/appdyn_d2d_mar
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_mar
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Shoudl I add antlrworks-1.4.3.jar to the git repo?

2013-03-19 Thread Alan Manuel Gloria
On Tue, Mar 19, 2013 at 6:54 PM, David A. Wheeler  wrote:
> The BNF requires the "antlrworks-1.4.3.jar" tool, which is an old version.
> Unfortunately, later versions don't work, and it looks like it'd be 
> nontrivial to fix.
>
> I'm thinking about adding antlrworks-1.4.3.jar to the git repo.
> That way, people can get it without trawling the network.
> This would add a 3.5M file (ugh).
> I don't plan to add it to the distribution file, so it's only git clone
> users who would see the load.
>
> Thoughts?

Shouldn't dependencies be declared in a README rather than be put in
the actual repo?

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_mar
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] bug#12216: peek-char incorrectly *CONSUMES* eof

2013-03-07 Thread Alan Manuel Gloria
On the debbugs mailinglist, Andy Wingo pretty much replied "will not
fix" to this bug.

Fortunately for src/kernel, we already have the mechanisms to put
wrappers around ports.  On Guile they're no-ops, but it is trivial to
modify them.

The sketch is as follows (I'll implement them later when I have time
and access to my hack computer):

1.  Modify make-read to have its returned function wrap a cons-cell
(or single-item vector) around the port.  That cons cell's car is a
port normally, but is replaced with the eof object if ever read-char
or peek-char receive an eof object

2.  Modify invoke-read to unwrap it, unless the cons-cell contains an
eof instead of a port (in which case return the EOF verbatim).

3.  Modify my-peek-char and my-read-char to check (eof-object? (car
port)) and return (car port) if so.  Otherwise execute the core
peek-char or read-char on the actual port, check if the return value
is eof, and replace the car if so.

4.  Put a guard on get-sourceinfo and have it return a nil if already
at EOF.  Modify attach-sourceinfo similarly so that if pos is a nil
then return just the object.

--
Symantec Endpoint Protection 12 positioned as A LEADER in The Forrester  
Wave(TM): Endpoint Security, Q1 2013 and "remains a good choice" in the  
endpoint security space. For insight on selecting the right partner to 
tackle endpoint security challenges, access the full report. 
http://p.sf.net/sfu/symantec-dev2dev
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Plan to release 0.7

2013-03-07 Thread Alan Manuel Gloria
On 3/8/13, David A. Wheeler  wrote:
> I plan to release a "0.7" ASAP so that people can easily download and
> install a sweet-expression reader, etc.
>
> That should help, for example, people experimenting with the first draft of
> the SRFI.
>

Sound fine to me.

Oh, and we haven't updated our ChangeLog file in *ages*.

Sincerely,
AmkG

--
Symantec Endpoint Protection 12 positioned as A LEADER in The Forrester  
Wave(TM): Endpoint Security, Q1 2013 and "remains a good choice" in the  
endpoint security space. For insight on selecting the right partner to 
tackle endpoint security challenges, access the full report. 
http://p.sf.net/sfu/symantec-dev2dev
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] New SRFI-110: Sweet-expressions!!!!!

2013-03-05 Thread Alan Manuel Gloria
Done!!

On 3/6/13, David A. Wheeler  wrote:
> BIG NEWS!
>
> We now have a new SRFI process, SRFI-110, for "sweet-expressions" in Scheme.
>  The current draft is here:
>   http://srfi.schemers.org/srfi-110/
>
> I STRONGLY encourage everyone here to also join the SRFI-110 mailing list.
> Just send mail with a "subscribe" subject line to: srfi minus 110 minus
> request at srfi dot schemers dot org
>
> Also, *please* let others in the Scheme community know about SRFI-110.
>
> For issues that apply to the SRFI (which is obviously specific to Scheme),
> please post to the SRFI-110 mailing list.
>
>  --- David A. Wheeler
>
> --
> Everyone hates slow websites. So do we.
> Make your web apps faster with AppDynamics
> Download AppDynamics Lite for free today:
> http://p.sf.net/sfu/appdyn_d2d_feb
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
Symantec Endpoint Protection 12 positioned as A LEADER in The Forrester  
Wave(TM): Endpoint Security, Q1 2013 and "remains a good choice" in the  
endpoint security space. For insight on selecting the right partner to 
tackle endpoint security challenges, access the full report. 
http://p.sf.net/sfu/symantec-dev2dev
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Comments on SRFI proposal (sweet-expressions) [Honu]

2013-03-04 Thread Alan Manuel Gloria
Okay, so I read the Honu paper more and more.

Honu *does* have a separate reader and macro-expander.

However, Honu's approach means that what Honu does is effectively turn
code like this:

function foo(x, y) { x + y; }

to this s-expression:

(honu-block function foo (x |,| y) ((x + y)) )

I'm *not* sure that the Honu reader actually does that - the Honu
reader probably emits just (function foo ) and the Honu language
(using Racket's language system) tacks on the honu-block before it.

The honu-block macro is a Scheme-level (actually, Racket-level, since
RnRS macros are just syntax-rules) macro.

Honu-level macros are *different* from Racket macros and are handled
differently (by my understanding, using Racket's expansion-time
environment to somehow store them while honu-block processes things).

This works for Honu because of the Pratt parsing enforced by
honu-block, meaning that the (x + y) part will be seen by Honu-level
macros as something practically close to (+ x y).  Because of the
tacked-on honu-block keyword, honu-block has full control of what
Honu-level macros see.

Still, it seems that Honu significantly obscures the code-is-data part
of Lisp, because of the significant transformations that honu-block
performs on its input list.

1.  Honu is not very back-compatible with Lisp.  Our approach allows
valid parsing of "string->symbol", Honu seems likely to convert that
to three atoms, 'string '-> 'symbol.  Our approach also allows a large
amount of existing, typically-formatted Lisp code to be parsed
identically to existing 'read; Honu makes changes that prevent
existing Lisp code to be read in, in conjunction with Honu code (i.e.
you can't copy-paste existing Lisp code into a Honu language file; you
can copy-paste existing Lisp code into a sweet-expression file most of
the time)

2.  Actually, Honu *can* support quote.  It's just that the syntax of
lists in quote doesn't match the syntax in the rest of Honu.  In Honu
a list is [1,2,3].  But in a quote context it's (1 2 3) (I think).
I'm not sure what the term sequence "quote [1,2,3]" would expand to,
but I suspect it's something like (quote (honu-bracket 1 |,| 2 |.|
3)).  So, lose homoiconicity and generality just in this one stroke.

3.  Honu requires a macro-expansion pass to convert a + b to (+ a b).
Sweet-expressions does not require a macro-expansion pass to convert
{a + b} to (+ a b).  This may not seem significant, unless you're,
say, writing a 4X game where your unit descriptions may need small
amounts of interpreted code, and because this is a unit description
file and you don't want your users to suddenly e-mail /etc/passwd to
an undisclosed third party when all they wanted to do was try out a
neat new unit description file they got off the internet, you're not
interested in giving the full power of macros in the little bits of
code, but you *are* interested in allowing the unit description file
to say "define power(berserker) { power(scout) + 2 }" (i.e. Principle
of Least Power).

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Comments on SRFI proposal (sweet-expressions)

2013-03-04 Thread Alan Manuel Gloria
On Monday, March 4, 2013, David A. Wheeler  wrote:
> Alan Manuel Gloria:
>> Looking at the repo, it seems dwheeler has managed to make a short
>> summary of Honu.
>
> Yes.  It'll take some time to set up the mailing list, get people on it,
etc.  I want to get the process started quickly... to make sure you can be
part of it.
>
>> So, for now, I'd like to add a few short observations on Honu:
>>
>> 1.  It does not appear to have something like a "quote" syntax,
>> instead having list "constants" be expressed using more-mainstream
>> [...] syntax, which is actually nearer to (list x ...) than (quote (x
>> ...)). This means that instead of using symbols as labels for, say,
>> modes or states or enumerations (as would be second nature to a Lisp
>> programmer), Honu programmers are subtly encouraged to use global
>> variables bound to numbers (a technique more typical in mainstream
>> languages that cannot quote source-level identifiers).
>
> Is it possible that they just didn't document "quote"?
> I don't know for sure if the "This means..." is true.  If you could dig in
> and make sure of that, that'd be awesome.  If that is true, the loss
> of "quote" is in my mind a devastating weakness.

It's *possible* but as I understand it, pratt parsing's basemost parser
emits a flat list of tokens, and the actual parser takes that flat list and
in Honu calls into the macro code of detected defined keywords. The
low-level macro example suggests that, and shows the recursion to the pratt
parser expression parser entry point.

This could mean that a defined quote macro could be implemented which
recurses into the expression parser, which recurses into the macro
dispatch. So an innocent "quote foo" could mean something different if foo
is defined as a macro.

A quote syntax form could return a single token after it, maybe. But this
is not as powerful as the Lisp quote.

I'm not certain what happens if a macro expands to itself. In particular
this suggests a possibly bad interaction with the parser for "syntax"
keyword.

>
>> 2.  I think it might be better to clarify the discussion into saying
>> that Honu does not implicitly separate reading from macro-expansion.
>> Instead, in Honu macro-expansion appears to be an inherent part of the
>> parsing process, largely due to the Pratt parser technique that
>> appears to be the basis of Honu's parser.
>
> Okay.
>
>> (I'm posting this here since I don't have access to my hacking
>> computer right now, and I'll just do this later unless dwheeler gets
>> impatient or bored and does it anyway).
>
> Please edit away!
>
> I've made a few edits after I submitted the draft anyway.
>
> --- David A. Wheeler
>
>
>
--
> Everyone hates slow websites. So do we.
> Make your web apps faster with AppDynamics
> Download AppDynamics Lite for free today:
> http://p.sf.net/sfu/appdyn_d2d_feb
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>
--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Comments on SRFI proposal (sweet-expressions)

2013-03-03 Thread Alan Manuel Gloria
On 3/4/13, David A. Wheeler  wrote:
> I just got an email from Michael Sperber (a SRFI editor).
>
> Overall he thought it was a "nice job" for an initial submission,
> with two comments:
> 1. We should  probably reference Honu:
>   http://www.cs.utah.edu/plt/publications/gpce12-rf.pdf
> 2. We should also provide the ANTLR file as an external file
>in addition to being in-line.
>
> #2 is trivial to do.
>
> #1 will require a little work, but not too bad.

Looking at the repo, it seems dwheeler has managed to make a short
summary of Honu.

So, for now, I'd like to add a few short observations on Honu:

1.  It does not appear to have something like a "quote" syntax,
instead having list "constants" be expressed using more-mainstream
[...] syntax, which is actually nearer to (list x ...) than (quote (x
...)). This means that instead of using symbols as labels for, say,
modes or states or enumerations (as would be second nature to a Lisp
programmer), Honu programmers are subtly encouraged to use global
variables bound to numbers (a technique more typical in mainstream
languages that cannot quote source-level identifiers).

2.  I think it might be better to clarify the discussion into saying
that Honu does not implicitly separate reading from macro-expansion.
Instead, in Honu macro-expansion appears to be an inherent part of the
parsing process, largely due to the Pratt parser technique that
appears to be the basis of Honu's parser.

Other than that, it seems to be a good-enough discussion of Honu.

(I'm posting this here since I don't have access to my hacking
computer right now, and I'll just do this later unless dwheeler gets
impatient or bored and does it anyway).

>
> Once we do that, he thinks he can get the SRFI process
> started very quickly.
>
> --- David A. Wheeler
>
> --
> Everyone hates slow websites. So do we.
> Make your web apps faster with AppDynamics
> Download AppDynamics Lite for free today:
> http://p.sf.net/sfu/appdyn_d2d_feb
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Should #!curly-infix stop #!sweet?

2013-03-01 Thread Alan Manuel Gloria
On 3/2/13, David A. Wheeler  wrote:
> Should #!curly-infix stop #!sweet?
>
> Originally it did.  I implemented "#!curly-infix" and found that our
> enable-curly-infix didn't disable, so #!curly-infix didn't, and so I changed
> the SRFI to match.  Now I'm not sure I did the right thing.
>
> You could argue that #!curly-infix should NOT stop #!sweet, since #!sweet
> embeds curly-infix, and this means that #!curly-infix is "safe" to
> arbitrarily add.

SRFI-sweet says that implementations MAY have sweet-expressions
enabled by default.  That actually argues for having a #!no-sweet, and
having #!curly-infix disable sweet expressions but retaining
curly-infix.

Dunno.  Either seems workable to me.

>
> You could argue that #!curly-infix SHOULD stop #!sweet, so that you can
> switch modes.
>
> Thoughts?
>
>  --- David A. Wheeler
>
> --
> Everyone hates slow websites. So do we.
> Make your web apps faster with AppDynamics
> Download AppDynamics Lite for free today:
> http://p.sf.net/sfu/appdyn_d2d_feb
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Cleaning up src/kernel.scm - any problems doing so?

2013-03-01 Thread Alan Manuel Gloria
This sentence:

"Some people require a second explanation of the simpler version of
sublist (“$”), even though “$” is currently very simple."

Could probably be better expressed as:

"Some people require a second explanation of SUBLIST, which is
essentially the explanation of the *current* version of SUBLIST
described in this SRFI."

--

The sentence:

"Adding this capability to “$” makes it much more complicated to describe."

seems redundant, since we already said:

"It complicates explanation of “$”"

earlier.

On 3/2/13, Alan Manuel Gloria  wrote:
> On 3/1/13, David A. Wheeler  wrote:
>> Alan Manuel Gloria:
>>
>>> Err I already wrote a draft section on Beni's proposal and pushed it
>>> *very* early this morning.
>>
>> Got it.  I took our versions and tried to merge them together.
>>
>> Please do take a look and fix any problems you see.
>>
>
> Seems okay, although:
>
> "There’s already a body of material on how to handle indentation-based
> languages, which tend to follow Python approaches and specifically do
> NOT differentiate between “indent 3 spaces” and “indent 1 space”, just
> INDENT."
>
> ...seems to come out of left field, given that the formal description
> above it mentions just "INDENT" and "DEDENT".  It may be better to
> reword it to something nearer to:
>
> "...which tend to follow Python or Haskell approaches and specifically
> consider the actual source stream to have matching indentations and
> dedentations"
>
> ...or, er, something clearer, anyway.  Erk.
>
> --
>
> Otherwise seems fine, we need more links to archive mailinglist messages.
>
> Sincerely,
> AmkG
>

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Cleaning up src/kernel.scm - any problems doing so?

2013-03-01 Thread Alan Manuel Gloria
On 3/1/13, David A. Wheeler  wrote:
> Alan Manuel Gloria:
>
>> Err I already wrote a draft section on Beni's proposal and pushed it
>> *very* early this morning.
>
> Got it.  I took our versions and tried to merge them together.
>
> Please do take a look and fix any problems you see.
>

Seems okay, although:

"There’s already a body of material on how to handle indentation-based
languages, which tend to follow Python approaches and specifically do
NOT differentiate between “indent 3 spaces” and “indent 1 space”, just
INDENT."

...seems to come out of left field, given that the formal description
above it mentions just "INDENT" and "DEDENT".  It may be better to
reword it to something nearer to:

"...which tend to follow Python or Haskell approaches and specifically
consider the actual source stream to have matching indentations and
dedentations"

...or, er, something clearer, anyway.  Erk.

--

Otherwise seems fine, we need more links to archive mailinglist messages.

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Cleaning up src/kernel.scm - any problems doing so?

2013-03-01 Thread Alan Manuel Gloria
On 3/1/13, David A. Wheeler  wrote:
> Cleanup hasn't been so bad.  I've tried to merge Alan Manuel Gloria and my
> text about the SUBLIST-dedent proposal into a coherent whole, and made some
> other cleanups.  I also cleaned up the src/kernel.scm code some.
>
> So... how about submitting a first draft to the SRFI editors by March 2?
> That means that they give us feedback March 9 or so, and soon afterwards
> create a mailing list.
>
> That will give us 2.5 weeks before we-don't-know-what-happens, and that
> looks like the fastest we can manage.
>
> Sound okay?

Sounds OK to me.

>
> --- David A. Wheeler
>
> --
> Everyone hates slow websites. So do we.
> Make your web apps faster with AppDynamics
> Download AppDynamics Lite for free today:
> http://p.sf.net/sfu/appdyn_d2d_feb
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Cleaning up src/kernel.scm - any problems doing so?

2013-03-01 Thread Alan Manuel Gloria
On Fri, Mar 1, 2013 at 1:21 AM, David A. Wheeler  wrote:
> I said:
>> > I think we should be ready to go by the Ides of March (March 15)...
>
> Alan Manuel Gloria:
>> Sounds fine, although that means I will be in Japan for much of the
>> SRFI discussion run (will be going early April to end of May).  I'll
>> be busier in the office but have (maybe) a bit more spare time, so
>> it's a definite maybe on whether I can participate more, or
>> participate less, during that time (^^)
>
> I think it's *vital* that you be able to participate, *especially*
> early on when we're more likely to get fundamental questions
> or radical new ideas that need sorting.
>
> Would it be better if we submit the draft SRFI circa March 8?
> I think we could do that.

Sounds fine if we can do that, sure.

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Cleaning up src/kernel.scm - any problems doing so?

2013-02-28 Thread Alan Manuel Gloria
Err I already wrote a draft section on Beni's proposal and pushed it
*very* early this morning.

Unless I was too sleepy to actually push it.  LOL.

On 3/1/13, David A. Wheeler  wrote:
> Unfortunately, it'll take time to get the new SRFI started; I forgot about
> that.  And I think it's vitally important to ensure that Alan is available
> those first weeks.
>
> New plan: Let's get a draft ready in a few days, and submit it.  We can work
> in parallel to refine it while they review it.  I'll write a draft section
> on Beni's proposal, and tweak the examples at least.
>
> --- David A. Wheeler
>
> --
> Everyone hates slow websites. So do we.
> Make your web apps faster with AppDynamics
> Download AppDynamics Lite for free today:
> http://p.sf.net/sfu/appdyn_d2d_feb
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


[Readable-discuss] End-of-line sequence

2013-02-28 Thread Alan Manuel Gloria
I saw a few recent changes on the repo regarding EOL.

It seems the latest spec simplifies EOL to:

LF | CR LF

...which is acceptable in the common case, I suppose, but I went and
searched for formal Unicode specs regarding end-of-line, and got:

http://www.unicode.org/standard/reports/tr13/tr13-5.html

Main points:

1.  NLF (new line function) is LF | CR | CR LF | NEL

2.  Treat any kind of NLF the same.

3.  "A readline function should stop at NLF, LS, FF, or PS"

Should we adhere to the Unicode specs more closely, even at the cost
of a more annoying Guile behavior?

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Cleaning up src/kernel.scm - any problems doing so?

2013-02-27 Thread Alan Manuel Gloria
On 2/28/13, David A. Wheeler  wrote:
> Alan Manuel Gloria:
>> Do we have a target day for SRFI submission?
>
> "When it's ready" :-).
>
> I think we should be ready to go by the Ides of March (March 15).  Does that
> sound plausible?  The code needs some cleanup, as does the SRFI text, but I
> think that should be enough time to give them some polish.  In particular, I
> want the SRFI text to be clear so people will comment on the content, and
> not "I don't understand what you mean".

Sounds fine, although that means I will be in Japan for much of the
SRFI discussion run (will be going early April to end of May).  I'll
be busier in the office but have (maybe) a bit more spare time, so
it's a definite maybe on whether I can participate more, or
participate less, during that time (^^)

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Cleaning up src/kernel.scm - any problems doing so?

2013-02-26 Thread Alan Manuel Gloria
On 2/27/13, David A. Wheeler  wrote:
> We need to clean up src/kernel.scm so we can use it in the draft SRFI
> as the sample implementation.  So...
>
> I intend to start removing the old implementation and the partial
> "AmkG New implementation", so that there's just one simple implementation
> in src/kernel.scm. People can always retrieve old versions via git, and
> there's
> absolutely nothing wrong with having other implementations, but I'd like for
> there
> to be one (relatively) simple implementation that clearly and directly maps
> to the BNF for use in the SRFI.
>
> There was a known defect in the "new" implementation, but I've since fixed
> it, and
> the new implementation succeeds on a fairly large test suite.
>
> Alan Manuel Gloria: You'll be happy to know that I've tweaked the new
> implementation
> so that an EOF without a preceding EOL tends to be handled as if there was a
> preceding EOL.
>
> Comments? Concerns?
>

None, go ahead.

Do we have a target day for SRFI submission?

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Proposal: allow closing SUBLIST by dedenting

2013-02-24 Thread Alan Manuel Gloria
On 2/25/13, David A. Wheeler  wrote:
> Alan Manuel Gloria:
>
>> Awww. (^.^)v
>
> :-).
>
>> Since you're unwilling to put the full Beni formulation in *right
>> now*, then let's use classic formulation. I hope somebody else speaks
>> up for the full Beni formulation and gives a fully interesting example
>> *real soon now* (^_^)
>
> Absolutely!  Thanks for being willing to do this.
> This particular formulation is definitely interesting, I think
> documenting it is important.
>
> And please make it clear that this is an upward-compatible
> extension that could be added later, without interfering with any
> existing sweet-expressions.
>
>> I volunteer to write up the Beni formulation for the SRFI-sweet
>> document - unless Beni wants to write it up himself.
>
> That'd be great.  Please feel free to document my "$-at-end"
> attempt at a compromise.  If you don't want to do that, I'll add it.
>

Yeah, although I'll wait a few days to see if Beni wants to write it
himself first.

>
>> Note that:
>>
>> $
>>   foo
>>
>> ==>
>>
>> ((foo))
>>
>> which is both non-obvious and not something I see as *useful*.  So
>> raising an error is fine with me too.
>
> Okay. John Cowan made the same point too.
> Looks like we'll drop that, at least for this edition.
>
> Once it's removed from the BNF, I think we need to make sure that the
> Scheme specifically checks for it and forbids it.  That way, people won't
> accidentally use such constructs for now, and that'll make it easier to
> add later if indeed it's added later.

I propose making it an explicit error in the BNF rather than just
making it an invalid sequence by implication of its absence.

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] SRFI-sweet draft for submission?

2013-02-24 Thread Alan Manuel Gloria
On 2/25/13, Alan Manuel Gloria  wrote:
> Also, I think I saw some other finalized SRFI's where the
> implementation is a separate file (also hosted on srfi.schemers.org);

SRFI-19 is one:

http://srfi.schemers.org/srfi-19/srfi-19.html
http://srfi.schemers.org/srfi-19/srfi-19.scm

SRFI-25 has a bunch of attached implementation files:

http://srfi.schemers.org/srfi-25/srfi-25.html
http://srfi.schemers.org/srfi-25/srfi-25-reference.scm
http://srfi.schemers.org/srfi-25/array.scm
http://srfi.schemers.org/srfi-25/opt.scm
http://srfi.schemers.org/srfi-25/as-procedure.scm
http://srfi.schemers.org/srfi-25/as-srfi-9-record.scm
http://srfi.schemers.org/srfi-25/as-plt-struct.scm

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


[Readable-discuss] SRFI-sweet draft for submission?

2013-02-24 Thread Alan Manuel Gloria
Okay, so here are a few more things we need to do for the SRFI-sweet draft:

1.  Arne's formulation discussion.  I've written up and committed this
already; anybody want to add something?
2.  Beni's extended SUBLIST discussion.
3.  Create links to mailing list discussions related to Design
Rationale sub-sections.

Anything else we need to do?  I know I saw a few commits a couple
weeks ago where David A. Wheeler synchronized the SRFI-sweet
implementation to the sweet.g ANTLR code, so I assume they're
currently still in synch modulo the current SUBLIST discussion.

Also, I think I saw some other finalized SRFI's where the
implementation is a separate file (also hosted on srfi.schemers.org);
I assume this is also acceptable up to now.  I think it's better to
attach our latest src/kernel.scm file as a separate file rather than
embedding it into the SRFI document; the discussions and arguments for
various details are substantially long already, and the
implementation, I think, would be more easily browsed as a separately
viewable file.

For that matter, I propose adding a linked table-of-contents, down to
the level of each subsection in our lengthy Design Rationale section.
It's easy to get lost there I think.

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Proposal: allow closing SUBLIST by dedenting

2013-02-24 Thread Alan Manuel Gloria
On 2/25/13, David A. Wheeler  wrote:
> Beni Cherniavsky-Paskin:
>> Here is yet another idea for opening multiple levels on one line, that
>> does
>> NOT involve column counting, only comparison of leading whitespaces.
>>
>> It's a backward-compatible extension to SUBLIST (similarly applicable to
>> any competing FOOLIST semantics), so we could leave it undecided for now,
>> and legalize it later.
>>
>> $ lets one open an inner list on one line, but currently it's only usable
>> when this list is the last element of the containing list:
>>
>> outer1 outer2 $ inner1
>> ! inner2
>>
>> You cannot express (outer1 outer2 (inner1 inner2) outer3)
>> without giving up on use of $.
>>
>> The proposal is to allow an unmatched dedent after inner2, and have that
>> return you to the outer level:
> ...
>
>
> Note: I earlier replied with a variant idea with subject
> "$ at end of line bug?", but Alan Manuel Gloria
> noted, "shouldn't we be discussing this on
> Beni's proposal thread?" so I'll continue on THIS thread instead.
> Sorry for the confusion...
>
>
> As noted earlier, this is an interesting proposal, but
> I have a variety of concerns with it.
>
>
> Alan Manuel Gloria:
>> I think that, conceptually, having a limitation is an additional
>> complication when teaching the notation.
> ...
>> I'd rather have the full Beni formulation of SUBLIST or the classic
>> 0.4 formulation, in that preference order.
>
> Okay.
>
> If that's so, and no one else speaks up, perhaps we should
> just continue to use the classic formulation.  I'm fine with that;
> we know that works well, and I think it's well-specified.

Awww. (^.^)v

Since you're unwilling to put the full Beni formulation in *right
now*, then let's use classic formulation. I hope somebody else speaks
up for the full Beni formulation and gives a fully interesting example
*real soon now* (^_^)

>
> We could ensure that nothing we do now *forbids* later
> extending it this way, and document this as a potential future extension.
> That would keep our options open.  Sound reasonable?
> Per the email quote above, Beni Cherniavsky-Paskin was fine with
> not specifying at this time as long as we didn't close the door to it,
> and this would be consistent with it.

I volunteer to write up the Beni formulation for the SRFI-sweet
document - unless Beni wants to write it up himself.

>
> Should we allow "$" at the end without partial dedents (creating an extra
> ()),
> or should we just drop that too?

I don't see a use for it, but I see no harm in specifying it that way.

Note that:

$
  foo

==>

((foo))

which is both non-obvious and not something I see as *useful*.  So
raising an error is fine with me too.

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] $ at end of line bug?

2013-02-23 Thread Alan Manuel Gloria
BTW the subject is misleading, shouldn't we be discussing this on
Beni's proposal thread?

On Sun, Feb 24, 2013 at 4:55 AM, Alan Manuel Gloria  wrote:
> On Sun, Feb 24, 2013 at 12:17 AM, David A. Wheeler
>  wrote:
>> As I posted earlier, I'm *really* uncomfortable with losing the ability to 
>> auto-check the grammar.  But I do understand the notion that extending 
>> SUBLIST, especially to handle "let" and similar constructs, could be useful.
>>
>> Beni Cherniavsky-Paskin:
>>>[I'm asking this because if it's 'fixed, my
>>>closing-SUBLIST-by-unmatched-dedent would allow:
>>>let $
>>>! ! x $ compute 'x
>>>! ! y $ compute 'y
>>>! body...
>>
>> I have a counter-proposal, maybe I can call it "Beni-Lite" :-) ???   And I 
>> even have a sample implementation that we can try out.
>>
>> I've just posted to the "devel" branch a change to the ANTLR implementation 
>> that permits closing SUBLIST by an unmatched DEDENT, but *only* if the "$" 
>> is the last item on a line (and there's something before "$" other than 
>> indent chars).  This limited semantic ("Beni-lite"?) covers the primary use 
>> cases I've seen, *AND* I've found a way to formulate it so that we can 
>> continue to use ANTLR's grammar checking and run-time input checking.
>>
>> To do this, I've tweaked the indent processor.  After you dedent, if the 
>> dedent doesn't match the parent indent, it then generates a RE_INDENT. This 
>> retains a whole lot of error-checking, both of the BNF and of the input 
>> during processing.  This means that:
>> let $
>> ! ! var1 value1
>> ! body...
>>
>> becomes:
>> let SUBLIST EOL
>> INDENT var1 value2 EOL
>> DEDENT RE_INDENT body...
>>
>>
>>
>> It includes a few test cases, which show how it works:
>>
>> let $
>> ! ! var1 value1
>> ! body...
>> ; ==> (let ((var1 value1)) body...)
>>
>> let $
>> ! ! var1 value1
>> ! ! var2 value2
>> ! body...
>> ; ==> (let ((var1 value1) (var2 value2)) body...)
>>
>> let $
>> ! ! var1 value1
>> ! ! var2 value2
>> ! ! var3 value3
>> ! body1 param1
>> ! body2 param2
>> ; ==>
>> ; (let ((var1 value1) (var2 value2) (var3 value3))
>> ;(body1 param1) (body2 param2))
>>
>>
>>
>> Even this backed-off version is complicated, but it's not MUCH more 
>> complicated, and it does retain all the error-checking that I'm very loathe 
>> to drop.  It only works when "$" is at the end of the line... but that seems 
>> like a reasonable limitation.
>>
>> Comments?
>>
>> I *especially* want to hear from Beni Cherniavsky-Paskin and Alan Manuel 
>> Gloria, since both have expressed an interest in this kind of capability, 
>> but I certainly want to hear from all.  I want to make this final notation a 
>> good balance between "simple" and "capable"... I worry that even this subset 
>> may be a step too far.
>>
>
> I think that, conceptually, having a limitation is an additional
> complication when teaching the notation.
>
> When explaining the Beni formulation we can say "A $ indicates a
> further indent, with the promise that either you will have a
> 'staggered dedent' like FIGURE X, or that you will close the sublist
> with a dedent to a 'real' indentation level on this line or a parent
> line of this line."
>
> Granted we could just mandate these patterns, but I worry that we are
> now slipping into the "notation is tied to underlying semantic" bug.
> Or in this case, "notation is tied to underlying legacy syntax".
>
> I'd rather have the full Beni formulation of SUBLIST or the classic
> 0.4 formulation, in that preference order.
>
> I'll admit that I don't have a use for the full Beni formulation other
> than for let, though.  I suspect there may be further use cases; but I
> haven't found any others yet.
>
> --
>
> Beni-full formulation, informally:
>
> The SUBLIST or "$" marker indicates that the text following it on that
> line will be indented by one more "virtual" indentation level than the
> current line.  The direct child lines of this line will then be
> considered child lines of only the text after the last SUBLIST marker,
> and the text after the SUBLIST marker will be considered a child of
> the

Re: [Readable-discuss] $ at end of line bug?

2013-02-23 Thread Alan Manuel Gloria
On Sun, Feb 24, 2013 at 12:17 AM, David A. Wheeler
 wrote:
> As I posted earlier, I'm *really* uncomfortable with losing the ability to 
> auto-check the grammar.  But I do understand the notion that extending 
> SUBLIST, especially to handle "let" and similar constructs, could be useful.
>
> Beni Cherniavsky-Paskin:
>>[I'm asking this because if it's 'fixed, my
>>closing-SUBLIST-by-unmatched-dedent would allow:
>>let $
>>! ! x $ compute 'x
>>! ! y $ compute 'y
>>! body...
>
> I have a counter-proposal, maybe I can call it "Beni-Lite" :-) ???   And I 
> even have a sample implementation that we can try out.
>
> I've just posted to the "devel" branch a change to the ANTLR implementation 
> that permits closing SUBLIST by an unmatched DEDENT, but *only* if the "$" is 
> the last item on a line (and there's something before "$" other than indent 
> chars).  This limited semantic ("Beni-lite"?) covers the primary use cases 
> I've seen, *AND* I've found a way to formulate it so that we can continue to 
> use ANTLR's grammar checking and run-time input checking.
>
> To do this, I've tweaked the indent processor.  After you dedent, if the 
> dedent doesn't match the parent indent, it then generates a RE_INDENT. This 
> retains a whole lot of error-checking, both of the BNF and of the input 
> during processing.  This means that:
> let $
> ! ! var1 value1
> ! body...
>
> becomes:
> let SUBLIST EOL
> INDENT var1 value2 EOL
> DEDENT RE_INDENT body...
>
>
>
> It includes a few test cases, which show how it works:
>
> let $
> ! ! var1 value1
> ! body...
> ; ==> (let ((var1 value1)) body...)
>
> let $
> ! ! var1 value1
> ! ! var2 value2
> ! body...
> ; ==> (let ((var1 value1) (var2 value2)) body...)
>
> let $
> ! ! var1 value1
> ! ! var2 value2
> ! ! var3 value3
> ! body1 param1
> ! body2 param2
> ; ==>
> ; (let ((var1 value1) (var2 value2) (var3 value3))
> ;(body1 param1) (body2 param2))
>
>
>
> Even this backed-off version is complicated, but it's not MUCH more 
> complicated, and it does retain all the error-checking that I'm very loathe 
> to drop.  It only works when "$" is at the end of the line... but that seems 
> like a reasonable limitation.
>
> Comments?
>
> I *especially* want to hear from Beni Cherniavsky-Paskin and Alan Manuel 
> Gloria, since both have expressed an interest in this kind of capability, but 
> I certainly want to hear from all.  I want to make this final notation a good 
> balance between "simple" and "capable"... I worry that even this subset may 
> be a step too far.
>

I think that, conceptually, having a limitation is an additional
complication when teaching the notation.

When explaining the Beni formulation we can say "A $ indicates a
further indent, with the promise that either you will have a
'staggered dedent' like FIGURE X, or that you will close the sublist
with a dedent to a 'real' indentation level on this line or a parent
line of this line."

Granted we could just mandate these patterns, but I worry that we are
now slipping into the "notation is tied to underlying semantic" bug.
Or in this case, "notation is tied to underlying legacy syntax".

I'd rather have the full Beni formulation of SUBLIST or the classic
0.4 formulation, in that preference order.

I'll admit that I don't have a use for the full Beni formulation other
than for let, though.  I suspect there may be further use cases; but I
haven't found any others yet.

--

Beni-full formulation, informally:

The SUBLIST or "$" marker indicates that the text following it on that
line will be indented by one more "virtual" indentation level than the
current line.  The direct child lines of this line will then be
considered child lines of only the text after the last SUBLIST marker,
and the text after the SUBLIST marker will be considered a child of
the text before the SUBLIST marker.  You can also chain SUBLIST
markers, like so:

probe $ call/cc $ lambda (exit)
! exit 42
==>
probe
! call/cc
! ! lambda (exit)
! ! ! exit 42

In addition, the SUBLIST marker allows a "staggered dedent", like so:

foo $ a b
! ! c
! d

In this case, the "a b" text has as its child the directly succeeding
child line of its line, while the line with "staggered" dedent will be
the next sibling of the "a b" text.  So the above is equivalent to:

foo
! a b
! ! c
! d

In general, the "staggered dedent" capability of SUBLIST is not used;
you are more likely to just close it directly:

foo $ a b
! c
d
===>
foo
! a b
! ! c
d

However, the staggered dedent is useful for LET:

let $
! ! var
! !   value
! ! var2
! !   value2
! body
! ...

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] $ at end of line bug?

2013-02-22 Thread Alan Manuel Gloria
On Fri, Feb 22, 2013 at 7:51 AM, David A. Wheeler  wrote:
> Alan Manuel Gloria:
>> I think a different approach is better.
>
> Definitely a possibility; I'm still trying to figure out if it's possible to 
> do this in a simpler/cleaner way.
>
> BTW, I'm realizing that this creates yet another potential problem: Disabled 
> error-checking.
> With this, a line with indentation that doesn't match its parents might be 
> okay (!).
> We may be able to quickly detect that and deal with it; I'd like to make sure 
> we
> can still quickly detect bad indents.
>
>
>>  The problem is that DEDENT_PARTIAL cannot give information about
>> *how many* ? exist on the indent stack.
>
> But how much of that information do we really need?
>
>
>> Instead, I think this calls for a more complicated indentation preprocessor:
>
> (pft)... That's the sound of my head exploding :-).
>
> I've read that several times and I don't think I fully understand it.
> I understand each line separately, but not why you believe they
> work properly together.  I'm imagining trying to create a math proof that
> this algorithm is correct... and failing completely.

Well, so far the only property I can prove is that the number of
INDENT's emitted is equal to the the number of DEDENT's emitted.  This
is due to the fact that every event that pushes an entry on the stack
also emits exactly one INDENT, and any event that pops an entry off
the stack also emits a DEDENT; the only exception is the part where
the top ? item is replaced, and that does not emit either an INDENT or
DEDENT, while stack height is preserved.  Thus each stack entry
represents a pending INDENT that is not yet matched by a DEDENT.  As
long as we empty the stack at EOF, then every INDENT gets paired at
some point with DEDENT.

As for SUBLIST working properly, what exactly about SUBLIST should we prove?

What needs to get proven in an indentation processor?

Basically, this indentation processor is just a more formal expression
of what Beni said in his initial email about DEDENT and SUBLIST.

>
> Also, I can't begin to imagine *explaining* that algorithm to someone.
> While the BNF has many lines, many people have had lots of training in
> BNFs and can pick them up quickly.  Indentation processing like this... not 
> so much.
>
> Granted, you could argue that's a limitation on MY end, and that's probably
> true enough.  But if I have trouble understanding it, I doubt I'm the only 
> one.
>
>
>> Basically, the formulation would remove all mention of GROUP_SPLIT and
>> SUBLIST (and all branches where they occur) but complicate the
>> indentation preprocessor.
>
> That's a significant part of the definition of these expressions,
> rendering them basically invisible to automated checking and analysis.
> I want this notation to work "because it's clearly correct"; using ANTLR
> to check it rigorously is a valuable way to get there.  That's a dangerous 
> loss.

I agree.

>
> Is there a way to simplify this, perhaps by finding some half-way approach?
>
> I plan to do some experimenting with the ANTLR BNF, and see if there's a way
> to tweak what we have while keeping the automated analysis working.
> Suggestions welcome.
>
> --- David A. Wheeler

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] If back-compatibility was not an issue...

2013-02-21 Thread Alan Manuel Gloria
I just want to warn that this is entirely non-serious, except it is.
If you didn't have to worry about back-compat, what would you do?

On 2/21/13, Alan Manuel Gloria  wrote:
> If back compatibility with Lisp in general was not an issue, what I
> thought I'd do was, I'd be like this:
>
> 1.  Disallow typical infix characters in typical identifiers.
> Instead, symbols are either entirely composed of infix characters or
> entirely composed of [A-Za-z_0-9].
> 1.1.  This means autodetect infix.  Down with convoke, use *<=>* instead!!
> (^.^)
> 1.2.  Since "..." is such a useful symbol in pattern-based syntax
> transformers, symbols composed entirely of "." are honorary non-infix
> symbols.  LOL.  (^.^)v
>
> 2.  Disallow improper lists
> - come on!  Improper lists mean that lists must always be implemented
> using the very specific singly-linked list data structure.
> - by disallowing improper lists, you allow any sequence structure to
> be used to implement lists: doubly-linked lists, arrays, concatenation
> trees, finger trees
>
> 3.  Autodetect infix, and have multiple non-infix-symbol datums in a
> list around an infix symbol put into lists automatically: "foo a + b"
> ==> "((+) (foo a) b)"
> 3.1.  Escape infixing by surrounding with ().  So you can express (map
> (-) ns) to specify the need to negate each element of a list of
> numbers rather than subtract a list of numbers from a procedure.  Or
> if you dislike () for that, then use {} instead.  You can always just
> use ((+)) if you really want a single-item list containing an infix
> symbol.  Or specify that the "real name" of an infix symbol includes
> {}, and the non-existence of those characters means "use infix
> meaning"
> 3.2.  Precedence???  We don't need no stinkin' precedence!  Use
> explicit parentheses if you're mixing infix operators!!
> 3.3.  A way of turning non-infix-symbols into temporarily-infix
> symbols (so that data gets rearranged) would also be nice.
>
> 4.  THERE WILL BE SUBLIST
> 4.1.  And SUBLIST shall work inside explicit parentheses: "(foo $ a
> b)" ==> (foo (a b))
>
> 5.  Use ";" for GROUP/SUBLIST.
> - real programmers don't comment1oneoneoneleveneleveneleven
> - use a different marker for comments.
>
> 6.  Fix let.  This will require 10+ more years of research, during
> which time David A. Wheeler will then prove that compiling a hardware
> synthesis tool on THREE different open-source compilers will somehow
> prevent all hardware backdoor attacks.
>
> 7.  I forgot to mention: mandatory indentation.
>

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


[Readable-discuss] If back-compatibility was not an issue...

2013-02-21 Thread Alan Manuel Gloria
If back compatibility with Lisp in general was not an issue, what I
thought I'd do was, I'd be like this:

1.  Disallow typical infix characters in typical identifiers.
Instead, symbols are either entirely composed of infix characters or
entirely composed of [A-Za-z_0-9].
1.1.  This means autodetect infix.  Down with convoke, use *<=>* instead!! (^.^)
1.2.  Since "..." is such a useful symbol in pattern-based syntax
transformers, symbols composed entirely of "." are honorary non-infix
symbols.  LOL.  (^.^)v

2.  Disallow improper lists
- come on!  Improper lists mean that lists must always be implemented
using the very specific singly-linked list data structure.
- by disallowing improper lists, you allow any sequence structure to
be used to implement lists: doubly-linked lists, arrays, concatenation
trees, finger trees

3.  Autodetect infix, and have multiple non-infix-symbol datums in a
list around an infix symbol put into lists automatically: "foo a + b"
==> "((+) (foo a) b)"
3.1.  Escape infixing by surrounding with ().  So you can express (map
(-) ns) to specify the need to negate each element of a list of
numbers rather than subtract a list of numbers from a procedure.  Or
if you dislike () for that, then use {} instead.  You can always just
use ((+)) if you really want a single-item list containing an infix
symbol.  Or specify that the "real name" of an infix symbol includes
{}, and the non-existence of those characters means "use infix
meaning"
3.2.  Precedence???  We don't need no stinkin' precedence!  Use
explicit parentheses if you're mixing infix operators!!
3.3.  A way of turning non-infix-symbols into temporarily-infix
symbols (so that data gets rearranged) would also be nice.

4.  THERE WILL BE SUBLIST
4.1.  And SUBLIST shall work inside explicit parentheses: "(foo $ a
b)" ==> (foo (a b))

5.  Use ";" for GROUP/SUBLIST.
- real programmers don't comment1oneoneoneleveneleveneleven
- use a different marker for comments.

6.  Fix let.  This will require 10+ more years of research, during
which time David A. Wheeler will then prove that compiling a hardware
synthesis tool on THREE different open-source compilers will somehow
prevent all hardware backdoor attacks.

7.  I forgot to mention: mandatory indentation.

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] $ at end of line bug?

2013-02-21 Thread Alan Manuel Gloria
On 2/21/13, David A. Wheeler  wrote:
> I said:
>> > I have a *lot* of concerns with that particular construct.
>
> Alan Manuel Gloria:
>> Why?  Compare:
> 
>
> It's not "must never happen", but I have a lot of concerns.  Here are ones
> that come to mind:
>
> 1. It really complicates explanation and implementation of "$".  Some people
> require a second explanation now, and "$" is really simple. Adding this
> capability to "$" makes it much more complicated to describe.  Every time we
> add a complication, we risk losing some potential users and implementers.

Fair point.  "$" in current semantics is already difficult to explain as-is.

>
> 2. I'm not sure that there's enough *value* to adding it.  There *ARE* use
> cases, and these use cases are definitely common enough to discuss doing
> something special with them.  But I worry that the contravening downsides
> will overwhelm it.  Currently, in certain cases we have to add "\\"-only
> lines; that's not really a hardship, especially since the resulting
> constructs are pretty easy to understand.

OK

>
> 3. It can be viewed as complicating the reading of code that uses it.  Up to
> this point, a dedent always ended the whole line above; now it can end it a
> part.  Perhaps the reduction in line count is fair compensation; that's not
> clear to me.
>

I suppose the main reason is "it's too easy to abuse".  Beni's
formulation has a single use case so far, the aforementioned let, but
excess misuse of the Beni SUBLIST can make users suspicious of using
it.

> 4. There's already a body of material on how to handle indentation-based
> languages, which tend to follow Python approaches and specifically do NOT
> differentiate between "indent 3 spaces" and "indent 1 space", just INDENT.
> We leave better-understood parsing theory if we do this.  I want to have it
> easily implemented, with many reasons to be *confident* it is
> well-designed... the more we leave established theory, the harder it is to
> do that.

Well, my formulation of Beni's formulation removes SUBLIST and SPLIT
(\\-inline) handling from the hands of the indentation parser and puts
it into the hands of the indentation preprocessor.  It could even
remove GROUP (\\-at-start) handling from the indentation parser and
keep it in the preprocessor, as long as the indentation parser can
handle two INDENT's in sequence.

>
>
> Let me speak to the last point.  If we *did* go this way (and I'm dubious
> right now), we need to make sure that this construct is clearly and
> unambiguously defined as part of some well-checked BNF grammar.  Turning
> every space into an INDENT, and reduced space into a DEDENT, seems to make
> this much worse.   I don't know of anyone who handles indent/dedent
> processing this way; people normally tokenize indentation to make parsing
> easier.  I want to stick to better-understood ground where we can, so we
> avoid any surprise disasters.
>
> So if we went this way, I suspect it would be better to model this by adding
> a new indentation token, DEDENT_PARTIAL, in addition to DEDENT.  A DEDENT
> undents back to the previous parent level; a DEDENT_PARTIAL undents back to
> something consistent with the parent and the current indent, but is
> (strictly) between them.  The indent parser would have to change to generate
> a DEDENT_PARTIAL, and the BNF would have to change to support
> DEDENT_PARTIAL.  That way, we at least continue to tokenize indentation
> changes.  I don't know if the BNF change would be easy or hard; if it's
> hard, I'm *really* disinclined.

I think a different approach is better.  The problem is that
DEDENT_PARTIAL cannot give information about *how many* ? exist on the
indent stack.

Instead, I think this calls for a more complicated indentation preprocessor:

1.  If you encounter a SUBLIST, emit an INDENT (or EOL-INDENT since
that seems to be your preferred formulation) and push ? on the indent
stack.
2.  If you encounter a GROUP/SPLIT that is inline (SPLIT meaning):
2.1.  If there is at least one ? on the indent stack top, pop off all
? until you reach a non-? item; emit a DEDENT for each ? popped.
2.2.  Otherwise, emit SAME (or just EOL, since that is how the current
BNF works).
3.  If you encounter an EOL, slurp the indentation, then:
3.1.  If the topmost non-? stack item is less than the indentation,
push the indentation on the stack and emit INDENT.
3.2.  If the topmost non-? stack item is equal to the indentation:
; comment: 3.2.1 and 3.2.2 are copies of 2.1 and 2.2, respectively
3.2.1.  If there is at least one ? on the indent stack top, pop off
all ? until you reach a non-? item; emit a DEDENT for each ? popped.
3.2

Re: [Readable-discuss] unhappy with the current direction

2013-02-20 Thread Alan Manuel Gloria
Heya Arne,

We're saddened at your unhappiness with the current direction, and
glad that you have made a concrete effort at defining a suitable
alternative semantics for special indentation extensions.

Currently, however, the consensus seems to be "sweet-expressions will
not switch directions, in any way, to use Arne's formulation."  As
discussed in the other thread, Proposal: ENLIST (Arne's ":"),
http://www.mail-archive.com/readable-discuss@lists.sourceforge.net/msg01066.html
, there are some issues which lead us to turn down your two
interrelated proposals.

Personally, I feel that your combined proposal can be made to work in
a language that is restricted to operate in ASCII, or if you have an
underlying implementation that reliably uses the same encoding as the
programmer.  With effort, it can be made to work even with
double-width CJK characters and other Unicode nastiness.

However, our goal is to develop a general notation that can be
applicable across many Lisplike languages.  Lisp is easy to implement
- the original 'eval' definition was barely a page of text - and it's
easy to parse for programs.  Hence, the existence of many Lisps.
Adding an indentation processor is already a tremendous complication
in the parsing, but handling the full generality of Unicode would be
an even worse complication (unless you restrict the important parts of
the code, or even the entire code, to ASCII).

Granted, your approach can be implemented using some sort of
preprocessor separate from the core Lisp implementation; in fact, it
seems to be defined so that this is easy (hence the need to denote
single items with ".") and the preprocessor does not even need to
actually understand Lisp syntax (meaning that potentially, a single
preprocessor implementation can work with many Lisp implementations -
the Lisp implementations just need to implement n-expressions, or even
just curly-infix, both of which are far more trivial to add than
indentation).  This may be considered a point in its favor, although
it certainly risks falling into the One True Implementation.

We hope you continue to work with or on indentation-based syntaxes for
Lisp, whether sweet-expressions, your current proposal, or some other
future notation you can develop.

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] $ at end of line bug?

2013-02-19 Thread Alan Manuel Gloria
On 2/20/13, David A. Wheeler  wrote:
>> > [I'm asking this because if it's 'fixed, my
>> > closing-SUBLIST-by-unmatched-dedent would allow:
>> >
>> > let $
>> > ! ! x $ compute 'x
>> > ! ! y $ compute 'y
>> > ! body...
>> > ]
>
> I have a *lot* of concerns with that particular construct.
>


Why?  Compare:

let
! \\
! ! x $ compute 'x
! ! y $ compute 'y
! use x y

to:

let $
! ! x $ compute 'x
! ! y $ compute 'y
! use x y

Basically, Beni's formulation extends our "monotonically increasing
indentation = SUBLIST" theorem, by allowing any subsequence of
monotonically increasing indentation to be compressed using SUBLIST.
The above cannot be compressed further since the x line is followed by
a line on the same indent, and is thus no longer monotonically
increasing.

So:

foo
  bar
quux
  quuux
  yod
zod
  wod
<==>
foo $ bar
quux
  quuux
  yod $ zod $ wod

Since the indent of "bar" is where the indentation stops monotonically
increasing, that is the extent to which SUBLIST can be used to
compress the indentation (hence "foo $ bar").

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] $ at end of line bug?

2013-02-19 Thread Alan Manuel Gloria
On 2/20/13, David A. Wheeler  wrote:
> Beni Cherniavsky-Paskin:
>> > This behaves surprisingly:
>> >
>> > $
>> > ! a b
>> > ! c d
>> > ==>
>> > ((a b (c d)))
>> >
>> > it seems $ consumes the following newline, resulting in same parsing as
>> > if I
>> > wrote
>> >
>> > $ a b
>> >c d
>> >
>> > Is this deliberate?
>
> Alan Manuel Gloria
>> No (at least not by me; check David's answer, but I suspect he didn't
>> implement it deliberately that way).
>
> Alan's right, that's unintentional in the Scheme implementation.
>
> The BNF does not permit this construct at all, so the ANTLR implementation
> will give an error in this case.
>
> The relevant production is it_expr, which permits only:
>   | SUBLIST hspace* is_i=it_expr {$v=list($is_i.v);} /* "$" first on line
> */
> That is, "$", after any hspaces, MUST be followed with an it_expr, and
> CANNOT
> be followed currently by ";" or an end-of-line marker.
>
>
>>  Every example we have has some
>> other datum after the "$", I never said anything about $-at-eol ever
>> since I first proposed SUBLIST on the mailinglist, and so on, so you
>> might legitimately say that this is "unspecified".
>>
>> > Since "a b" is on a child line, I'd it to parse in the same manner as "c
>> > d",
>> > resulting in ((a b) (c d)).
>>
>> That seems reasonable, given your rules.  One might say that:
>>
>> $
>> ! a b
>> ! c d
>> ==>
>> $ \\
>> ! a b
>> ! c d
>
> I'm okay with that, especially if it makes using the construct "more
> natural"
> and avoids turning a plausible use into an error.
>
> It's a trivial 1-line addition to the BNF.  If we *don't* add that, then I
> clearly
> need to add an error-check to the Scheme implementation.
>

Hmmm

$
! a b
! c d

INDENT ; stack: (0 ?)
INDENT a b ; stack: (0 ? 2)
SAME c d ; stack: (0 ? 2)
DEDENT DEDENT

\\
!\\
!!a b
!!c d

(
  (
(a b)
(c d)))

==> (((a b) (c d))), not ((a b) (c d)) - note the extra () introduced
by $ compared to \\

--

However despite that, Beni's let example is correct:

let $
x $ compute 'x
y $ compute 'y
  use x

let INDENT ; stack: (0 ?)
 INDENT x INDENT compute 'x ; (0 ? 4 ?)
 DEDENT ; stack (0 ? 4), indentation 4
 y INDENT compute 'y ; (0 ? 4 ?)
 DEDENT DEDENT ; stack (0 ?), indentation 2
 use x ; stack (0 2)
DEDENT

let
!\\
!!x
!!!compute 'x
!!y
!!!compute 'y
!use x


>> > [I'm asking this because if it's 'fixed, my
>> > closing-SUBLIST-by-unmatched-dedent would allow:
>> >
>> > let $
>> > ! ! x $ compute 'x
>> > ! ! y $ compute 'y
>> > ! body...
>> > ]
>
> I have a *lot* of concerns with that particular construct.
>
> But we could certainly allow $-at-end-of-line regardless,
> on the grounds of consistency.
>
> So let's add $-at-EOL, unless someone objects soon.
>
> --- David A. Wheeler
>
> --
> Everyone hates slow websites. So do we.
> Make your web apps faster with AppDynamics
> Download AppDynamics Lite for free today:
> http://p.sf.net/sfu/appdyn_d2d_feb
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Proposal: allow closing SUBLIST by dedenting

2013-02-19 Thread Alan Manuel Gloria
Okay, Beni showed how to properly use his formulation of SUBLIST for
multi-item let, in the other thread "$ at end of line bug?":

let $
x $ compute 'x
y $ compute 'y
  use x y

Here's another (ab)use:

let $ $ x
! ! ! ! ! compute 'x
! ! ! ! y
! ! ! ! ! compute 'y
! use x y

==>

let INDENT INDENT x ; stack: (0 ? ?)
   INDENT compute 'x ; stack (0 ? ? 10)
   DEDENT y ; stack (0 ? 8)
   INDENT compute 'y ; stack (0 ? 8 10)
  DEDENT DEDENT ; stack (0 ?), indentation = 2
  use x y ; stack (0 2)
DEDENT

==>

let
!\\
!!x
!!!compute 'x
!!y
!!!compute 'y
!use x y

--


I like Beni's formulation.  It's a whole lot cooler than my original
formulation of SUBLIST, and follows the SUBLIST and monotonic indent
equivalence theorem:

foo $ x $ y

<==>
foo
! x
! ! y

--

Also need to insert this rule for interaction between SUBLIST and GROUP/SPLIT.

SPLIT.  Whenever a GROUP/SPLIT is encountered that is not the first
item on the line (i.e. SPLIT semantics):
SPLIT.1.  if the top stack item is ?, pop off ? items until reaching a
non-? item; emit DEDENT for each popped ?
SPLIT.2.  otherwise, emit SAME

--

Given this, I suspect we can also express <* *> in terms of the
indentation stack.

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] $ at end of line bug?

2013-02-19 Thread Alan Manuel Gloria
On Tue, Feb 19, 2013 at 9:04 PM, Beni Cherniavsky-Paskin
 wrote:
> This behaves surprisingly:
>
> $
> ! a b
> ! c d
> ==>
> ((a b (c d)))
>
> it seems $ consumes the following newline, resulting in same parsing as if I
> wrote
>
> $ a b
>c d
>
> Is this deliberate?

No (at least not by me; check David's answer, but I suspect he didn't
implement it deliberately that way).  Every example we have has some
other datum after the "$", I never said anything about $-at-eol ever
since I first proposed SUBLIST on the mailinglist, and so on, so you
might legitimately say that this is "unspecified".

> Since "a b" is on a child line, I'd it to parse in the same manner as "c d",
> resulting in ((a b) (c d)).

That seems reasonable, given your rules.  One might say that:

$
! a b
! c d
==>
$ \\
! a b
! c d

>
> [I'm asking this because if it's 'fixed, my
> closing-SUBLIST-by-unmatched-dedent would allow:
>
> let $
> ! ! x $ compute 'x
> ! ! y $ compute 'y
> ! body...
> ]

Hmm...

let INDENT ; stack: (0 ?)
INDENT  x INDENT compute 'x ; stack: (0 ? 4 ?)
DEDENT ; stack: (0 ? 4), indentation = 4
y INDENT compute 'y ; stack: (0 ? 4 ?)
  DEDENT DEDENT ; stack: (0 ?), indentation = 2
  body ... ; stack: (0 2)
DEDENT

==>
let
!\\
!!x
!!!compute 'x
!!y
!!!compute 'y
!body

--

looks legit.

Hmm, let's try the SUBLIST and monotonic-indentation equivalence
theorem... i.e.:

foo
! bar

<===>

foo $ bar

So, let's try it:

let $
! ! x
! ! ! compute 'x
! body ...

==>

let INDENT ; stack: (0 ?)
 INDENT x ; stack: (0 ? 4)
 INDENT compute 'x ; stack: (0 ? 4 6)
 DEDENT DEDENT ; stack: (0 ?), indentation = 2
 body ... ; stack: (0 2)
DEDENT

==>
let
!\\
!!x
!!!compute 'x
!body ...

--

Looks good so far.  I think I prefer your formulation of SUBLIST if
it's truly back-compatible (and even if shown non-back-compatible, if
the back compatibility loss is acceptable in the typical case).  It
seems to me that much of SUBLIST's power may be due to the fact that
it has a hidden surprisingly elegant formulation like yours, leading
to its hidden surprisingly elegant semantics.

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Proposal: allow closing SUBLIST by dedenting

2013-02-19 Thread Alan Manuel Gloria
Okay, okay, currently:

let
  $ x $ compute 'x
  use x

==>

(let
  ((x (compute 'x))
  (use x))

So, let's try the new formulation:

let
!!$ x $ compute 'x
!!use x
==>
let
  INDENT INDENT x INDENT compute 'x ; stack: (0 2 ? ?)
  DEDENT DEDENT ; stack: (0 2), indentation = 2
  use x
DEDENT
===>
let
!\\
!!x
!!!compute 'x
!use x

So it works right even in the degenerate case.

But it doesn't *extend* the way it might be naively expected, as seen
in the previous posts:

let
  $ x $ compute 'x
y $ compute 'y
  use x y

==>
let
!\\
!!x
!!!compute 'x
y
!compute 'y
!use x y


---

Hmm.

I wonder if, however, using a similar approach for ENLIST rather than
SUBLIST would work???

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Proposal: allow closing SUBLIST by dedenting

2013-02-19 Thread Alan Manuel Gloria
let
!!$ x
!!compute 'x
y
!!compute 'y
!!use x y

==>

let
  INDENT INDENT x ; stack: (0 2 ?)
  INDENT compute 'x ; stack: (0 2 ? 6)
  DEDENT ; stack: (0 2 ?), indentation = 4
  y ; stack: (0 2 4)
  INDENT compute 'y ; stack (0 2 4 6)
  DEDENT DEDENT ; stack (0 2)
  use x y
DEDENT
==>
let
!\\
!!x
!!!compute 'x
!!y
!!!compute 'y
!use x y

---

Hmmm.

let
!!$ x (compute 'x)
y (compute 'y)
!!use x y

===>

let
  INDENT INDENT x (compute 'x) ; stack: (0 2 ?)
  INDENT y (compute 'y) ; stack: (0 2 ? 4) - bummer
  DEDENT DEDENT ; stack: (0 2)
  use x y
DEDENT

>

let
!\\
!!x (compute 'x)
!!!y (compute 'y)
!use x y

bummer

On 2/19/13, Alan Manuel Gloria  wrote:
> On 2/19/13, Beni Cherniavsky-Paskin  wrote:
>> Here is yet another idea for opening multiple levels on one line, that
>> does
>> NOT involve column counting, only comparison of leading whitespaces.
>>
>> It's a backward-compatible extension to SUBLIST (similarly applicable to
>> any competing FOOLIST semantics), so we could leave it undecided for now,
>> and legalize it later.
>>
>> $ lets one open an inner list on one line, but currently it's only usable
>> when this list is the last element of the containing list:
>>
>> outer1 outer2 $ inner1
>> ! inner2
>>
>> You cannot express (outer1 outer2 (inner1 inner2) outer3)
>> without giving up on use of $.
>>
>> The proposal is to allow an unmatched dedent after inner2, and have that
>> return you to the outer level:
>>
>> outer1 outer2 $ inner1
>> ! ! inner2
>> ! outer3
>>
>> which would be equivallent to:
>>
>> outer1 outer2
>> ! inner1
>> ! ! inner2
>> ! outer3
>>
>> More formally (described for simplicity in terms of numeric indentation
>> levels; easily doable in terms of exact substrings):
>>
>> - Every $ pushes a "?" placeholder onto the stack of known indent levels.
>> - As before, increases in indentation push a specific number onto the
>> stack.
>> - Dedents matching a level on the stack are handled as before, closing
>> all
>> levels to the right, whether specific or placeholders.
>> - A dedent that doesn't match any specific level is *only* allowed if
>> there
>> is at least one placeholder between the closest specific levels.  All
>> higher levels are closed, and the *rightmost* (see rationate at end) of
>> these placeholders is converted to the specific level seen.
>>   Let's say you had (10 ? ? 16) on the stack and you encounter a line
>> starting with 14 spaces. This closes 16 and the new stack is (10 ? 14).
>>   A following 13 line would close 14 and leave (10 13), and then a
>> following 12 line would be an error.
>
> I think it's also important to consider the "SAME" (as opposed to
> INDENT or DEDENT) token.  In particular:
>
> x
> ! foo $ bar
> ! a b
>
> ==>
>
> (x
>   (foo bar)
>   (a b)
> )
>
> Since the INDENT/SAME/DEDENT decision is based on the indentation
> stack, I think we should specify it as follows:
>
> 1.  Every $ adds a ? to the indentation stack, and emits an INDENT.
> 2.  On encountering an EOL, slurp the indentation.
> 3.  If the indentation is greater than the topmost non-? stack entry,
> push its indentation level on the stack and consider it an INDENT.
> 4.  If the indentation is equal to the topmost non-? stack entry, pop
> off ? stack entries (emitting a DEDENT for each).  If there are no ?
> on the stack top, emit a SAME.
> 5.  If the indentation is less than the topmost non-? stack entry, pop
> off ? stack entries (emitting a DEDENT for each) until you reach a
> state where the topmost non-? stack entry is less than or equal to the
> indentation.
> 5.1.  If the topmost non-? stack entry is equal to the indentation,
> pop off ? stack entries (emitting a DEDENT for each).
> 5.2.  if the topmost non-? stack entry is less than the indentation,
> and there is at least one ? entry, pop off the topmost ? entry and
> replace it with the current indentation (do not emit any INDENT or
> DEDENT tokens).
> 5.2.  Otherwise, error!
>
> So, let's consider this classic SUBLIST text:
>
> probe $ call/cc $ lambda (exit) $ cond
>   foo? $ exit 1
>   bar? $ 2
>
> ==>
> probe INDENT call/cc INDENT lambda (exit) INDENT cond
>; at this stage, stack is (0 ? ? ?)
>INDENT foo? INDENT exit 1
>; at this stage, stack is (0 ? ? ? 2 ?)
>; it sees an indent of 2, so it emits a DEDENT here
>; via rule #4.
>DEDENT
>bar? INDENT 2
>; at this stage, stack is (

Re: [Readable-discuss] Proposal: allow closing SUBLIST by dedenting

2013-02-19 Thread Alan Manuel Gloria
On 2/19/13, Beni Cherniavsky-Paskin  wrote:
> Here is yet another idea for opening multiple levels on one line, that does
> NOT involve column counting, only comparison of leading whitespaces.
>
> It's a backward-compatible extension to SUBLIST (similarly applicable to
> any competing FOOLIST semantics), so we could leave it undecided for now,
> and legalize it later.
>
> $ lets one open an inner list on one line, but currently it's only usable
> when this list is the last element of the containing list:
>
> outer1 outer2 $ inner1
> ! inner2
>
> You cannot express (outer1 outer2 (inner1 inner2) outer3)
> without giving up on use of $.
>
> The proposal is to allow an unmatched dedent after inner2, and have that
> return you to the outer level:
>
> outer1 outer2 $ inner1
> ! ! inner2
> ! outer3
>
> which would be equivallent to:
>
> outer1 outer2
> ! inner1
> ! ! inner2
> ! outer3
>
> More formally (described for simplicity in terms of numeric indentation
> levels; easily doable in terms of exact substrings):
>
> - Every $ pushes a "?" placeholder onto the stack of known indent levels.
> - As before, increases in indentation push a specific number onto the
> stack.
> - Dedents matching a level on the stack are handled as before, closing all
> levels to the right, whether specific or placeholders.
> - A dedent that doesn't match any specific level is *only* allowed if there
> is at least one placeholder between the closest specific levels.  All
> higher levels are closed, and the *rightmost* (see rationate at end) of
> these placeholders is converted to the specific level seen.
>   Let's say you had (10 ? ? 16) on the stack and you encounter a line
> starting with 14 spaces. This closes 16 and the new stack is (10 ? 14).
>   A following 13 line would close 14 and leave (10 13), and then a
> following 12 line would be an error.

I think it's also important to consider the "SAME" (as opposed to
INDENT or DEDENT) token.  In particular:

x
! foo $ bar
! a b

==>

(x
  (foo bar)
  (a b)
)

Since the INDENT/SAME/DEDENT decision is based on the indentation
stack, I think we should specify it as follows:

1.  Every $ adds a ? to the indentation stack, and emits an INDENT.
2.  On encountering an EOL, slurp the indentation.
3.  If the indentation is greater than the topmost non-? stack entry,
push its indentation level on the stack and consider it an INDENT.
4.  If the indentation is equal to the topmost non-? stack entry, pop
off ? stack entries (emitting a DEDENT for each).  If there are no ?
on the stack top, emit a SAME.
5.  If the indentation is less than the topmost non-? stack entry, pop
off ? stack entries (emitting a DEDENT for each) until you reach a
state where the topmost non-? stack entry is less than or equal to the
indentation.
5.1.  If the topmost non-? stack entry is equal to the indentation,
pop off ? stack entries (emitting a DEDENT for each).
5.2.  if the topmost non-? stack entry is less than the indentation,
and there is at least one ? entry, pop off the topmost ? entry and
replace it with the current indentation (do not emit any INDENT or
DEDENT tokens).
5.2.  Otherwise, error!

So, let's consider this classic SUBLIST text:

probe $ call/cc $ lambda (exit) $ cond
  foo? $ exit 1
  bar? $ 2

==>
probe INDENT call/cc INDENT lambda (exit) INDENT cond
   ; at this stage, stack is (0 ? ? ?)
   INDENT foo? INDENT exit 1
   ; at this stage, stack is (0 ? ? ? 2 ?)
   ; it sees an indent of 2, so it emits a DEDENT here
   ; via rule #4.
   DEDENT
   bar? INDENT 2
   ; at this stage, stack is (0 ? ? ? 2 ?)
   ; an empty line may be considered an indent of 0,
   ; so insert 5 DEDENT's
DEDENT DEDENT DEDENT DEDENT DEDENT

==>
probe
! call/cc
! ! lambda (exit)
! ! ! cond
! ! ! ! foo?
! ! ! ! ! exit 1 ; 5 indent's so far, so 5 levels, seems right
! ! ! ! bar?
! ! ! ! ! 2 ; 5 dedents after this, so we close!!

--

Looks about right.

Now the main reason to implement SUBLIST this way is, of course, the
bane of indentation syntax, LET:

let
!!$ x $ compute 'x
y $ compute 'y
!!use x y
==>
let
  ; the first indent below is the "real" indent
  INDENT INDENT INDENT x INDENT compute 'x
  ; at this point, stack is (0 2 ? ?)
  ; again, first indent below is "real" indent"
  INDENT y INDENT compute 'y
  ; at this point, stack is (0 2 ? ? 4 ?)
  ; since we get back to an indent of 2,
  ; emit 2 DEDENT's to get past the 4,
  ; then (via rule 5.1) pop off all ? to
  ; reach the 2 (which involves popping
  ; off 4 indents).
  DEDENT DEDENT DEDENT DEDENT use x y
  ; again, empty line, pop off the single dedent
  DEDENT
==>
let
!\\
!!\\
!!!x
compute 'x
!y
!!compute 'y
.

well, bummer, doesn't work.

Oh well.

Sincerely,
AmkG


>
> A common objection to any scheme allowing unmatched dedents is that it
> requires lookahead, both for machine parsing *and humans*.  When you read:
>
> foo
> ! ! bar
> ... pages of stuff
> ! ! baz
> ! quux
>
> it's very disconcerting to realize that all this bar...baz stuff was not

Re: [Readable-discuss] Scheme implementation and testsuite status

2013-02-18 Thread Alan Manuel Gloria
On 2/19/13, David A. Wheeler  wrote:
> I've improved the Scheme sweet-expression implementation and test suite
> further;
> here's a summary.  It's working well overall.  However, in the process of
> adding lots of tests
> I've identified a subtle bug in the Scheme implementation THAT isn't in the
> ANTLR implementation.
> If anyone wants to help identify the problem or solution for that bug (see
> below) that'd be great.
>
> Anyway...
>
> The Scheme implementation now accepts #!+space as a SRFI-22 comment to EOL,
> #!/  ...   !# and #!.  ...  !# as non-nesting multi-line comments, and
> #!directives
> (#!directives must begin with a letter).  These were mentioned in SRFI-105,
> and are documented as SHOULDs in the draft SRFI-sweet specification.
> In the Scheme implementation a #!directive currently just reads up to a
> whitespace (or EOF) and throws away the text; that is obviously
> imperfect, but it is better than what we had before and gives us something
> better
> to work with.  So finally #!sweet isn't an error :-).
>
> The Scheme implementation also now accepts #u8(...) syntax.
>
> I've added a large slew of tests for the Scheme implementation, and in the
> process
> also fixed a small bug combining <*...*> and improper lists
> (now <* a . b *> works as expected).
>
>
> As I mentioned above, there *is* one bug I know of.  It appears to involve
> an interaction
> between <*...*> and multiple sublists when "*>" is after other things.
> Again, if someone would help me track this problem
> down (at least its cause) that'd be great.  It's in "tests/sweet-testsuite",
> search for FIXME;
> it is currently commented out since it's known to fail.  The test case is:
>
> let <* x $ cos $ f c *>
> ! dostuff x
>
>
> That SHOULD produce (as the ANTLR implementation does):
> (let ((x (cos (f c
>   (dostuff x))
>
> However, the Scheme implementation incorrectly returns:
> (let (x (cos ((f c
>   (dostuff x))
>
>
> Interestingly, the Scheme implementation works just fine with:
> let <* x $ cos $ f c
> *>
> ! dostuff x
>
>
> I don't have time to track down that bug for now. If someone wants to start
> (and at least
> post some hints, doing that many eyes thing) that'd be awesome.

Going only from your previous source descriptions (I don't have access
to my hack machine right now), it feels like the problem is with
propagating upwards the monadic fail operation ("failed due to *>")
from the lower level SUBLIST handling.

I assume that your top-level t_expr correctly handles the *> case and
correctly passes it upwards; I think it's the lower levels which fail
to correctly handle *>.  That's why *> on a line by itself is
correctly handled (SUBLIST handler sees EOL-SAME, so it closes its
list correctly, and then t_expr sees the *> and acts as if it found an
EOF and propagates the failure upward).

For the *>-at-eol case, I suspect your SUBLIST handler handles it too
greedily and fails to propagate the *> upward.

$0.02

(yeah, I just gotta insert "monad" somewhere when discussing parsers)

Sincerely,
AmkG

--
The Go Parallel Website, sponsored by Intel - in partnership with Geeknet, 
is your hub for all things parallel software development, from weekly thought 
leadership blogs to news, videos, case studies, tutorials, tech docs, 
whitepapers, evaluation guides, and opinion stories. Check out the most 
recent posts - join the conversation now. http://goparallel.sourceforge.net/
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Proposal: ENLIST (Arne's ":")

2013-02-18 Thread Alan Manuel Gloria
So what's the consensus?  It seems we're the only two here, Arne is
not responding to the mailinglist, and no one else is making any
comments either way.

I suggest we at least write it up as a rationale no SRFI-sweet; maybe
the more public SRFI process will pick up a few people who will
provide a better alternative view on this topic.  I tried my best to
push for ENLIST using what I think is Arne's semantics, but I may be
biased due to my sheer love of SUBLIST.

I volunteer to write this rationale topic.

On 2/18/13, David A. Wheeler  wrote:
> Alan Manuel Gloria:
>> Well, it's very easy to describe ENLIST informally:
>
> Well, it's *slightly* easier to describe - maybe - but the losses are really
> substantial.
> And "easy to describe" is an illusion once you re-add position calculation
> for
> arbitrary encodings and code systems and typefaces.  The "ASCII-only
> universe"
> stays simpler but just doesn't describe the world as it is or will be.
>
> And "ease of description" is NOT the best measure anyway.
> We want "ease of reading and use, at scale"... not just simplicity of
> description.
> Most programming languages - and math -
> have shown that humans are willing to learn some syntax, if it's something
> they use often enough that they can amortize the learning time.
> And people read more than they write.  A notation that is more pleasant
> to *read* is, I think, more important than "shortest possible description"
> or "shortest number of rules".  There's a balance, of course, and
> reasonable
> people can differ on where that is best placed.  But after reading these
> ideas,
> I'm convinced this approach would be much *worse* than what we have now.
>
>> We *could* argue that for 90% of the code you'd want to write, the
>> ASCII-only restriction is not a big problem, and for 90% of the
>> environments you'd want to program in, having a fixed-width font is a
>> given.  Then we could say that for international text, you can't have
>> ":" after any international parts (not portably, anyway).  We lose
>> some code density (due to loss of SPLIT and SUBLIST) and the ability
>> to read code meaningfully when presented in a variable-width font, but
>> gain a very simple (informally) semantic, which is (relatively) easy
>> for the uninitiated to grasp.
>
> Sure, that can be argued, but that seems a precarious position to me.
> We know that these assumptions can be (and are) falsified a thousand ways.
> The semantic doesn't actually appear all that much simpler to me, and
> the losses of the other capabilities are substantial.
> And I still don't see the strong use case.
>
>> As an aside, I have no idea how right-to-left text works in Unicode
>> (arabic text, I think hebrew text too).  I do know there are
>> "direction changed" code points in Unicode.
>
> http://xkcd.com/1137/
>
>>  So, more complexity in
>> order to keep track of "real characters".  And then there's text
>> normalization, where multiple code points should end up being treated
>> as single characters semantically
>
> Yes indeed.  Yet another area of problems.
>
> The whole idea of knowing what a "position" is seems very pointless
> when you have differing sequences of characters.  If there were no other
> way
> to handle it, then we'd have to handle it, but we *already* have a notation
> that
> does not require this kind of magic.
>
>
> --- David A. Wheeler
>
> --
> The Go Parallel Website, sponsored by Intel - in partnership with Geeknet,
> is your hub for all things parallel software development, from weekly
> thought
> leadership blogs to news, videos, case studies, tutorials, tech docs,
> whitepapers, evaluation guides, and opinion stories. Check out the most
> recent posts - join the conversation now.
> http://goparallel.sourceforge.net/
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
The Go Parallel Website, sponsored by Intel - in partnership with Geeknet, 
is your hub for all things parallel software development, from weekly thought 
leadership blogs to news, videos, case studies, tutorials, tech docs, 
whitepapers, evaluation guides, and opinion stories. Check out the most 
recent posts - join the conversation now. http://goparallel.sourceforge.net/
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Proposal: ENLIST (Arne's ":")

2013-02-17 Thread Alan Manuel Gloria
On 2/18/13, David A. Wheeler  wrote:
> So while I appreciate your efforts to make concrete exactly what ENLIST
> would
> entail, I'm becoming convinced that we should definitely *NOT* add any form
> of
> ENLIST to the sweet-expression notation.   The line-ending one is too
> limited, and
> the magic-column version depends on assumptions that we KNOW are widely
> false.
> Forcing to ASCII-only doesn't deal with variable-width types and is absurd
> since
> not everyone uses English for everything.
> In general, depending on really knowing the widths of different characters
> is just
> absurd in an internationalized world.  And even after all that, neither
> interpretation
> has the strength of strong use cases that just can't be reasonably done
> another way.
>
> If anyone has a strong counter-argument, I'd certainly like to hear it
> ASAP.
> What I want to see is a load of use cases that are really important and
> really hard to do otherwise... so much that false assumptions are acceptable
> :-).

Well, it's very easy to describe ENLIST informally:

1.  The ":" marker, called ENLIST, marks a new "indent level" without
requiring a separate line.  This basically means that you can consider
":" as a newline, followed by an indentation to that position.

And with ENLIST, you get most of what you want for GROUP and a good
portion of SUBLIST - it's just that our current GROUP is GROUP/SPLIT
and SUBLIST's greedy nature is the source of much of its power (for
good or ill).

The problems with ENLIST only arise when ENLIST semantics are looked
at more deeply, and largely only for international code.

One could argue that using non-ASCII characters for code elements
(variable names, function names, etc.) is bad style, every programmer
should have access to fixed-width fonts (otherwise we are revoking
your geek license), and international strings should be implemented
using GNU gettext, the way god intended international text to be
implemented.  This means that programming in a strict ASCII-only style
with fixed-width fonts is probably fine, until you want international
text without fooling around with the GNU gettext mark of the beast
_(), someone *else* (like your boss) forcibly revokes your geek
license and prevents you from using fixed-width fonts, and if you're
being a jerk about your PhD dissertation and write all your variable
names as single greek letters in UTF-8, just to make your paper more
interesting ("Γ is a mapping between symbols and their types,
which in our text we will call the 'type-environment'").


We *could* argue that for 90% of the code you'd want to write, the
ASCII-only restriction is not a big problem, and for 90% of the
environments you'd want to program in, having a fixed-width font is a
given.  Then we could say that for international text, you can't have
":" after any international parts (not portably, anyway).  We lose
some code density (due to loss of SPLIT and SUBLIST) and the ability
to read code meaningfully when presented in a variable-width font, but
gain a very simple (informally) semantic, which is (relatively) easy
for the uninitiated to grasp.

>
> I really do want to hear all ideas, but I think we've delved so deeply into
> this idea
> that at least one Balrog has shown up. Lacking Gandalf's flame of Anor, I'm
> planning on
> running to Moria's exit :-).

Dunno 'bout you, but I hear the Mule has taken over the Foundation and
we'd better look for the second one.

--

As an aside, I have no idea how right-to-left text works in Unicode
(arabic text, I think hebrew text too).  I do know there are
"direction changed" code points in Unicode.  So, more complexity in
order to keep track of "real characters".  And then there's text
normalization, where multiple code points should end up being treated
as single characters semantically

>
>
> --- David A. Wheeler
>
> --
> The Go Parallel Website, sponsored by Intel - in partnership with Geeknet,
> is your hub for all things parallel software development, from weekly
> thought
> leadership blogs to news, videos, case studies, tutorials, tech docs,
> whitepapers, evaluation guides, and opinion stories. Check out the most
> recent posts - join the conversation now.
> http://goparallel.sourceforge.net/
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
The Go Parallel Website, sponsored by Intel - in partnership with Geeknet, 
is your hub for all things parallel software development, from weekly thought 
leadership blogs to news, videos, case studies, tutorials, tech docs, 
whitepapers, evaluation guides, and opinion stories. Check out the most 
recent posts - join the conversation now. http://goparallel.sourceforge.net/
___

Re: [Readable-discuss] Proposal: ENLIST (Arne's ":")

2013-02-17 Thread Alan Manuel Gloria
On 2/18/13, David A. Wheeler  wrote:
> Alan Manuel Gloria wrote:
>> Subject: [Readable-discuss] Proposal: ENLIST (Arne's ":")
>> Here's the semantic of ENLIST:
>
> Whew!  Thanks for drilling down a potential semantic.
> I do not think we should do this (for reasons described below), but
> the first step is to have something concrete enough to discuss,
> and I really appreciate that you've turned vague discussions into details.
>
>
>> 1.  ENLIST-at-the-start:
> ...
>
> Plausible enough.
>
>
>> 2.  ENLIST-inline:
>>
>> When found inline, ENLIST detects its column location. It then acts as
>> if ithere were an EOL followed by an indentation to its column location.
>>
>> Specifically, to determine the indentation text to insert:
>>
>> 2.1.  Copy the current line's indentation (tabs, spaces, and !) directly.
>> 2.2.  Any non-whitespace character on the current line after the
>> line's indentation, and before the ":" being considered, is replaced
>> with a space.
>>
>> CAVEAT:  Because a "character" may vary between different encodings,
>> and because different Lisplike's have different capabilities regarding
>> reading text in different encodings, ONLY ASCII CHARACTERS ARE
>> CONSIDERED.  If 2.2 above finds a character that is not in the ASCII
>> domain (0->126) then it throws an error.
>
> Ack! Ack! Ack!
>
> I think this is just broken.  Devising a human-readable
> data notation in 2013 that cannot work with non-ASCII characters is,
> in my opinion, a complete non-starter.
>
> Even if you only use ASCII, this notation ignores the problem of
> variable-width fonts (I'm currently writing this using a variable-width
> font).

Even in fixed-width fonts, many (all?) CJK chars are displayed
double-width, making the term "fixed width" a misnomer.  And then
there's encoding troubles.  Many simple Scheme's (and Lisps) use the
character=byte encoding (one of the reasons for the de facto R6RS
rejection), and just pass string bytes directly to the system, on the
assumption that the programmer wants that literally.  A portable
implementation (one that works across multiple Scheme's) would have to
just know if the interpreter/compiler/whatever it's on has byte=char,
or has a universal UTF-8 assumption (NOT yet universal; our Japanese
mother company randomly uses either EUC-JP or Shift-JIS), or has ports
configurable with encoding, or has ports that autodetect (!) encoding,
just to handle non-ASCII, never mind the CJK's.

As an aside, Haskell gets away with this (magic column position)
because it has evolved in such a way that there is now One True
Implementation for it.  GHC AFAIK handles CJK quite well, and AFAIK
also supports various encodings (which also helps to cement its
position as the One True Implementation; other implementations have a
really, really long road to take to even reach a minor fraction of
GHC's capabilities, so typical users bend over backwards to install
GHC on their systems).

>
>> Programmers are thus restricted in that non-ASCII characters cannot be
>> used before an ENLIST on the same line.
>
> I understand *why*, but to me, that limitation suggests that it's just too
> broken to accept.
>
> I really appreciate the effort to formalize this, but with these details
> exposed to the
> light of analysis, I think this particular baby is pretty ugly.  :-).  Or is
> that ^.^ ?
>
> There was another variation of ENLIST that closed matching parens at the end
> of the line;
> that at least wasn't sensitive to visual character widths, etc.  Not that
> I'm sold on that
> variant either, but at least it didn't have that (to-me-fatal) flaw.

Pretty much the only use major use case for the "line-ending ENLIST" I
can see is:

define : foo x y
  whatever
  whatever ...

If "line-ending ENLIST" ended at either GROUP/SPLIT, SUBLIST, or an
EOL, we could do:

define : foo x y $ probe $ call/cc $ lambda (return) $ cond
  : has? x 'some-property $ return 42
  : has? y 'some-property $ return 41
  : else $ return 0

So: line-ending ENLIST has its niche.  It just doesn't seem to be a
powerful enough niche (I personally think it's bad style to put
complicated code in the conditions of cond, or if, or whatever, so
something like has?(x 'some-property) is acceptable.  Arguably in the
above case {x has? 'some-property} is even clearer, and doesn't even
need the line-ending ENLIST).

>
> Perhaps even worse, I don't think there's enough justification for WHY we
> need yet
> another syntactic construct.  ENLIST (either meaning) is not powerful enough
> to
> replace any of the 

Re: [Readable-discuss] Proposal: extended PERIOD notation

2013-02-17 Thread Alan Manuel Gloria
On 2/18/13, David A. Wheeler  wrote:
> Alan Manuel Gloria:
>> <* define-library \\ (srfi 41 primitive)
>>
>> export . (
>>   stream-cons stream-null
>>   stream-pair? stream-null? stream?
>>   stream-car stream-cdr
>>   stream-lambda
>> )
>
> which can then be closed with:
>> *>
>
>
>
> Quick confirmation, to make sure we have the same understanding...
> When you surrounded "srfi 41 primitive" with parens, did you intend
> it to mean something different than if they weren't?  Or was that just
> a style you prefer?

Style preference; Scheme libraries seem to be named (whatever whatever
whatever ...) in parentheses, e.g. (rnrs base (6)) (scheme base)
(scheme cxr).  I think of the parentheses as part of the name of the
library; see also my examples using guile define-module on the source
tree.

Sincerely,
AmkG

--
The Go Parallel Website, sponsored by Intel - in partnership with Geeknet, 
is your hub for all things parallel software development, from weekly thought 
leadership blogs to news, videos, case studies, tutorials, tech docs, 
whitepapers, evaluation guides, and opinion stories. Check out the most 
recent posts - join the conversation now. http://goparallel.sourceforge.net/
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


[Readable-discuss] Proposal: ENLIST (Arne's ":")

2013-02-14 Thread Alan Manuel Gloria
Here's the semantic of ENLIST:

1.  ENLIST-at-the-start:

ENLIST at the start of a line denotes that the line is to be
considered to be indented at that location, regardless of where it is
located.  It has no other effect, but acts as an "invisible" symbol.
As a corollary, only the first ever ENLIST on the line is invisible;
succeeding ENLIST's (even ones directly after an ENLIST-at-the-start)
have the ENLIST-inline meaning below.

This is different from GROUP/SPLIT, where multiple
GROUP/SPLIT-at-the-start is the same as one (and zero, for that
matter, except when it's the only item on the line).

Otherwise, ENLIST-at-the-start is the same as SPLIT-at-the-start (it's
an invisible symbol).

2.  ENLIST-inline:

When found inline, ENLIST detects its column location. It then acts as
if ithere were an EOL followed by an indentation to its column
location.

Specifically, to determine the indentation text to insert:

2.1.  Copy the current line's indentation (tabs, spaces, and !) directly.
2.2.  Any non-whitespace character on the current line after the
line's indentation, and before the ":" being considered, is replaced
with a space.

CAVEAT:  Because a "character" may vary between different encodings,
and because different Lisplike's have different capabilities regarding
reading text in different encodings, ONLY ASCII CHARACTERS ARE
CONSIDERED.  If 2.2 above finds a character that is not in the ASCII
domain (0->126) then it throws an error.

This caveat should help in the worst case: when the implementation
lives in a character=byte world, but the programmer is exploiting this
and using the system's native encoding when writing strings (so that
string text and even #| ... |# comments can have encoded non-ASCII
characters that the implementation will pass verbatim to the system).
Except in the case where the encoding uses 0x1B to introduce non-ASCII
characters (IIRC there's an encoding which uses that).

Programmers are thus restricted in that non-ASCII characters cannot be
used before an ENLIST on the same line.  This allows an octet stream
to be read in by different implementations of this spec in exactly the
same way, as long as the encoding used by the writer of the octet
stream is ASCII-compatible.

3.  ENLIST-at-end:

ENLIST-at-end has no semantic defined.  If an ENLIST is at the end of
a line, it is considered either an ENLIST-at-the-start (if it is the
only non-indent non-whitespace on the line) or ENLIST-inline (if there
is text before it).

--

So, transformations:

:
  :
x

==>

\\
  \\
x

--


let : : x $ foo bar
meow x

==>

let : : x $ foo bar
^ copy "let ", replace every non-whitespace with space: ""
meow x

==>

let
: : x $ foo bar
meow x

==>

let
:
  : x $ foo bar
meow x

==>

let
\\
  x $ foo bar ; initial : can be removed here
meow x

--

define : foo bar
   meow bar

==>

define
   : foo bar
   meow bar

==>

define
   foo bar
   meow bar

--
Free Next-Gen Firewall Hardware Offer
Buy your Sophos next-gen firewall before the end March 2013 
and get the hardware for free! Learn more.
http://p.sf.net/sfu/sophos-d2d-feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] unhappy with the current direction

2013-02-14 Thread Alan Manuel Gloria
I've been reviewing the ancient records (LOL was most of
sweet-expressions decided just last year? (^_^)v)

So, this is just a recap of why the current sweet-expressions looks
the way it currently does.

--

As a complete and utterly gratuitous non-sequitur, I prefer (^.^)
smilies to :-) smilies because the () pair up in the former.

--

The path that was tread by sweet-expressions to get to where we are
now was basically:

1.  David A. Wheeler started with indentation semantics in general
(i.e. deduce parens from indent)

2.  David then (apparently) searched through existing semi-formalized
proposals for indentation and found SRFI-49:
2. a.  Indentation means "child of next less indented line above it"
2. b.  Multiple items on a line form a list
2. c.  Single items are just that item.
2. d.  Symbol 'group when found as the first item on a line is deleted
(i.e. the magic non-existent symbol).  To start a line with an actual
"group" you double up the "group" so that the first group is deleted
but the second remains (this is explained later on this list by Egil
Moller; initially our understanding was that it forced a grouping).

3.  David adds curly-infix and n-expressions over the basic SRFI-49
I-expressions (these two were somewhat independently built, mostly by
David, although discussed in the list; in particular I think I (Alan)
was the one who pointed out that automatic infix detection sucked, by
using the "convoke" example).

4.  List goes on hiatus as secondary participants move on, and David
(apparently) goes on a PhD-hunting spree and incidentally proves for
some reason that compiling things twice using open-source compilers
prevents some guy named ken from adding backdoors to every system on
the planet.

5.  David begins planning out some extensions over the basic SRFI-49,
describes them slightly on his webpage.  Some posts exist on the list,
scattered over 2006->2011, mostly David very occassionally posting
something about something.
5. a.  This includes some random stuff about "SPLICE", which is mostly
due to Arc's nasty if syntax.  Initially SPLICE is just a continuation
marker, then David extends it so that it has an inline meaning (the
same as the current GROUP/SPLIT when inline), and finally David
extends it so that it becomes invisible when at the start of a line.
SPLICE is spelled "\".

6.  Arne floats the idea to replace "group" with the syntax ".".
David mentions preferring a "larger" character ("because a period is
almost too small") and floats the idea to use "\".  This discussion
peters out mostly unresolved.

7.  Some guy named almkglor pops up late in June 2012, rants about how
Haskell is kewl and how every Lisp should be exactly like Haskell
except when it's like Lisp, and complains that every Haskell
implementation he can find can't be bootstrapped on his employer's
system except for Hugs98, which can't run GHC and doesn't have any of
GHC's kewl extensions like type class families (which he still doesn't
understand, but are kewl anyway).  He builds a parser description for
sweet-expressions using a system that exists only in his head.

8.  almkglor incidentally mentions that "\" (which David last proposed
as an alternative spelling for "group" instead of ".") was also
proposed before by David as SPLICE.  He points out that the
SPLICE-at-the-end rule is not easily implementable on a
one-char-lookahead machine, at least if you're going to consider
whitespace+EOL == EOL (which you should).

9.  Since David proposed "\" for SPLICE and later proposed "\" for
GROUP, almkglor assumes that what David is actually proposing is that
SPLICE and GROUP be somehow merged into a single semantic, and starts
working out how to safely merge both.  At this point GROUP is still
considered as meaning "add an extra layer of indent" rather than the
current meaning of "magical invisible symbol that is automatically
removed if it's the very first symbol".

10.  almkglor points out that Egil Moller himself said (in a message
somewhere in the limbo of The Hiatus) that "group" was intended to be
the magic invisible symbol, so that GROUP at the beginning was
equivalent to not having anything there, it just marked a point at
which that particular line actually indented.

11.  almkglor points out that Egil Moller's explanation means that
GROUP and SPLICE work exactly the same when at the start of a line.

12.  almkglor and David start discussing GROUP, SPLICE, and another
semantic called ENLIST (in modern terms, it acts more like the current
":" notation by Arne). Arne points out that SPLICE-inline rule is
complicated to explain; almkglor counters with the fact that it's
needed for easy usage of Arc if-syntax and CL keyword-syntax.

13.  David trolls the mailing list with the idea to use "." for indentation.

14.  almkglor goes on a spree of starting all sorts of threads on the
mailinglist to confuse everyone else into submission.

15.  almkglor renames SPLICE to SPLIT, since it's no longer actually a
SPLICE, wit

[Readable-discuss] Proposal: extended PERIOD notation

2013-02-11 Thread Alan Manuel Gloria
xref. Arne Babenhauserheide's concept, I'm proposing that we steal his
extended PERIOD notation and add it into sweet-expressions.

Basically:

foo
  . x

==>

(foo
  x)

...which is currently what we have.

However, the extended PERIOD notation is:

foo
  . x y

==>

(foo
  x y)

... in contrast to:

foo
  x y

==>

(foo
  (x y))

--

For interaction with existing notations:

foo
  . x $ y z $ w

==>

foo
  . x (y z w)

==>

(foo
  x (y z w))

--

foo
  . x \\ y z \\ w

==>

foo
  . x
  y z
  w

==>

(foo
  x
  (y z)
  w)



This is useful in some cases:

<* define-library \\ (srfi 41 primitive)

export
  . stream-cons stream-null
  . stream-pair? stream-null? stream?
  . stream-car stream-cdr
  . stream-lambda


--

However, for the above case the current sweet-expressions can also express this:

<* define-library \\ (srfi 41 primitive)

export . (
  stream-cons stream-null
  stream-pair? stream-null? stream?
  stream-car stream-cdr
  stream-lambda
)
...

The question, really, is:

Sometimes people write multiple short arguments to a form all on a
single line, in order to reduce vertical space.  However, such a line
can be expressed using the existing . ( ... ) form (see "export"
example above).  Arguably, the existing ". ( ... )" form is esoteric,
and "( )" disables ! indentation inside it.  Should we support the new
extended PERIOD notation?

AmkG: will support, will not push

--
Free Next-Gen Firewall Hardware Offer
Buy your Sophos next-gen firewall before the end March 2013 
and get the hardware for free! Learn more.
http://p.sf.net/sfu/sophos-d2d-feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] unhappy with the current direction

2013-02-11 Thread Alan Manuel Gloria
On 2/11/13, Arne Babenhauserheide  wrote:
> Hi Alan,
>
> (I’m answering to both mails here)
>
> Am Montag, 11. Februar 2013, 11:07:30 schrieb Alan Manuel Gloria:
>> Your main contributions seem to be the extended "." behavior (. a =>
>> a, . a b -> a b) and the ":" syntax.  I don't see any use, even in
>> your examples, of the single-item-on-a-line-is-single-item-list
>> behavior.
>
> The reason for that is consistency: Making sure that when you learn a
> minimal set of rules you can understand the structure of all code you see.
>

Consistency and convenience are both needed in a notation.  The key is
to find the balance between both.  I think in this case, the
single-item case tends to occur more often than the
single-item-function-call case.

Even for preprocessing, consider the following rule:

A line is considered a "single-item line" if:
1.  Strip trailing and leading spaces from the line.
2.  If there are any spaces inside the line that are outside matched
() [] {} "" #||#, it is not a single-item line.
3.  Newlines/EOL inside matching () [] {} "" #||# are  considered
spaces and do not "terminate" the line.

So even if you insist on a separate preprocessing pass rather than a
full parser, it's possible to still correctly process the
single-item-line.

>> That's fine and all, but suppose I'm defining a method for Guile GOOPS?
>>
>> define-method : hack (x )
>> ! do-hack-on-cat x
>>
>> Oops, except hack only works on cats anyway, so I'll just optimize
>> things (because profiling shows that method calls in GOOPS take up all
>> my time, LOL) and turn hack into an ordinary function:
>>
>> define : hack x
>> ! do-hack-on-cat x
>>
>> Oh, no!!  Now I have to adjust the indentation of everything inside
>> it!  Luckily hack x just contains do-hack-on-cat, so all I need to do
>> is adjust that single line.
>>
>> define : hack (x )
>> !  do-hack-on-cat x
>
> Well, I’m a Python-Programmer. In Python you run into that everytime you
> remove or add an if. Before I used rectangle-edit, it disturbed me a bit.
> Now it’s quite painless:
>
> C-SPACE M-↓ ↑ C-7 → C-x C-r C-k

The example I show is worse, because it doesn't apply to just if: it
applies to every misspelled token.

Although 

> There would be a simple way to fix it, though: Make the position of : only
> significant when you want to indent deeper. To make this consistent: Make
> the indentation of a line only relevant for deeper nested lines (child
> lines). Then the following would all be valid code:
>
> if : = a 1
>b
>   c
>
> if
> = a 1
> b
>   c
>
> if : = a 1
>   b
>   c
>
> if
> = a 1
>   b
>   c
>
> If the indentation is equal or lower than a previous indentation layer, the
> bracket of that indentation layer gets closed.

I see.  This does lessen (but not remove) problem #1.

>
>> 3.  You need to explicitly specify how double-width CJK characters are
>> handled when found before a ":" (ban them in code?  But what about
>> strings and #| |# comments?).  Do we treat them as single character
>> columns (easy implementation, but potentially confusing, and possibly
>> limiting international code) or do we treat them as double character
>> columns (need to consider encoding, and implementations need to keep a
>> list of all such double-width characters)?
>
> Being able to reduce indentation of later lines (as long as they stay child
> lines) would also solve this for most cases.

Please tell me: what should an implementation do when a double-width
CJK character is encountered?  Treat it as a +1 column position or +2
columns position?

At the very least, say "+1 column position, so people should avoid
using a : followed by a line more-indented than the : after a
double-width character, as it would be confusing."  Unless you're
willing to pay the price of every implementation keeping a list of
each double-width character.

>
>> ":" seems to put a lot of pressure on implementations, using your
>> current explanation.  Perhaps we can change ":" to be more local (i.e.
>> it won't require keeping track of column position, and won't cause
>> cascading affects when text before it changes)?
>
> For me the inline : mainly exists for consistency: It generalizes GROUP.
>
> Essentially GROUP adds a new indentation layer, so you could just allow
> using it inline. But I use : for group, because I think that \\ looks alien
> to normal text and so it hampers readability for all people who aren’t used
> to bash-escaping.

Our c

Re: [Readable-discuss] unhappy with the current direction

2013-02-10 Thread Alan Manuel Gloria
I looked at your python code:

1.  It seems that it currently doesn't handle ":" in the middle of a line, yet.

2.  It seems that multiple ": " at the start of each line are ignored,
and only the last one is used.  So the following is possibly (?)
valid:

define foo(bar)
: cond
: : meow?(bar)
: : : cat bar
: : woof?(bar)
: : : dog bar
: : else
: : : error 'foo "error!"

--

About ":"

How about this semantic instead?

":" introduces a (, and a promise to add ) at the end of that line.
It is like a limited $, except that $ will not wrap a single item on
the line (: will) and $ can cross the line end.

This localizes ":", meaning that we can use it this way:


define : add-if-all-numbers lst
  call/cc
lambda : exit
  let loop
\\
  lst lst
  sum 0
if : null? lst
  sum
  if : not : number? : car lst
exit #f
loop : cdr lst
+ sum : car lst

This seems to be a lot more readable, since the previous rule for ":"
*required* a lot more horizontal space; this time, it's optional (see
the arguments to loop on the last two lines for a good use of it).

--

When crossing line boundaries, $ does a better job than your current
":" idea, because it doesn't require keeping track of column
positions.  So I think $ should keep that job, and only use : for the
limited case where it's useful to only put it to the end of the line.

For example, say I'm debugging a long and boring stream function
(using SRFI-41 streams).  So I develop a "probe" function like so:

define-stream probe(x) $ cond
  stream-pair?(x)  $ begin
display (stream-car x) \\ newline()
stream-cons
  stream-car x
  probe $ stream-cdr x
  else$ stream-null

And I apply it to my stream code like so:

define-stream stream-map(f s) $ probe $ cond
  stream-pair?(x)  $ stream-cons
   f $ stream-car x
   stream-map f $ stream-cdr x
  else$ stream-null

In the first place, ":" can't support the shown cond-pattern.  So
without $, it would look like (without probe):

define-stream stream-map(f s)
  cond
stream-pair?(x)  : stream-cons
 f : stream-car x
 stream-map f : stream-cdr x
else: stream-null

With probe:

define-stream stream-map(f s)
  probe
cond
  stream-pair?(x)  : stream-cons
   f : stream-car x
   stream-map f : stream-cdr x
 else: stream-null

So, just to probe my code, I need an extra indentation.  With $, I
don't need the extra indentation.

":" can't be used here (using your current idea for ":"), since it
would require indenting even more than just using a separate line
would.

"$" is surprisingly versatile.

-


A new synthesis?

Perhaps we can *keep* GROUP/SPLIT \\, SUBLIST $, and COLLECTINGLIST <*
*>, use the EXTENDPERIOD . a b, and add the new LINELIST :

Then we can do something like:

<* define-library \\ (amkg foo)

export
  . cat dog meow
  . whatever woof arf

import
  (scheme base)

<* begin

define : cat x
  let : : y {x + 1}
meow x y

define : dog x
  woof $ meow {x - 1} {x + 2}

...

*>;begin
*>;define-library

what you think?

--
Free Next-Gen Firewall Hardware Offer
Buy your Sophos next-gen firewall before the end March 2013 
and get the hardware for free! Learn more.
http://p.sf.net/sfu/sophos-d2d-feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] unhappy with the current direction

2013-02-10 Thread Alan Manuel Gloria
On 2/11/13, Arne Babenhauserheide  wrote:
>> So: can you be more clear about how your indentation-based syntax
>> interacts with the n-expression stack?
>
> That was a part I wasn’t perfectly sure about when I wrote - and which I
> could not fix before sending, because I wrote late at night and knew that I
> would not have time to improve it the next few days.
>
> Conceptually:
>
> - neoteric at the beginning of a line is hard to do right
>   (it would always be a double bracket).
> - neoteric within a line, or in a line which starts with .
>   would just be the corresponding s-expression.
> - curly-infix would just be the s-expression - except if
>   the whole line is curly-infix. I don’t like that exception…
>   maybe the line with only curly infix should just be prefixed
>   with a ..
>
> define : fibup maxnum count n-1 n-2
>if {maxnum = count}
>  . {n-1 + n-2}
>  fibup maxnum {count + 1} {n-1 + n-2} n-1

You know what I suggest?  Drop the
single-item-on-a-line-is-single-item-list rule.  Include the
"n-expression datum on a line by itself is just that item - if you
want to code a function call to a 0-arity function, explicitly put ()
around or after" from sweet.  None of your examples rely on the
single-item-list behavior and must explicitly turn it off anyway, so I
think you should optimize the presentation for the more common usage.

Your main contributions seem to be the extended "." behavior (. a =>
a, . a b -> a b) and the ":" syntax.  I don't see any use, even in
your examples, of the single-item-on-a-line-is-single-item-list
behavior.

>
>
>
> The : is just a shortcut for starting a new line at the indentation of the
> :. So
>
>define : fibfast n
>   if {n < 2}
>   . n
>   fibup n 2 1 0
>
> could be written as
>
>define
>   fibfast n
>   if {n < 2}
>   . n
>   fibup n 2 1 0

That's fine and all, but suppose I'm defining a method for Guile GOOPS?

define-method : hack (x )
! do-hack-on-cat x

Oops, except hack only works on cats anyway, so I'll just optimize
things (because profiling shows that method calls in GOOPS take up all
my time, LOL) and turn hack into an ordinary function:

define : hack x
! do-hack-on-cat x

Oh, no!!  Now I have to adjust the indentation of everything inside
it!  Luckily hack x just contains do-hack-on-cat, so all I need to do
is adjust that single line.

define : hack (x )
!  do-hack-on-cat x

--

The advantage of the current approach is that column positions are
only significant for the first non-whitespace non-! character on a
line.

: breaks that.  It now makes :'s column position significant.  This
has some drabacks

1.  As seen above, changing text before the ":" marker will
potentially affect the interpretation of every non-blank line after
that.  This is in contrast to \\ and $, which are completely
localized.  Sure, it's rare to change define-method (or
define-whatever) to define, but suppose I had misspelled defin-method
and started continuously coding several lines?  What if I misspelled
one of my own non-standard macros (so that the IDE won't highlight it,
since it doesn't recognize the the correctly spelled keyword anyway,
meaning a very high chance of me missing any misspelling)?

2.  The implementation now needs to keep track of column positions all
the time, because we are never sure that we won't encounter it
suddenly.  This is significant because it means a complete
reimplementation of n-expressions, one that does indeed keep track of
column positions.  This means we also need to completely reimplement
string parsing (currently we depend on the underlying Lisp's
implementation), symbol parsing, and number parsing.

3.  You need to explicitly specify how double-width CJK characters are
handled when found before a ":" (ban them in code?  But what about
strings and #| |# comments?).  Do we treat them as single character
columns (easy implementation, but potentially confusing, and possibly
limiting international code) or do we treat them as double character
columns (need to consider encoding, and implementations need to keep a
list of all such double-width characters)?

":" seems to put a lot of pressure on implementations, using your
current explanation.  Perhaps we can change ":" to be more local (i.e.
it won't require keeping track of column position, and won't cause
cascading affects when text before it changes)?

--

In conclusion: I think the extended "." is OK, ":" not so much (needs
more explaining/thinking).  I object to the
single-entity-is-list-of-one-item rule.

Sincerely,
AmkG

--
Free Next-Gen Firewall Hardware Offer
Buy your Sophos next-gen firewall before the end March 2013 
and get the hardware for free! Learn more.
http://p.sf.net/sfu/sophos-d2d-feb
___
Readable-discuss mailing list
Readable-

Re: [Readable-discuss] unhappy with the current direction

2013-02-10 Thread Alan Manuel Gloria
Okay, I checked, and I'm not sure how you propose to handle curly-infix.

It seems, according to your examples, that a line composed of a single
curly-infix item is that item, not a list of that item.

In fact, I think I want to be very clear on what, exactly, it is that
you envision the following code to be in s-expressions:


define : fibup maxnum count n-1 n-2
   if {maxnum = count}
 {n-1 + n-2}
 fibup maxnum {count + 1} {n-1 + n-2} n-1

>From this example, it appears that there's special handling for
curly-infix, because using the set of rules I derived from what I
think is the intent of your ruleset (and hand-processing ":"), this
becomes:

(define (fibup maxnum count n-1 n-2)
  (if (= maxnum count)
((+ n-1 n-2)) ; huh??
(fibup maxnum (+ count 1) (+ n-1 n-2) n-1)))

In fact, I think I want to be much more clear here:

So: can you be more clear about how your indentation-based syntax
interacts with the n-expression stack?

Sincerely,
AmkG

--
Free Next-Gen Firewall Hardware Offer
Buy your Sophos next-gen firewall before the end March 2013 
and get the hardware for free! Learn more.
http://p.sf.net/sfu/sophos-d2d-feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] unhappy with the current direction

2013-02-10 Thread Alan Manuel Gloria
Attached find a simple implementation (which does *not* handle
comments, blank lines, and ":").

I've also pushed it on the git repo.

On Sat, Feb 9, 2013 at 4:59 PM, Alan Manuel Gloria  wrote:
> On Sat, Feb 9, 2013 at 1:43 PM, Alan Manuel Gloria  wrote:
>> - at the start of the read, the "previous line's indent" is considered
>> as negative.
>> - A line with the same indent as the previous line inserts a ")".  It
>> also inserts a "(" unless the line starts with "."
>> - a line with a greater indent than the previous line inserts a "("
>> unless the line starts with "."
>> - a line with a lesser indent than the previous line inserts a ")" for
>> each indentation level popped, followed by a closing ")"
>> - "." at the start of the line is removed.
>>
>
> Scratch that.  Here's a better implementation, based on what I see as
> the core stuff you want.
>
> This ruleset bans a more indented line after a "."-initial line.  None
> of your examples shows that case, and I think that the simplistic
> approach I'm using is hard to hack a decent effect with it.  I also
> ignore ":", because I'm not sure if its effect crosses line boundaries
> (and if it does, how you're supposed to handle double-width CJK
> characters.)
>
> - the reader has two variables: a stack of indentation levels, and a
> boolean dot flag.  Initially the stack contains a single negative
> item, and the dot flag is false.
> - When the current line is more indented than the stack top:
> - - if the dot flag is set, error!!
> - - if it starts with ".", just set the dot flag
> - - otherwise insert a "(" and clear the dot flag and push the new
> indent on the stack.
> - When the current line is at the same indent as the stack top:
> - - if the dot flag is cleared, insert ")".
> - - if it starts with ".", just set the dot flag
> - - otherwise insert a "(" and clear the dot flag
> - Otherwise:
> - - if the dot flag is cleared, insert ")"
> - - pop off stack items until we reach an indent with the exact same
> indent as the current line; emit ")" for each popped item (warning:
> off-by-one error might be here, so need to actually check by
> implementing)
> - - if it starts with "." just set the dot flag
> - - otherwise insert a "(" and clear the dot flag
>
> nb: blank lines might cause (), need to consider those.
> nb: also, see the warning above, need to actually check it.
>
> Hope this helps.  If you can get an implementation (even just a simple
> one that does a text-to-text substitution, and without ":", like the
> above) show us so we can think about it more.
>
> Sincerely,
> AmkG


arne-formulation.scm
Description: Binary data


sample.arne
Description: Binary data
--
Free Next-Gen Firewall Hardware Offer
Buy your Sophos next-gen firewall before the end March 2013 
and get the hardware for free! Learn more.
http://p.sf.net/sfu/sophos-d2d-feb___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] unhappy with the current direction

2013-02-09 Thread Alan Manuel Gloria
On Sat, Feb 9, 2013 at 1:43 PM, Alan Manuel Gloria  wrote:
> - at the start of the read, the "previous line's indent" is considered
> as negative.
> - A line with the same indent as the previous line inserts a ")".  It
> also inserts a "(" unless the line starts with "."
> - a line with a greater indent than the previous line inserts a "("
> unless the line starts with "."
> - a line with a lesser indent than the previous line inserts a ")" for
> each indentation level popped, followed by a closing ")"
> - "." at the start of the line is removed.
>

Scratch that.  Here's a better implementation, based on what I see as
the core stuff you want.

This ruleset bans a more indented line after a "."-initial line.  None
of your examples shows that case, and I think that the simplistic
approach I'm using is hard to hack a decent effect with it.  I also
ignore ":", because I'm not sure if its effect crosses line boundaries
(and if it does, how you're supposed to handle double-width CJK
characters.)

- the reader has two variables: a stack of indentation levels, and a
boolean dot flag.  Initially the stack contains a single negative
item, and the dot flag is false.
- When the current line is more indented than the stack top:
- - if the dot flag is set, error!!
- - if it starts with ".", just set the dot flag
- - otherwise insert a "(" and clear the dot flag and push the new
indent on the stack.
- When the current line is at the same indent as the stack top:
- - if the dot flag is cleared, insert ")".
- - if it starts with ".", just set the dot flag
- - otherwise insert a "(" and clear the dot flag
- Otherwise:
- - if the dot flag is cleared, insert ")"
- - pop off stack items until we reach an indent with the exact same
indent as the current line; emit ")" for each popped item (warning:
off-by-one error might be here, so need to actually check by
implementing)
- - if it starts with "." just set the dot flag
- - otherwise insert a "(" and clear the dot flag

nb: blank lines might cause (), need to consider those.
nb: also, see the warning above, need to actually check it.

Hope this helps.  If you can get an implementation (even just a simple
one that does a text-to-text substitution, and without ":", like the
above) show us so we can think about it more.

Sincerely,
AmkG

--
Free Next-Gen Firewall Hardware Offer
Buy your Sophos next-gen firewall before the end March 2013 
and get the hardware for free! Learn more.
http://p.sf.net/sfu/sophos-d2d-feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] unhappy with the current direction

2013-02-08 Thread Alan Manuel Gloria
On Sat, Feb 9, 2013 at 7:47 AM, Arne Babenhauserheide  wrote:
> Hi,
>
> You might have noticed that after initial excitement I drew back from 
> readable again. The reasons were partly time problems, but mostly that I have 
> the feeling that readable currently moves into a direction which does not 
> feel right to me.
>
> There is now indentation based syntax (great!) with special casing for 
> sublists (useful for nested functions), restart lists (hm) and now <* ... *> 
> (looks alien).
>
>
> To me this lost the beauty of lisp, that you have few fixed syntax rules 
> which become second nature. Instead we now have mixed metaphors and code 
> which can be written in a multitude of ways - which goes counter to 
> readability (it’s not about every special case being beautiful, but having a 
> consistent style which is nicely readable in most cases).
>
>
> And it just felt wrong to see more and more special cases being added. That 
> smelled of a problem in the basic concept.
>
>
> Also I wondered how code like the following would be represented:
>
> (concat "I want " (getwish from me) " - " username)
>
> Currently I only see this option:
>
> concat "I want " getwish(from me) " - " username
>
> But not this
>
> concat "I want "
>getwish from me
>" - " username
>
>
> I did not get my mind off the idea, though (and did not want to), and I 
> derived a simpler concept from it:
>
> - if a line starts with a . it is a continuation of the parent line
>   (the last line which had lower indentation).
> - if a line is further indented than the previous line,
>   it opens a new bracket (except if it starts with a .),
> - if it is indented equally, then it closes a bracket and opens a new one
>   (except if it starts with a ., then it only closes a bracket).
> - A : sourrounded by whitespace defines a new indentation level
>   (similar to restart list, but more general).
>
> That provides 4 clear rules, one of which is similar to an existing rule
> ( “(. a) → a” becomes “(. a b c) → a b c” ). And that’s all the syntax to 
> learn with no special cases.
>
>
> Essentially all it does is giving up the rule that a variable on its own is a 
> variable instead of a function call.
>
>
> By prefixing all variables with “.”, it also gets line continuations for free:
>
> a b c d e
>   . f g h
>   . i j k
>
> is equivalent to
>
> (a b c d e
>f g h
>i j k)
>

Really?  Because your rule is:

> - if it is indented equally, then it closes a bracket and opens a new one
>   (except if it starts with a ., then it only closes a bracket).

So:
(a b c d e
  f g h
  ) i j k

?


>
> And the problematic code switches to
>
>
> concat "I want "
>getwish from me
>. " - " username

You know, this second example suggests that maybe the "then it only
closes the bracket" is incorrect.

Here's a set that seems to be closer to what you want (ignoring ":" for now)

- at the start of the read, the "previous line's indent" is considered
as negative.
- A line with the same indent as the previous line inserts a ")".  It
also inserts a "(" unless the line starts with "."
- a line with a greater indent than the previous line inserts a "("
unless the line starts with "."
- a line with a lesser indent than the previous line inserts a ")" for
each indentation level popped, followed by a closing ")"
- "." at the start of the line is removed.

So:

concat "I want"
  getwish from me
  . " - " username

at the start of read, the previous line's indent is negative, so
"concat" at indent 0 is more indented and inserts a "(":

(concat "I want"
^
  getwish from me
  . " - " username

the next line is more indented than the previous line, so insert:

(concat "I want"
  (getwish from me
  ^
  . " - " username

The next line has same indent, but also a ".", so insert only a ")":

(concat "I want"
  (getwish from me
  ) " - " username
  ^

The next line is empty, which is an indent at 0, so pop off one indent
(one ")") and add a closing ):

(concat "I want"
  (getwish from me
  ) " - " username
))

erk, that has an extra ")",

... or something anyway.  Maybe "." should raise a flag that
suppresses ")" for the next line.  But I think that ends up having a
stack in the case of indentation.

...or something, at least.  Hehe.

>
>
> Some of the Examples¹ from the sf.net site look like this (also using curly 
> infix, since that’s useful for easier math):
>
>
>define : fibfast n
>   if {n < 2}
>   . n
>   fibup n 2 1 0
>
> define : fibup maxnum count n-1 n-2
>if {maxnum = count}
>  {n-1 + n-2}
>  fibup maxnum {count + 1} {n-1 + n-2} n-1
>
> define : factorial n
>if {n <= 1}
>. 1
>{n * factorial{n - 1}}
>
> define : gcd x y
>if {y = 0}
>. x
>gcd y : rem x y
>
>
>
> define : add-if-all-numbers lst
>call/cc
>  la

Re: [Readable-discuss] New sweet-expression reader is now the default in the "develop" branch

2013-02-05 Thread Alan Manuel Gloria
On 2/6/13, David A. Wheeler  wrote:
> Before we declare a "0.7", I think we need to greatly expand the test suite
> to cover new functionality... and make sure the Scheme implementation
> passes, too :-).
>
> The new Scheme implementation handles a lot - including real programs - but
> there are some edge cases and "new" functionality it doesn't handle:
> 1. It doesn't handle #u8(), such as #u8(5 6 7).

This is new in R6RS (where it's #vu8) and R7RS.

> 2. It doesn't handle the new #!... variations.  Basically, #!DATUM like
> #!sweet should be consumed (and ignored if it has no special meaning),
> "#!"+space is a SRFI-22 one-line ignored value, "#!"+ period or slash goes
> to matching "!#" (guile-like).

I think R6RS decided that #!foo specifically requires that sequence of
characters, to be terminated by any delmiiter (space, tab, open paren,
close paren, semicolon).  #! is hard to handle given how much it's
gotten overloaded.

> 3. It has trouble with "." as the last *content* of a list. Which means that
> '. works, but (quote .) doesn't.  That's weird, I think '. and (quote .)
> should mean exactly the same thing.  Anybody who uses "." as a variable name
> should be taken out and shot, but we should *try* to be general, and we need
> '. at least to self-implement.  Actually, we inherit this limitation from
> the SRFI-105 implementation; I think we should fix this, and post a fix in
> the SRFI-105 mailing list.  Such a change would accept: (.) and (quote .)
> for example.  But maybe I'm wrong; certainly (.) is not a common construct.

. is not a valid identifier according to R5RS and R6RS. In both, an
identifier is either a peculiar identifier, or an initial followed by
zero or more subsequents.  A peculiar identifier is + - or ... in
R5RS; R6RS includes -> followed by zero or more subsequents.  The
defined initials in R5RS is  or a special initial; the special
initials do not include ".".  In R6RS initial can also be a Unicode
>127 character with particular listed categories, or a \x hex escape.
None of those includes ".", so it's not a valid identifier, and is not
even valid as the first character of an identifier.

. being accepted as a symbol is a Guile-ism, and even in Guile is not
consistently supported.  In Guile '(.) yields a parsing error.

>
>
> I think I'll emphasize editing "tests/sweet-testsuite", which has "correct"
> followed by "test" value.  Different implementations will print lists
> differently, so that makes it easier to use the same testsuite for different
> implementations.
>
> --- David A. Wheeler
>
> --
> Free Next-Gen Firewall Hardware Offer
> Buy your Sophos next-gen firewall before the end March 2013
> and get the hardware for free! Learn more.
> http://p.sf.net/sfu/sophos-d2d-feb
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

--
Free Next-Gen Firewall Hardware Offer
Buy your Sophos next-gen firewall before the end March 2013 
and get the hardware for free! Learn more.
http://p.sf.net/sfu/sophos-d2d-feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Proposal: EOF automatically closes collecting lists

2013-02-04 Thread Alan Manuel Gloria
On 2/5/13, John Cowan  wrote:
> Alan Manuel Gloria scripsit:
>
>> *  To create an R7RS library out of a bunch of definitions in a file,
>> simply put something like the following at the top of your file; there
>> is no need to change your existing formatting of existing definitions:
>
> I don't recommend that.  The better approach is to put the define-library
> form into a separate file, as is normally done in Chibi, with
> an include library-declaration in that file.

*shrug* then consider the style guide sufficiently modified to mention
R6RS library forms instead.

* To create an R6RS library out of a bunch of definitions in a file,
simply put something the following at the top of your file: there is
no need to change your existing formatting of existing definitions:
<* library \\ (your library (1 0 0))
export
  your-function
  rename internal:your-function external:your-function
  ...
import
  (rnrs base (6)) ; you probably need this
  ...
<* begin

define your-function ...
...

* An R7RS library can be created similarly.  However, the
recommendation is to leave the definitions in a separate file, and
just use R7RS include or include-ci, like so:
define-library (your library)
  export
your-function
rename internal:your-function external:your-function
...
  import
(scheme base)
...
  include "implementation-file.scm"

--

I personally prefer keeping the library spec with the definitions,
though, so even on R7RS I'd still put the <* define-library \\ blah
form.

Sincerely,
AmkG

--
Free Next-Gen Firewall Hardware Offer
Buy your Sophos next-gen firewall before the end March 2013 
and get the hardware for free! Learn more.
http://p.sf.net/sfu/sophos-d2d-feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


[Readable-discuss] Proposal: EOF automatically closes collecting lists

2013-02-04 Thread Alan Manuel Gloria
Here's how you might write a library in r7rs draft 8 using s-expressions:

(define-library (amkg meow)
(export meow)
(import (scheme base))

(begin

(define (meow) (cat "meow" "meow"))

(define (cat . xs)
  (for-each
(lambda (x)
  (display x) (newline))
xs))

) ; begin
) ; define-library

With proposed 0.7 semantics, it can be expressed in t-exprs as:

<* define-library \\ (amkg meow)
export meow
import (scheme base)

<* begin

define meow() $ cat "meow" "meow"

define cat(. xs)
  for-each
lambda (x)
  display x \\ newline()
xs

*>
*>

I'm proposing, however, that the COLLECTINGLISTEND tokens should be
*optional*, since we expect the "large" usage of collecting lists to
encompass entire files.

That way, we can say in style guidelines for R7RS t-exprs:

--

*  To create an R7RS library out of a bunch of definitions in a file,
simply put something like the following at the top of your file; there
is no need to change your existing formatting of existing definitions:

<* define-library \\ (your library name)
export
  your-definition
  rename internal:your-definition external:your-definition
  ...
import
  (scheme base) ; you likely need this
  (some other library)
  ...
other-library-declaration-such-as-include-or-cond-expand
...

<* begin

define your-definition ...
...

* To create R6RS libraries, use something effectively similar to the
above, except you can only use "export" and "import", and exactly in
that order, make sure to import "(rnrs base (6))" instead of "(scheme
base)", and use "library" instead of "define-library".

--

Basically, we allow the user to remove trailing *> if the collecting
list is the last thin of importance in a file.  This is important
since in R7RS a library definition will have two trailing close parens
(one for the begin containing the definitions, the other for the
define-library) and we need two extra lines to contain the trailing *>
(I'm not sure what happens with "*> *>" on a line by itself; maybe
that'll work too, but still...)

I feel this reduces some of the line-noisiness of collecting lists
while allowing a more flexible indenting / spacing of library
definitions.

What you think?

Sincerely,
AmkG

--
Free Next-Gen Firewall Hardware Offer
Buy your Sophos next-gen firewall before the end March 2013 
and get the hardware for free! Learn more.
http://p.sf.net/sfu/sophos-d2d-feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] New sweet-expression reader is now the default in the "develop" branch

2013-02-04 Thread Alan Manuel Gloria
On Mon, Feb 4, 2013 at 7:47 PM, David A. Wheeler  wrote:
> Alan Manuel Gloria 
>
>> Why 0.9?  Latest is 0.6, and the latest wiki modifications page is
>> Modifications-0.7.  Modifications-0.7 mentions the new <* ... *> rules
>> already, so there doesn't seem to be a justifiable reason to skip 2
>> numbers.
>
> A fair question!  We obviously have room for more numbers :-).
>
> But I don't know of any other proposed changes to the syntax or semantics
> of sweet-expressions; operators, meanings, etc. seem set.
> My intent is that this be the next-to-last version of the syntax before it's
> "official".  We then go through the SRFI process, make whatever changes
> (if any) that surfaces, and then declare the results final, aka 1.0.
> Working backwards, the previous version would be 0.9..
>
> But if you think we should call the next version 0.7, that's great by me.
> We can obviously skip from 0.7 to 1.0 if it's done :-).
>

I'd say 0.7.  After all SRFI process for curly-infix forced us to bump
the version number up a notch (0.5 -> 0.6); it's probably conceivable
that SRFI process for sweet-expressions will require us to go up
another version or two, so I think 0.7 is just the right place.  I'm
not completely convinced that the current semantics for collecting
lists is "final", after all.

I suppose go for SRFI after 0.7 release?

Sincerely,
AmkG

> --- David A. Wheeler
>
> --
> Everyone hates slow websites. So do we.
> Make your web apps faster with AppDynamics
> Download AppDynamics Lite for free today:
> http://p.sf.net/sfu/appdyn_d2d_jan
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss

--
Free Next-Gen Firewall Hardware Offer
Buy your Sophos next-gen firewall before the end March 2013 
and get the hardware for free! Learn more.
http://p.sf.net/sfu/sophos-d2d-feb
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] New sweet-expression reader is now the default in the "develop" branch

2013-02-03 Thread Alan Manuel Gloria
On 2/4/13, David A. Wheeler  wrote:
> The new Scheme reader seems to work well.  With the full collecting list
> implementation it passes the existing sweet-expression test suite, and it
> works correctly for processing sweeten and letterfall.  I've installed an
> exception handler, so if an error is detected, the rest of the text is
> skipped until we see a blank line and try again.
>
> So... the new Scheme reader is now the default reader in the "develop"
> branch.  The old reader still exists; you can enable it by setting the
> environment variable "SWEETOLD".  After a while I intend to remove it.
>
> I've updated the draft SRFI, and I notice that Alan Manuel K. Gloria has
> made a lot of improvements to the draft SRFI as well.
>
> I think the next steps are:
> * Clean up src/kernel.scm by removing the old implementation
> * Post on the website the <*...*> rules, which would make this
> sweet-expression version 0.9 (since we've changed the semantics by adding
> collecting lists, and we've hammered out the other semantics too).
> * Release the "develop" version as version 0.9

Why 0.9?  Latest is 0.6, and the latest wiki modifications page is
Modifications-0.7.  Modifications-0.7 mentions the new <* ... *> rules
already, so there doesn't seem to be a justifiable reason to skip 2
numbers.

> * Start the SRFI process with the draft SRFI.
>
>  --- David A. Wheeler
>
> --
> Everyone hates slow websites. So do we.
> Make your web apps faster with AppDynamics
> Download AppDynamics Lite for free today:
> http://p.sf.net/sfu/appdyn_d2d_jan
> ___
> Readable-discuss mailing list
> Readable-discuss@lists.sourceforge.net
> https://lists.sourceforge.net/lists/listinfo/readable-discuss
>

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_jan
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] Specifying #-syntax extensions

2013-01-29 Thread Alan Manuel Gloria
On 1/30/13, David A. Wheeler  wrote:
> Alan Manuel Gloria:
>> I'm concerned about # syntax.
>>
>> In particular, I'm worried about # syntax being used for non-datums
>> (basically, comments).
>>
>> I wonder if adding this to the spec would be a good idea:
>>
>> 
>> If an implementation supports some way of
>> extending the reader syntax at all,
>> such as by providing a hook into the # reader,
>> then that hook MUST be able to signal
>> a non-datum (basically, a comment).
>
> The issue is certainly real.  But without a standard way to signal it,
> it's not clear what this text would do for anyone.  I think it should at
> best be a "SHOULD", and perhaps not even that if there's no
> standard interface.
>
> Are you trying to slyly slip comment-tag into the spec :-) ?

Ugh, no.  I regret that bit of hackery (T.T).  That's the reason why
my example uses the () = comment, (datum)=datum convention instead.
Basically, I was kinda suggesting that convention should be used.

Should we strengthen that convention ()=comment, (datum) = datum (AND
MOST DEFINITELY NOT comment-tag, WHO WROTE THAT CODE? ^^;;;) instead
and demote the MUST to SHOULD?

Sincrely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_jan
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


[Readable-discuss] GROUP_SPLICE name

2013-01-29 Thread Alan Manuel Gloria
According to our Modifications-0.3 Wiki page, the behavior for "\\"
that won out was called "SPLIT".  Maybe we should do some extensive
renaming of GROUP_SPLICE into SPLIT instead?

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_jan
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


[Readable-discuss] Specifying #-syntax extensions

2013-01-29 Thread Alan Manuel Gloria
I'm concerned about # syntax.

In particular, I'm worried about # syntax being used for non-datums
(basically, comments).

I wonder if adding this to the spec would be a good idea:


If an implementation supports some way of
extending the reader syntax at all,
such as by providing a hook into the # reader,
then that hook MUST be able to signal
a non-datum (basically, a comment).
For example,
such a hook might require the convention
that the hooked procedure will return
either the empty list '() -
which indicates that the read-in text is a comment -
or a one-item list whose first item is the read in datum.
When an implementation of this SRFI reads a piece of text
that invokes the hook,
if the hooked procedure signals a non-datum,
it MUST be treated as an s-expression comment
(i.e. the scomment production above is extended to match that text).
If the hooked procedure signals a datum,
it MUST be treated as a possible n-expression head,
and a subsequent opening
(, [, or {
MUST be treated as an n-expression tail that will
affect that head.


Basically, I worry that people will de-facto-standardize on just
returning a datum (without any way of signalling a comment), and if
the text read in is a comment, to recurse into 'read.  Recursing into
'read is problematic for an indentation processor as it has a very
rich state.

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_jan
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] My sweet-expression re-implementation passes the sweet-expression test suite

2013-01-29 Thread Alan Manuel Gloria
On 1/30/13, David A. Wheeler  wrote:
> I said:
>> > Found and fixed.  The BNF action rule for "head SUBLIST rhs" used the
>> > monify
>> > function, which was completely unnecessary (I think this was a
>> > cut-and-paste
>> > from elsewhere and I didn't remove the monify).
>
> Alan Manuel Gloria:
>> That's the first thing I thought when I saw your bug report ^^.
>
> Sigh.  I'm only human, a fact I try to demonstrate daily :-).

Don't worry, I designed SUBLIST, so it's just expected that I'd figure
out implementation bugs of SUBLIST easily.  The bug has to do with the
tricky "a $ b" case, which is exactly the same as "a b", which many
people might find surprising.  The rationale for that is to provide
consistent formatting for constructs like cond, especially when
combining branches composed of complex computations with branches that
have a simple variable reference or constant.

>
> So I'm trying to use a mixture of approaches to make the
> final SRFI spec and implementation really high-quality:
> 1. ANTLR grammar checks (so grammar's more likely to be right)
> 2. Two implementations of the new spec (so grammar is widely implementable)
> 3. Big automated test suite, including checks with the old version results
> (so that the actual interpretation is what was intended, and that the
>  implementation is more likely to be right).
> 4. Peer review.  That'd be you guys :-).
>
>> Looks good.  My approach is still getting modded several times in my
>> head.  I think my approach will allow us to use a simple parser
>> combinators sublibrary (but really requires SAME due to the branch
>> after head).  I'm a bit busy IRL; I'll try to hack together something
>> using my alternative approach this weekend, but no promises.
>
> As an experiment, that approach sounds interesting, but I really do *NOT*
> want to use that approach for either the SRFI spec or the SRFI
> implementation.
> As I mentioned before, such a spec won't have the additional ANTLR
> grammar checks (unless you implement it in ANTLR).

Well, currently I'm planning on hacking together a parser-combinator
library and essentially converting from ANTLR syntax to
Scheme+parser-combinator syntax.  I'll have to change the tokenizer
around quite a bit in order to emit tokens that (part of) the ANTLR
spec will accept, but that's doable.  So I'd argue that, if I get it
working, it'll be even closer to the ANTLR spec., since it will *be*
the ANTLR spec, except in a Schemely syntax.  And a tokenizer.

^^,

> Also, I want to ensure that the shown-implementation has properties like
> (1) it doesn't depend on advanced Scheme capabilities (so it can port to
> not-quite-Schemes and other Lisps) and

Well, the only advanced Scheme capability it actually uses is lexical
scoping and anonymous functions.  That rules out elisp, admittedly.

I did mention using call/cc, but only as an even more theoretical 3rd
approach, which I am currently not pursuing.  If I get time, maybe I
will, as I suspect it will make the tokenizing structure even clearer.

> (2) it closely matches the spec.
> Also, the stronger separation of the pieces, while making each part simpler,
> will
> hide from humans how they combine, the very issue I want to make
> crystal-clear.

Hmm, granted.  I still think separating them is better because of the
conceptual simplicity, and the only combination involved is one
calling the other.  Basically all I'm doing is applying the "message
passing == function call" insight of the Lambda Teh Lutimate.

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_jan
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] What SHOULD this mean?!?

2013-01-29 Thread Alan Manuel Gloria
On 1/30/13, David A. Wheeler  wrote:
> I said:
>> > I've tweaked the ANTLR BNF so that initially-indented special comments
>> > are
>> > consumed, with the following hspace consumed too,...
>
> Alan Manuel Gloria:
>> I vaguely remember hacking this change in the previous version (which
>> is why there's a second entry point for sweet-read).  Or maybe
>> something else, don't remember well.
>
> Ah, that makes sense.

Yeah, on current develop that's on line 1441.  There's a
readblock-clean-rotated which accepts an extra leading object.  This
is called because on peeking a # we don't know if it's a datum or a
comment; if we read the #-thingy and it's not a comment, call
readblock-clean-rotated.

>
> Is there anything else like that, as best you remember?
> Now that we're trying to make the spec rigorous, I'd like to make sure
> we don't lose any important functionality.

None yet.  If you post more maybe it'll jog my memory (^_^);

Sincerely,
AmkG

--
Everyone hates slow websites. So do we.
Make your web apps faster with AppDynamics
Download AppDynamics Lite for free today:
http://p.sf.net/sfu/appdyn_d2d_jan
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] My sweet-expression re-implementation passes the sweet-expression test suite

2013-01-28 Thread Alan Manuel Gloria
On 1/29/13, David A. Wheeler  wrote:
> I said that my BNF:
>> *does* have a bug when processing letterfall, though. letterfall has a
>> construct in main.sscm that (simplified) is:
>> car $ gettimeofday()
>>
>> Pretty simple and straightforward.  Current unsweeten correctly implements
>> this as:
>>   (car (gettimeofday))
>>
>> But "SWEETNEW=new ./unsweeten" incorrectly implements that as:
>>   (car gettimeofday)
>>
>> Sigh.  It turns out this is a bug in the BNF :-(, so the code is correctly
>> implementing a bad spec.  I need to track down what's gone wrong.
>
> Found and fixed.  The BNF action rule for "head SUBLIST rhs" used the monify
> function, which was completely unnecessary (I think this was a cut-and-paste
> from elsewhere and I didn't remove the monify).

That's the first thing I thought when I saw your bug report ^^.

>
> The new sweet-expression implementation now passes the sweet-expression test
> suite, and processes both sweeten.sscm and a version of letterfall
> correctly.  (Or at least, it produces the same results as the old one did.)

Looks good.  My approach is still getting modded several times in my
head.  I think my approach will allow us to use a simple parser
combinators sublibrary (but really requires SAME due to the branch
after head).  I'm a bit busy IRL; I'll try to hack together something
using my alternative approach this weekend, but no promises.

Feel free to return some of the test cases you removed and add a few
more.  The test of letterfall is to play it ^^.  In theory, all you
need to do is replace the readable/kernel.scm with the new version on
a fresh-from-the-tarball copy of letterfall and just ./configure &&
make && ./letterfall.  Of course if you need an env variable make sure
to do the make inside the SWEETNEW=new env (letterfall itself doesn't
use the sweet-reader, only the Makefile does).

--
Master Visual Studio, SharePoint, SQL, ASP.NET, C# 2012, HTML5, CSS,
MVC, Windows 8 Apps, JavaScript and much more. Keep your skills current
with LearnDevNow - 3,200 step-by-step video tutorials by Microsoft
MVPs and experts. ON SALE this month only -- learn more at:
http://p.sf.net/sfu/learnnow-d2d
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


Re: [Readable-discuss] What SHOULD this mean?!?

2013-01-28 Thread Alan Manuel Gloria
On 1/29/13, David A. Wheeler  wrote:
> The current testsuite says that in sweet-expressions the following should
> mean "(foo (a b) . c)":
> foo
> !  a b
> !  .
> !  c
>
> SHOULD it mean that?  My ANTLR BNF doesn't do that, it just treats lone "."
> as a period, but we *did* support that previously.
>

*shrug* I think it's bad style either way (either you use "," as a
symbol, or you use improper lists to structure what is code or
code-like).  So either way will do.  Can even be "unspecified" as far
as I'm concerned.

"." as symbol is not a good idea in general in Lisps, and improper
lists in code-like structures is almost as bad.

> It also has said that lone abbreviation on a line, followed by an indent,
> applies that abbreviation to the body. E.G., this would mean "(quote (aaa
> bbb))":
> '
> ! (aaa bbb)
>
> Again, my ANTLR BNF doesn't do that, but we used to.  This one is debatable,
> since you can get the same effect with the word "quote" in Scheme (though
> that reasoning doesn't apply to Common Lisp).

It might be *clearer* for the user to write that, in some contexts.
So I think we should support this one at least.

>
> I've tweaked the ANTLR BNF so that initially-indented special comments are
> consumed, with the following hspace consumed too, and then recurses back to
> the t_expr production, like this:
>| (FF | VT)+ EOL retry2=t_expr {$v=$retry2.v;}
>| (initial_indent_no_bang | hspace+ )
>  (n_expr {$v = $n_expr.v;} /* indent processing disabled */
> + | scomment hspace* sretry=t_expr {$v=$sretry.v;}
>   | comment_eol retry3=t_expr {$v=$retry3.v;} )
>| initial_indent_with_bang error
>| EOF {generate_eof();} /* End of file */
> This is so that initially-indented block comments don't quietly disable
> sweet-expressions in the next line, like this:
>   #|  Hello |#
>   foo bar
> I think should be "(foo bar)" not "foo" then "bar".

I vaguely remember hacking this change in the previous version (which
is why there's a second entry point for sweet-read).  Or maybe
something else, don't remember well.

Sincerely,
AmkG

--
Master Visual Studio, SharePoint, SQL, ASP.NET, C# 2012, HTML5, CSS,
MVC, Windows 8 Apps, JavaScript and much more. Keep your skills current
with LearnDevNow - 3,200 step-by-step video tutorials by Microsoft
MVPs and experts. ON SALE this month only -- learn more at:
http://p.sf.net/sfu/learnnow-d2d
___
Readable-discuss mailing list
Readable-discuss@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/readable-discuss


  1   2   3   4   5   >