Login

Domain Specific Languages - Ruby, a Sign Post on the Road to Smalltalk

There's so much talk lately about Ruby being so great for writing domain specific languages, but this is only partially true, Ruby's not all it's cracked up to be. Too much hype and not enough substance, if one looks a little deeper.

Every programmer knows one domain specific languages that is so common, it's built into most languages, predicate logic. The good old if, if/else, and while forms, and several variations of them like do, unless, etc. So please forgive me while I state the obvious. Each form works using true/false as the input, and a block of code to be conditionally or repeatedly executed depending upon the value of the input. In a C'ish form, these look like so...

if(aBooleanCondition){
  someCodeToCall();
} else {
  someOtherCodeToCall();
}

while(aBooleanCondition){
    someCodeToCall();
}

There's nothing new here, every programmer knows this. What's interesting is that Ruby, like most languages, uses special forms for predicate logic. If Ruby is so great at writing domain specific languages, why not implement the most common domain specific language, predicates, just like any other embedded domain specific language?

This might sound crazy, but there's no reason that if/else and while need be part of the language, they can be moved into the library, given a language sufficiently powerful enough. When I first learned Smalltalk, the piece of code that blew my mind the most, was exactly this. Smalltalk the language, has no if/else or while statement, instead the domain specific language of predicates is implemented with simple objects and method calls, no compiler voodoo "required" (this is actually optimized by the compiler, I speaking conceptually here). Here's the most interesting bits.

True>>ifFalse: alternativeBlock
    ^nil

True>>ifFalse: falseAlternativeBlock ifTrue: trueAlternativeBlock
    ^trueAlternativeBlock value

True>>ifTrue: alternativeBlock
    ^alternativeBlock value

True>>ifTrue: trueAlternativeBlock ifFalse: falseAlternativeBlock
    ^trueAlternativeBlock value

False>>ifFalse: alternativeBlock
    ^alternativeBlock value

False>>ifFalse: falseAlternativeBlock ifTrue: trueAlternativeBlock
    ^falseAlternativeBlock value

False>>ifTrue: alternativeBlock
    ^nil

False>>ifTrue: trueAlternativeBlock ifFalse: falseAlternativeBlock
    ^falseAlternativeBlock value

BlockContext>>whileTrue: aBlock 
    ^ [self value] whileTrue: [aBlock value]

And here's how this DSL is used in Smalltalk...

aBooleanCondition 
    ifTrue: [ self someCodeToCall ]
    ifFalse: [ self someOtherCodeToCall ]
[aBooleanCondition] whileTrue: [ self someCodeToCall ]

The main thing to note here, beside the beauty of Smalltalk, is that blocks, objects, and methods calls are the necessary building blocks of "language" itself, any language. Having a succinct notation for the delayed evaluation of code, and allowing that code to be placed into variables and passed around, is all one needs to build virtually any domain specific language they can dream up.

Ruby at first glance, appears to have this trait. Ruby has blocks, but it didn't do them right. Ruby introduced an ugly hack called yield for pretending to pass a block with a terse form {}, but it only works for the last argument to a method, you can't pass two blocks to a method with this same terse syntax. The above predicate domain specific language can't be implemented in Ruby in exactly the same way, because Ruby can't pass both blocks cleanly, and even has two forms for specifying a block, the short and sweet { } and the longer "do end". This simple case works...

aBooleanCondition.ifTrue { someCodeToCall }

But the two block case won't, at least not in a single method call, you'd have to chain two calls together.

aBooleanCondition
    .ifTrue { someCodeToCall }
    .ifFalse { self someOtherCodeToCall }

Having keyword message syntax, is another vital piece of the puzzle. You see Ruby code faking this all the time by passing around associations to avoid the ugliness of positional nameless arguments, or as above, chaining multiple call together to fake the keyword style. But this doesn't look like idiomatic Ruby, and Ruby won't allow you to build forms that look like the built in if/else/while.

Rather than suffer this ugliness, Ruby simply provided a procedural syntax for predicate logic, with reserved words at the language level. Ruby, as nice as it is, is still a language that "can" build limited domain specific languages, but not necessarily with a syntax on par with what the language itself provides.

Smalltalk seems much more a notation, that can do nothing but build domain specific languages. Ruby isn't object oriented at the level Smalltalk is, is still falls back to procedural constructs and special syntax for many things. Smalltalk, is pure, objects all the way down, at every level, even the simplest and most common domain specific language of all, predicate logic. When you create a domain specific language in Smalltalk, your code never looks different than code provided by the compiler writer himself, it's one syntax to rule them all.

Smalltalk shares this trait with languages such as Lisp and Scheme, truly growable languages that put you, the programmer, in charge of what language you want, not some compiler writer who might take six more years to add some feature you just got to have now. When you need a new language feature in Smalltalk, you simply add it. It's a feeling that once you've become accustomed to, you can't live without, and one you don't quite get with Ruby.

There's been a lot of fuss lately about the next Ruby not supporting continuations, a feature vital in building a framework as elegant as Seaside. Yet, continuations were added to Squeak in about 39 lines of code, no big fuss necessary. This is that feeling I'm talking about, no waiting for the next official VM to support them, it's just a Smalltalk class, like any other.

Ruby is terse, nice looking, and even massively productive, but elegant it is not. And maybe that doesn't matter to most, but for those like me, elegance is real power, power that Ruby doesn't have. Ruby's an interesting sign post on the way from mainstream languages like Java and C#, but it's not the destination, it's just a good warm up for learning Smalltalk.

Comments (automatically disabled after 1 year)

Ramon Leon 6348 days ago

Of course, voodoo is used to optimize for performance reasons, I simply meant conceptually, it's not required.

chris r. 6348 days ago

While Smalltalk may be slightly more "pure" in that absolutely everything is method calls, I think Ruby is being more practical, making if/else and while special forms.

Does the Smalltalk syntax for if/else look any prettier than Ruby's? Not really. It's a bit more verbose and looks a bit strange compared to C-based languages. If/else, while, etc do fairly low-level magic and are frequently used. I think that's sufficient reason to make them special forms. Even Lisp has special forms, and it invented the programmable programming language concept.

And are you ever really going to replace the objects that control if or while et al. ? Doubtful, unless you're doing some weird sort of debugging. And in those cases, a nice debugger would probably be more effective.

On the blocks thing, yes, Ruby methods can only take one implicit block. But outside of if/else, while, or their ilk, how many methods take more than one block? Very few. Ruby isn't prematurely optimizing for multiple blocks becuase they aren't needed much. You can pass multiple blocks in Ruby, but it /will/ be uglier because you'll have to use a lambda. This is a reasonable compromise when 95% of the time, you'll only take one block.

Sacrificing a little purity for practicality is a good thing in my book. What next, make local var assignment a method call? (or is it already? I honestly haven't used Smalltalk in a while). Ruby isn't perfect though, and does have some notable flaws. But the aforementioned issues aren't them.

I totally agree with you about the continuations thing though. Ruby should definitely keep them.

Ignorant Bystander 6348 days ago

"I totally agree with you about the continuations thing though. Ruby should definitely keep them."

That's not the point. The point is that continuations were added to Squeak regardless of whether the original designers intended them to be there or not. Squeak is easily extentable by the end programmers.

Ramon Leon 6348 days ago

The Smalltalk syntax is prettier than Ruby's, because it's consistent and object oriented through and through. Yes, Smalltalk looks strange compared to C based languages, so does Lisp, but they're both better, C's just more popular.

In many ways, ruby is more practical, it's closer to the mainstream, but don't underestimate the power of purity. Lisp and Smalltalk both gain their considerable power, from the purity of their syntaxes.

How many methods take more than one block... well, when you "can" pass more than one block cleanly, a lot more than when you can't. They are needed, but you don't see them in Ruby, because it can't do it, that doesn't mean multiple blocks aren't a common use case in languages that support them.

Ruby isn't a programmable language in the same way Lisp or Smalltalk are, I'm not dissing Ruby, I'm just pointing out that the hype is a bit inflated, it could have been done better... and has, in Smalltalk.

Pete 6348 days ago

In ruby:

def true.ifTrue
  yield
end
def true.ifFale
  self
end
def false.ifTrue
  self
end
def false.ifFalse
  yield
end
(1 == 1).ifFalse {
  puts "Shouldn't get here!"
}.ifTrue {
  puts "All is good in the world!"
}

...but why would I want to do that when I have a nice, easily recognisable if/then/else, unless, etc syntactic construct?

I would take a page from the book of Lisp (and why more people don't use it) "purity is powerful, but ease of use trumps ease of implementation".

For another example of ease-of-use take a look at Haskell's 'do' notation. It is just sugar - but it sure is sweet the way it makes something "pure" (monads and sequencing) easier to work with.

P.S. I agree, many things are done better in Smalltalk - but many things are done better in Ruby - and I seem to favour the Ruby way (but you might like to see Rubinius - which seems an attempt to do ruby on the bluebook VM).

Ramon Leon 6348 days ago

That's my point, you wouldn't want to do this in Ruby, it'd be ugly, because Ruby makes it ugly.

Ruby's full of compromises that supposedly make it more practical, but I think it really makes it more complex, and I favor simplicity.

In comparison to Java or C#, Ruby is incredibly simple and concise, but compare Ruby's reserved words to Smalltalk's...

Ruby...

FILE, and, def, end, in, or, self, unless, LINE, begin, defined?, ensure, module, redo, super, until, BEGIN, break, do, false, next, rescue, then, when, END, case, else, for, nil, retry, true, while, alias, class, elsif, if, not, return, undef, yield

vs Smalltalk...

true, false, nil, self, super

Smalltalk pushes control structure into the library, where they belong, not in the language. New control structure can then be added anytime, without requiring a new VM. Ruby isn't more practical than Smalltalk in this regard, it's less practical. Lispers would say the same thing, and they're right as well.

The if/else/while constructs weren't the point, they were simply an example, meant to illustrate how Ruby isn't so good at doing domain specific languages. Ruby can't even handle the most common domain specific language of all, predicates. If it can't do that cleanly, I have little faith it could do something much more complex. Ruby is just a language, Smalltalk and Lisp are meta languages for building languages.

Göran Kramp] 6347 days ago

Hi!

I am a Smalltalker and haven't actually hacked any Ruby yet (though I do use rublog, for fun). But...

...a nice mentionable side effect of the Smalltalk way in this regard is that there actually have been new constructs added over the years, like ifNil:, ifEmpty:, ifNotNilDo: and various flavors and friends of those. And you don't need to be a Compiler hacker to do it, it is trivial.

So having the base construct being written in a way so that new similar constructs are also "first class" makes it much more suitable for "growing the language", IMHO. Inlining of certain common constructs for performance reasons does not change this fact.

Similar examples can be found in the iteration family of methods - I often add my own blablaDo: methods in my domain objects in order to make it easier and more accessible.

cheers, Göran]

Richard 6347 days ago

The unsupported argument that Ruby is being "practical" by treating predicates specially is just a bunch of crap. To see why, it's worthwhile to know the limits of Smalltalk's uniformity.

Smalltalk is not completely uniform, even ignoring the half-dozen bugs in the language. For one thing, variable assignments and returns are not messages. In Self, they are. Other things that could do with improvement include:

  • becoming homoiconic (eg, having macros) like Lisp
  • not having classes, just objects
  • storing code in ASTs, making syntax a tool convention
  • being able to inject live objects into dead code
  • having multiple names for classes

Most of these are clear winners. All but one, eliminating classes. Because as it turns out, if you turn classes into just another convention which the programmer is free to break, it becomes more difficult to write tools for the language. Classes are an extremely useful way to organize code and if you can't rely on their existence then things just become a whole lot more complicated.

There are plenty of cases where breaking uniformity provides some advantage. Smalltalk's special syntax for blocks (compared to Lisp's lambdas) allows the programmer to rapidly make an important distinction in code.

The point here is that none of these breaks in uniformity are justified by "it's practical". One doesn't need to fall back on generalities such as "it's practical" when there exist concrete reasons to do something. Either there exist concrete reasons why Ruby's predicates are special or it's all a bunch of crap.

Ramon Leon 6347 days ago

Exactly, there are things that are more practical in Ruby, scripting for example. Most Smalltalks require an image to run, Vista Smalltalk may change this for the windows platform.

Smalltalk isn't perfect, as Richard points out, there are things that aren't message sends, and features such as macros that aren't really compatible with Smalltalk's runtime image based nature.

Göran aslo makes some interesting points about ifNil:, ifEmpty:, ifNotNilDo: and freinds; Smalltalkers extend the language all the time, and often those things become idiomatic and even over time, voodoo'd by the VM for performance reasons.

It's nice to be able to do such things, the syntax is simply far more flexible than Ruby's mis-mash of Pearl/Python/Smalltalk/Lisp.

In Ruby's favor, it's pushed Smalltalk in new directions as well, its mixins prompted the creation of traits in Smalltalk. It's also generated a lot of interest in Smalltalk, having stolen its object model directly from Smalltalk, so Ruby has its uses. ;)]

Ramon Leon 6347 days ago

I said voodoo "can" be used, when something becomes enough of an idiom to make it worthwhile, but it's not required, ever.

If true and false weren't inlined by the compiler, it'd be very slow, but it'd run just fine. Most other control structures aren't optimized, ever, and are still perfectly usable and idiomatic.

Smalltalk at least gives you the option to build real control structures, Ruby doesn't.

Ramon Leon 6347 days ago

You'd have to ask a VM hacker. But who cares, that misses the point. Most control structures aren't optimized by the compiler, #ifTrue:ifFalse: is a special case because it's the most basic and most used of all control structures. The point is you can add your own "new" control structures whenever you like, and the code is syntactically identical to how #ifTrue:ifFalse: does it.

Lisp has the same capability, Ruby does not, or at least, Ruby can only partially do this, in some limited cases, which admittedly, covers most use cases you'd need to build a DSL.

schlenk 6347 days ago

Tcl also has 'if' not as part of the language syntax, leading to this fun discussion: http://wiki.tcl.tk/4821

and this one: http://wiki.tcl.tk/16892

Richard 6347 days ago

That brings up another irregularity in Smalltalk which I didn't want to go into. In Smalltalk it's not possible to use an expression or a variable as a standin for a function's name as evidently you can with TCL. It would be nicer to have parentheses imply evaluation than the current #perform: method.

Which brings up an interesting issue. The artificial regularity of having #perform: look like any other method even though it isn't is a kind of uniformity. It's uniformity of the rules of the language at the expense of uniformity of the principles of the language.

Another irregularity is that there are very different scoping rules for methods and objects. Methods are looked up in the class hierarchy while objects are looked up in namespaces. That's the price you pay for having classes. At least this disjunction explains why you can't use a variable as a standin for a function.

Ramon Leon 6347 days ago

Can you show a sample of what you'd prefer for evaluation over #perform:? I don't exactly find that a wrinkle, being a message send taking a symbol, it certainly fits the paradigm of the language.

Not all Smalltalk's have namespaces, let's not overgeneralize. Class names are global in Squeak, as they were in Smalltalk-80.

Ramon Leon 6346 days ago

No, you're still misinterpreting what I'm saying. You're too hung up on the #ifTrue:ifFalse: example. It's just an example, here, try another. Make up another DSL, say one for blogging, have a method called

aComment 
     ifSpam: [aBlog blackList: aComment author]
     ifNotSpam: [aPost publish: aComment].

See... #ifSpam:ifNotSpam:, same syntax style as built in #ifTrue:ifFalse:, you the programmer can make up your own mini language that works for "YOU". The compiler writers could later choose to optimize this, if it ever became so popular is needed to be part of the base language, like #ifTrue:ifFalse:.

So one last time, I'm not talking about #ifTrue:ifFalse:, I'm just using it as an example of a common mini language, because it's the smallest one I could think of that every programmer knows.

Stop trying to be "right" and start trying to understand what I'm saying, I'm starting to think you're misunderstanding me on purpose.

Ramon Leon 6346 days ago

Sure, it's possible, sorry, not trying to place any blame, just seemed you kept hammering on something that wasn't relevant.

I chose #ifTrue:ifFalse: precisely because Ruby does it without using its own facilities for building DSL's, making it a great case of Ruby's lack of consistency with itself.

Smalltalk DSL's look just like Smalltalk; Ruby DSL's look nothing like Ruby, that's an important thing to notice.

Ramon Leon 6346 days ago

I'm not insisting that Ruby should mimic Smalltalk at all, and I think you just made my point for me. Can you make an embedded DSL in Ruby that looks like Ruby's if, I don't think so, but if I'm wrong, please show me.

Also note, that by not doing it like Smalltalk, and placing the if first, it'd no longer be polymorphic (unless Ruby has multiple dispatch aka Lisp, but I don't think it does), which may or may not be important, just something to note about the Smalltalk version. In the Smalltalk version, #ifSpam might use different algorithms for different receivers, maybe an e-mail is spammed differently than a blog post, who knows.

Ramon Leon 6346 days ago

I don't need to make better arguments, I made my point just fine. If you disagree, then so be it.

I'm a Ruby programmer, at least a bit, I use it for unit testing my web apps, and as far as I know, you can't make a native looking "if" like control structure of your own. If you know otherwise, show me.

As for the polymorphism, I clearly stated "which may or may not be important, just something to note", so please don't rebut it like you're making some point I didn't already address. You seem intent on misunderstanding, misinterpreting, or simply disagreeing with everything I say, whether true or not, the conversation is no long enjoyable, so I'm done.

John DeHope 6327 days ago

Focusing in on reproducing predicate logic in-language for a moment... Isn't it a given that a procedural language (as opposed to a functional one) must have at least "if" implemented as part of the core language itself? I played around with some magic syntax a bit and I could not imagine how to represent an "if" statement without a functional language. Once you have "if" you can get everything else I've ever come across (for, while, switch...) but it seems to me that you must have "if" from the beginning to get anywhere.

Ramon Leon 6327 days ago

Yes, but we're talking about a functional/object oriented implementation here, not a procedural one. Smalltalk has no procedural constructs, just objects. It's basically doing everything with lambdas, functional style. Ruby uses procedural constructs, this is what I'm complaining about, it mixes styles, one way for built in stuff, another for your own DSLs.

Dave Newton 6327 days ago

Re: multi-dispatch; there's an implementation available via gems called 'multi'. I haven't used it yet, but at first glance it looked cute. Not quite as elegant as other implementations for the obvious reasons, but still cute :)

Dave Newton 6327 days ago

Forgot links: http://multi.rubyforge.org http://multi.rubyforge.org/img5.html shows what it looks like.

Jason Watkins 6327 days ago

"The main thing to note here, beside the beauty of Smalltalk, is that blocks, objects, and methods calls are the necessary building blocks of "language" itself, any language."

The authoritative tone of your article is at odds with over-reaching you do in statements like this.

SKI combinators. Lambda. Self-Calculus. Rho-Calculus. Concatinative Combinators. There are many possible foundations for computational languages. Most of them do not have anything resembling objects, methods, or blocks. By your reasoning we should not call these languages, since they lack the necessary building blocks. Absurd.

Even a passing familiarity with computer science would inform you of this and guide you away from such a broad claim.

I feel like I could have enjoyed the topic of your post, but as it is, it's too drowned in sophistry.

Ramon Leon 6327 days ago

You misinterpret what I'm saying, that wasn't an exclusionary statement, I didn't say it was the only possible foundation for a language. I simply meant any language you want to make up with Lambda's, which is what Smalltalk DSL's are made from.

Blocks are just Lambda's, well, they're more than that, but they're used just like Lambda's and serve the same role within Smalltalk. I made no broad claims nor do I pretend to be an authority on such matters, as with all things on this site, these are just my current opinions and understandings.

Jason Watkins 6327 days ago

"I simply meant any language you want to make up with Lambda's"

So objects and methods are necessary in any language you want to make up with lambdas?

Ramon Leon 6327 days ago

No, of course not, again, you need to consider the context in which I'm writing, Smalltalk. In Smalltalk, when creating a domain specific langauge, objects(lambda, aka block, being an object) and methods are all that are necessary to create any language you wish... I'm not making some grand statement on computer science here dude, this isn't LTU, this is my blog, keep that in mind.

Scott Fleckenstein 6327 days ago

"you can't make a native looking "if'" like control structure of your own. If you know otherwise, show me."

Why would you need to, you already have an if. You have not presented any example of control structures where they are needed.

Reading the comments we see the following: ifNil:, ifEmpty:, ifNotNilDo:, ifSpam:, and ifNotSpam:

Each one of those can be just as easily implemented such that

if object.nil? #which you already have if object.empty? #which arrays have (use .any? for enumerables*) unless object.nil? #also, already there if object.spam? unless object.spam?

*yes, I know .any? doesn't have the same exact semantics as empty? with regard to nils

I see no case presented where you couldn't simply do:

def Object.spam? false end

and then override the implementation where you need to to get real spam detection.

The whole article is useless, you provide no justifications for why it is better. Just because you can do something doesn't mean it should be done. Tell us why again control structures should be in the library?

Edoc 6326 days ago

Not to go OT, but the REBOL language supports DSLs in a way that might satisfy the author. REBOL makes heavy use of blocks, and there are no keywords in the language. It's a bit like Scheme and Forth, with influences from Smalltalk.

A Dr. Dobb's article illustrates the basics, including DSLs: http://www.ddj.com/184404172

To make robust DSL's REBOL makes use of grammars-based parsing. For more on that, see http://www.REBOL.com for docs, or:

http://en.wikibooks.org/wiki/REBOLProgramming/LanguageFeatures/Parse

Ramon Leon 6326 days ago

Scott, control structures should be in the library because compiler writers aren't omnipotent and can't foresee every possible future need.

You obviously prefer to program "in" a language, rather than "on" a language; good for you, but I subscribe to a different school of thought. I want to work a in malleable language that can be brought closer to the problem domain in order for the code to get simpler.

Paul Graham has a good simple example in his book On Lisp...

(defmacro aif (test-form then-form &optional else-form)
  `(let ((it ,test-form))
     (if it ,then-form ,else-form)))

Where he adds a new anaphoric if that evaluates an expression, and if the output is not null, introduces a new variable binding called "it" into the scope of an if, greatly simplifying that common pattern of code.

Minimal languages such as Lisp and Smalltalk that allow you to extend their control structures via the library are simply obviously better than those that reserve such power to the compiler writer. If you don't see the value in such abilities, so be it, to each his own. I however, see obvious value in such and think no further explanation is necessary.

shev 6322 days ago

You mentioned that Ruby is hyped, and that this hype is unfair.

I will tell you that the only real thing that was hyped is Ruby on Rails.

Ruby however is not. It has built its reputation exactly for its clean syntax. Something which Smalltalk isnt famous for. And the same goes for DSL, which usually, are cleaner than the underlying language.

Ramon Leon 6321 days ago

Ruby... clean syntax, lol. Ruby's OK, but Smalltalk is far more famous for it's clean syntax, if by clean you mean simple. Ruby's more popular, no doubt, and has a more familiar syntax from a mainstream point of view, but Smalltalk kicks its ass on syntax, easily. Ruby's syntax is horribly complex in comparison.

aguillen 6311 days ago

LISP > SMALLTALK > RUBY

We all know that! Still, Ruby is much nicer than other mainstream languages. If it weren't for Ruby I would have never learned Lisp... So... we're getting there...

Kan 6271 days ago

Hi, just surfed in. I enjoyed looking around your web site. This site has been very useful to me so far and I have barely scrathed the surface of it.

morganusvitus 6192 days ago

The site looks great ! Thanks for all your help ( past, present and future !)

alex 6184 days ago

hi nice site.

 6174 days ago

You have a good site, i enjoyed my stay!

Alex 6172 days ago

Thank You

she 5992 days ago

I fail to see how the smalltalk if/else is looking better than ruby.

How is this beautiful?

"False>>ifFalse: falseAlternativeBlock ifTrue: trueAlternativeBlock ^falseAlternativeBlock value"

You say, we should not underestimate the power of purity.

I say, let's not underestimate the beauty of the underlying syntax.

(And btw I dont want to use a GUI when I instead can use text. Ruby is the challengor to Perl, not to Smalltalk. Let the smalltalkers do all their GUI work they want to. And smalltalk has thousand warts built upon the core, how is it that one-file-per-method and one-dir-per-class? This SUCKS. In this case I would rather want to use a prototype-based language with a good syntax and go away with the forced class OOP thinking instead, if someone chooses to enforce such rigid rules without real clear advantages - my source files are highly ordered in a way I chose fit)

Ramon Leon 5992 days ago

It's simple, the Ruby if/else is special syntax you can't duplicate, the Smalltalk if/else is a polymorphic method call that looks just like every other method call in the system, something you can duplicate.

You can't extend Ruby and keep the same syntax as Ruby itself, that sucks. There is no one file per method and one directory per class, there are no files, you clearly don't really grok Smalltalk yet, all those things you're griping about are features. Smalltalk is a very clean language where everything is consistent, Ruby is full of warts and exceptions for no good reason.

But if you like Ruby, use it. Use your text editor to edit your dead files, I'll continue to use my browser to edit live classes, files suck. I won't give up dynamic typing AND refactoring support, only one of which you have in Ruby, and it's precisely because it still uses files.

naisioxerloro 5955 days ago

Hi. Good design, who make it?

S. Potter 5845 days ago

@chrisr This is rather late, but I did just want to point out that Ruby is keeping continuations in 1.9 and 2.x going forward. I am not sure if this was under discussion when you made the comment or if you misunderstood the author's point about continuations in the blog post content?

Anyway Ramon, thank you for your piece. Conceptually I completely agree with you, but pragmatically I go with the languages that I can bare to develop in at the time that have good traction and momentum. Unfortunately Smalltalk has neither currently except in a microcosm of the programming world.

Many good points for thought, which is greatly appreciated by this evolving Rubyist.

Ramon Leon 5845 days ago

I agree with you about Ruby being more pragmatic, and that's certainly a good reason to choose it. Smalltalk however, is much more fun, and for those of us who do have the option to use it, pragmatism be damed, I'm going for the fun!

Jimmie Houchin 5827 days ago

Personally, I think it depends greatly on how you define pragmatic or practical.

For me a lone developer. I am very familiar with the tools available to me with Squeak. I can search, discover and find code. I have a history of all of my code. I have elegant version control with Monticello. Any time I even consider using something else because it is pragmatic. I have to think long and hard about all of the things I do within Squeak that I would have to find replacement tools and learn in those "pragmatic" languages.

I would have to choose an IDE or editor. I would have to choose a version control system and potentially have to learn several at least to a certain point, depending on what projects I want to use or contribute to. I would have to learn the pragmatic language. I would have to learn the tools for which I am choosing said pragmatic language, ie: Rails, etc. I would have to learn the debugging tools for said language and environments. I would have to learn how to search for the code I need to accomplish whatever task is before me. And these are just the simple things off of the top of my head that I am aware of. The list could easily grow larger.

For the legions of people who have already done all of the above and settled upon answers for these things, then yes, Ruby, Python, etc. can be the pragmatic choice.

But if you haven't yet invested significant time in the above scenario. Then Squeak/Smalltalk could be a most excellent and pragmatic choice. And even if you have invested significant time in all of the above for your current pragmatic language. Squeak/Smalltalk can still be an excellent and pragmatic choice. All of the above is so elegantly a part of the Squeak/Smalltalk development environment that it is so very productive if you will spend the modest amount of time to learn it. I believe that once you do, you are amply rewarded with a very productive experience.

Basically, just wanted to add that the definition of pragmatic must be that of the individual. And that no single language has that defined for every situation or person.

Squeak/Smalltalk is a very enabling experience. And one you can enjoy the journey. :)

Ramon Leon 5827 days ago

Well said!

about me|good books|popular posts|atom|rss