STXJavaScriptLanguage.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 24 Sep 2013 23:18:24 +0200
branchinitialV
changeset 1180 01c6be61f29c
parent 607 fba974a1ddd8
child 774 36a47ada858c
permissions -rw-r--r--
checkin from stx browser

"
 COPYRIGHT (c) 2009 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libjavascript' }"

ProgrammingLanguage subclass:#STXJavaScriptLanguage
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Kernel-Languages'
!

!STXJavaScriptLanguage class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2009 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    provide info about which tools are to be used for the
    embedded JavaScript-like language in Smalltalk (not a real JavaScript,
    that's why it's called STXJavaScript)
"
! !

!STXJavaScriptLanguage methodsFor:'accessing'!

name
    "Answers a human-readable name of myself:
     'Smalltalk' for SmalltalkLanguage,
     'Ruby' for RubyLanguage..."

    ^ 'JavaScript'
!

sourceFileSuffix
    "Answers a default suffix for source files, i.e.
     'st' for Smalltalk, 'js' for JavaScript or 'rb' for Ruby'"

    ^ 'js'
! !

!STXJavaScriptLanguage methodsFor:'accessing - classes'!

codeGeneratorClass
    "Answers a class that can generate code"

    ^ JavaScriptCodeGeneratorTool

    "Created: / 30-01-2011 / 15:19:48 / cg"
!

compilerClass
    "Answer a class suitable for compiling a source code in 'my' language"

    ^ Smalltalk::JavaScriptCompiler
!

compilerWithBreakpointSupportClass
    "Answer a class suitable for compiling a source code with breakpoints
     in 'my' language"

    ^ Smalltalk::JavaScriptCompilerWithBreakpointSupport

    "Created: / 22-07-2013 / 15:46:39 / cg"
!

evaluatorClass
    "Answer a class suitable for doit evaluation in 'my' language"

    ^Smalltalk::JavaScriptParser
!

explainerClass
    "Answers a class used by browser and debugger to
     show some hints about the code. It is OK to return
     nil, which means that there is no explainer for given
     language.
    "

    "return nil by default"
    ^Explainer

    "Created: / 21-08-2009 / 08:49:29 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

metaClass
    "will be used for new classes (in the class wizard)"

    ^ JavaScriptMetaclass

    "Modified: / 30-01-2011 / 10:06:16 / cg"
!

parserClass
    "Answer a class suitable for parsing a source code in 'my' language"

    ^Smalltalk::JavaScriptParser
!

sourceFileReaderClass
    "Answers a class that can be used for
     reading & compiling source files"

    ^ JavaScriptSourceReader
!

sourceFileWriterClass
    "Answers a class is used for source file writing (i.e. file-out)"

    ^ JavaScriptSourceFileWriter
!

syntaxHighlighterClass
    "return the class to use for syntaxHighlighting (prettyPrinting) this class -
     this can be redefined in special classes, to highlight classes with
     Lisp, Prolog, ASN1, Basic :-) or whatever syntax."

    ^ Smalltalk::JavaScriptSyntaxHighlighter
! !

!STXJavaScriptLanguage methodsFor:'source queries'!

methodDefinitionTemplateForSelector:aSelector andArgumentNames:argNames
    "given a selector, return a prototype definition string"

    aSelector numArgs > 0 ifTrue:[
        aSelector isKeyword ifTrue:[
            ^ String streamContents:[:stream |
                stream nextPutAll:'function '.
                stream nextPutAll:(aSelector copyReplaceAll:$: with:$_).
                stream nextPutAll:'('.
                argNames 
                    do:[:eachArgName|
                        stream nextPutAll:eachArgName.
                    ]
                    separatedBy:[
                        stream nextPutAll:', '.
                    ].
                stream nextPutAll:')'.
             ].
        ].
        ^ 'function operator(',aSelector,') (',(argNames at:1),')'
    ].
    ^ 'function ',aSelector,'()'

    "
     STXJavaScriptLanguage instance 
        methodDefinitionTemplateForSelector:#foo andArgumentNames:#()

     STXJavaScriptLanguage instance
        methodDefinitionTemplateForSelector:#+ andArgumentNames:#('aNumber')

     STXJavaScriptLanguage instance
        methodDefinitionTemplateForSelector:#foo:bar:baz: andArgumentNames:#('fooArg' 'barArg' 'bazArg')
    "
! !

!STXJavaScriptLanguage methodsFor:'testing'!

isSTXJavaScript
    "true iff this is the ST/X-javascript language"

    ^ true
! !

!STXJavaScriptLanguage class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !