ProgrammingLanguage.st
author Claus Gittinger <cg@exept.de>
Tue, 29 Sep 2009 22:07:17 +0200
changeset 12048 03f10902431c
parent 12012 a1294c2b4026
child 12056 6342579137b7
permissions -rw-r--r--
added: #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.
"
"{ Package: 'stx:libbasic' }"

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

ProgrammingLanguage class instanceVariableNames:'Instance'

"
 No other class instance variables are inherited by this class.
"
!

!ProgrammingLanguage 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.
"
! !

!ProgrammingLanguage class methodsFor:'initialization'!

initialize

     LanguageQuerySignal := 
            QuerySignal new
                nameClass:self message:#languageQuerySignal;
                notifierString:'asking for current language';
                handlerBlock:[:ex | ex proceedWith:SmalltalkLanguage instance].

    "Created: / 12-08-2009 / 14:56:11 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 16-08-2009 / 10:36:11 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ProgrammingLanguage class methodsFor:'instance creation'!

forFile: aFilename 
    "
     Answers a language for given source file. If none is found,
     SmalltalkLanguage is returned (to provide backward compatibility)"
    
    ^ self instancesDetect: [:each | each canReadSourceFile: aFilename ]
        ifNone: [ SmalltalkLanguage instance ]

    "Created: / 16-08-2009 / 10:08:44 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

forStream: aStream 
    "
     Answers a language for given source stream. If none is found,
     SmalltalkLanguage is returned (to provide backward compatibility)"
    
    aStream isFileStream ifFalse: [ ^ SmalltalkLanguage instance ].
    ^ self forFile: aStream fileName

    "Created: / 16-08-2009 / 10:56:26 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

named: aString 
    ^ self 
        instancesDetect:[:each | each name = aString ]
        ifNone: [ self error: 'No language named ' , aString ].

    "
        ProgrammingLanguage named: 'Smalltalk'

        ProgrammingLanguage named: 'Ruby'"

    "Created: / 15-08-2009 / 22:40:26 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 16-08-2009 / 10:58:01 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

named: aString ifNone: aBlock
    ^ self 
        instancesDetect:[:each | each name = aString ]
        ifNone: aBlock

    "Created: / 21-08-2009 / 13:07:10 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ProgrammingLanguage class methodsFor:'Signal constants'!

languageQuerySignal

    ^LanguageQuerySignal

    "Created: / 12-08-2009 / 14:57:07 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ProgrammingLanguage class methodsFor:'accessing'!

all
    "
    Anwers a collection of all available languages
    "        

    ^self allSubclasses collect:[:each|each instance]


    "
        ProgrammingLanguage all
    "

    "Created: / 16-08-2009 / 13:43:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

current

    "
        ProgrammingLanguage current
    "


    ^LanguageQuerySignal query

    "Created: / 12-08-2009 / 15:02:59 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

instance

    Instance ifNil:[Instance := self new].
    ^Instance

    "Created: / 16-08-2009 / 10:36:37 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ProgrammingLanguage class methodsFor:'enumerating'!

allDo: aBlock

    ^self allSubclassesDo:
        [:each|aBlock value: each instance]

    "Created: / 16-08-2009 / 14:07:40 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ProgrammingLanguage class methodsFor:'private'!

instancesDetect: detectBlock ifNone: failBlock


    self allSubclasses 
        do:[:cls|(detectBlock value: cls instance) ifTrue:[^cls instance]].
    ^failBlock value

    "Created: / 16-08-2009 / 10:57:32 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ProgrammingLanguage class methodsFor:'testing'!

isAvailable: langName

    self instancesDetect: [:lang|lang name = langName] ifNone: [^false].
    ^true

    "
        ProgrammingLanguage isAvailable: 'Smalltalk' 
        ProgrammingLanguage isAvailable: 'Ruby'  
        ProgrammingLanguage isAvailable: 'Haskell'   
    "

    "Created: / 21-08-2009 / 12:56:32 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ProgrammingLanguage methodsFor:'accessing'!

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

    ^ self subclassResponsibility

    "Created: / 15-08-2009 / 22:38:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 16-08-2009 / 10:47:21 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

sourceFileSuffix

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

    ^self subclassResponsibility

    "Created: / 16-08-2009 / 10:42:40 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ProgrammingLanguage methodsFor:'accessing - classes'!

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

    ^self subclassResponsibility

    "Created: / 21-08-2009 / 13:00:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

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"
    ^nil

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

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

    ^self subclassResponsibility

    "Created: / 21-08-2009 / 13:00:30 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

sourceFileReaderClass

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

    ^self subclassResponsibility

    "Created: / 16-08-2009 / 09:00:23 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

sourceFileWriterClass

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

    ^self subclassResponsibility

    "Created: / 16-08-2009 / 09:40:19 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ProgrammingLanguage methodsFor:'printing & storing'!

storeOn:aStream

    self class == ProgrammingLanguage 
        ifTrue:
            [super storeOn:aStream]
        ifFalse:
            [aStream 
                nextPutAll:'ProgrammingLanguage';
                nextPutAll:' named: ';
                nextPutAll:self name storeString].

    "
        ProgrammingLanguage instance storeString  

        SmalltalkLanguage instance storeString 
    "

    "Created: / 16-08-2009 / 10:52:28 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ProgrammingLanguage methodsFor:'queries'!

canReadSourceFile: aFilename
    "
    Answers true iff file contains source code
    in 'my' language        
    "

    "Trivial implementation here, to be overriden by
     subclasses"

    ^aFilename suffix = self sourceFileSuffix

    "Created: / 16-08-2009 / 10:10:33 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ProgrammingLanguage methodsFor:'testing'!

isSmalltalk

    ^false

    "Created: / 16-08-2009 / 09:01:27 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ProgrammingLanguage methodsFor:'utilities - file in/file out'!

fileIn: aFilename

    ^self sourceFileReaderClass fileIn: aFilename

    "Created: / 16-08-2009 / 13:28:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

fileInStream: aStream

    ^self sourceFileReaderClass fileInStream: aStream

    "Created: / 16-08-2009 / 11:05:46 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ProgrammingLanguage methodsFor:'utilities - source code'!

writeComment: aStringOrStringCollection on: aStream 
    "
        Utility method - writes a comment to a stream
        using proper syntax"
    
    ^ self sourceFileWriterClass new fileOutComment: aStringOrStringCollection
        on: aStream

    "Created: / 21-08-2009 / 09:35:07 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!ProgrammingLanguage class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/ProgrammingLanguage.st,v 1.3 2009-09-29 20:07:17 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic/ProgrammingLanguage.st,v 1.3 2009-09-29 20:07:17 cg Exp $'
!

version_SVN
    ^'Id: ProgrammingLanguage.st,v 1.2 2009/09/23 12:23:35 fm Exp '
! !

ProgrammingLanguage initialize!