ProjectDefinition.st
author Claus Gittinger <cg@exept.de>
Thu, 17 Aug 2006 17:24:39 +0200
changeset 9569 b0bf179c9bf5
parent 9559 06e8b0498471
child 9575 353ef8cc798f
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 2006 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:libbasic3' }"

Object subclass:#ProjectDefinition
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'System-Support-Projects'
!

!ProjectDefinition class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2006 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.
"
! !

!ProjectDefinition class methodsFor:'instance creation'!

newForPackage:packageID
    ^ self 
        newNamed:(self initialClassNameForDefinitionOf:packageID) 
        package:packageID.

    "Created: / 11-08-2006 / 14:27:19 / cg"
!

newNamed:newName package:packageID
    |newClass|

    "/ for now, we are strict.
    self assert:(self initialClassNameForDefinitionOf:packageID) = newName.
    self assert:(self ~~ ProjectDefinition).  "ProjectDefinition is abstract"

    newClass := self
                    subclass:(newName asSymbol)
                    instanceVariableNames:''
                    classVariableNames:''
                    poolDictionaries:''
                    category:(self defaultCategory).

    newClass package:packageID asSymbol.
    ^ newClass

    "Created: / 09-08-2006 / 17:57:37 / fm"
    "Modified: / 09-08-2006 / 19:27:53 / fm"
    "Modified: / 17-08-2006 / 17:24:23 / cg"
! !

!ProjectDefinition class methodsFor:'accessing'!

defaultCategory
    ^'* Projects *'

    "Created: / 11-08-2006 / 14:16:49 / cg"
!

initialClassNameForDefinitionOf:aPackageId
    |s|

    s := aPackageId asString copy replaceAny:':/' with:$_.
    (s endsWith:$_) ifTrue:[
        s := s copyWithoutLast:1
    ].
    ^ s

"
   DapasXProject initialClassNameForDefinitionOf:'bosch:dapasx/interactiver_editor' 
   DapasXProject initialClassNameForDefinitionOf:'stx:libbasic' 
   DapasXProject initialClassNameForDefinitionOf:'stx:goodies/xml' 
"

    "Created: / 09-08-2006 / 17:44:47 / fm"
    "Modified: / 11-08-2006 / 14:00:05 / cg"
!

libraryName
    ^ self libraryNameFor:self package

    "
       bosch_dapasx_datenbasis_Definition libraryName
    "

    "Modified: / 09-08-2006 / 18:20:29 / fm"
    "Modified: / 17-08-2006 / 14:13:14 / cg"
!

libraryNameFor:aProjectID 
    ^ aProjectID asString copy replaceAny:':/' with:$_

    "
       bosch_dapasx_datenbasis libraryName
    "

    "Modified: / 09-08-2006 / 18:20:29 / fm"
    "Modified: / 17-08-2006 / 14:13:21 / cg"
!

module
    ^ self moduleOfClass:self

    "
       bosch_dapasx_datenbasis_Definition module
       DapasX_Datenbasis module
    "

    "Created: / 08-08-2006 / 20:24:53 / fm"
    "Modified: / 09-08-2006 / 16:16:37 / fm"
    "Modified: / 17-08-2006 / 14:13:28 / cg"
!

moduleDirectory
    ^ self moduleDirectoryFor:self package

    "
        bosch_dapasx_datenbasis_Definition moduleDirectory
        bosch_dapasx_parameter_system_Definition moduleDirectory
    "

    "Created: / 08-08-2006 / 20:25:39 / fm"
    "Modified: / 17-08-2006 / 14:13:36 / cg"
!

moduleDirectoryFor:aProjectID 
    ^ (aProjectID subStrings:$:) last

    "
        bosch_dapasx_datenbasis_Definition moduleDirectory
        bosch_dapasx_parameter_system_Definition moduleDirectory
    "

    "Created: / 08-08-2006 / 20:25:39 / fm"
    "Modified: / 17-08-2006 / 14:13:41 / cg"
!

moduleFor:aProjectID 
    ^ (aProjectID subStrings:$:) first

    "
       DapasXProject module
       DapasX_Datenbasis module
    "

    "Created: / 09-08-2006 / 16:16:16 / fm"
    "Modified: / 17-08-2006 / 14:13:46 / cg"
!

moduleOfClass:aClass 
    ^ self moduleFor:aClass package

    "
       DapasXProject module
       DapasX_Datenbasis module
    "

    "Created: / 09-08-2006 / 16:16:16 / fm"
    "Modified: / 17-08-2006 / 14:13:51 / cg"
!

msdosPathToPackage:aPackageID 
    "Returns the path to the package defined by aPackageID relative to my path"
    
    ^ self msdosPathToTop , '\..\' , (self msdosTopRelativePathToPackage:aPackageID)

    "
     self msdosPathToPackage:'bosch:dapasx/kernel'
    "

    "Created: / 09-08-2006 / 16:35:22 / fm"
    "Modified: / 17-08-2006 / 14:21:53 / cg"
!

msdosPathToPackage:toPackageID from:fromPackageID
    "Returns the path to the package defined by aPackageID relative to my path"
    
    ^ (self msdosPathToTopFor:fromPackageID) , '\..\' , (self msdosTopRelativePathToPackage:toPackageID)

    "
     self msdosPathToPackage:'bosch:dapasx/kernel' from:'bosch:dapasx/application'
    "

    "Created: / 17-08-2006 / 14:26:39 / cg"
!

msdosPathToTop
    "Returns the path to stx counting the number of $/ and $: in the package name and adding for each one '../' to get the ST/X top directory"

    ^self msdosPathToTopFor: self package 

    "
     bosch_dapasx_datenbasis_Definition msdosPathToTop    
     DapasX_Datenbasis pathToTop  
    "

    "Created: / 09-08-2006 / 15:45:54 / fm"
    "Modified: / 17-08-2006 / 14:25:28 / cg"
!

msdosPathToTopFor: aProjectID
    "Returns the path to stx counting the number of $/ and $: in the package name and adding for each one '../' to get the ST/X top directory"

    ^ (((1 to:(aProjectID asCollectionOfSubstringsSeparatedByAny:':/') size)
            collect:[:n | '..\']) asStringWith:'') , 'stx'    

    "
     self msdosPathToTopFor: #'bosch:dapasx/datenbasis'   
    "

    "Created: / 09-08-2006 / 15:45:54 / fm"
    "Modified: / 17-08-2006 / 14:25:18 / cg"
!

msdosTopRelativePathToPackage:aPackageID 
    "Returns the path to the package as specified by aPackageID relative to the top directory"
    
    ^ aPackageID asString copy replaceAny:':/' with:$\

    "
     self msdosTopRelativePathToPackage:'stx:goodies/xml'
     self msdosTopRelativePathToPackage:'bosch:dapasx/kernel'
    "

    "Created: / 17-08-2006 / 14:20:44 / cg"
!

packageName

^self packageNameFor: self package


"
   bosch_dapasx_hw_schnittstellen_Definition  packageName
   bosch_dapasx_datenbasis_Definition packageName
   bosch_dapasx_parameter_system_Definition packageName
"

    "Created: / 08-08-2006 / 20:24:53 / fm"
    "Modified: / 09-08-2006 / 16:16:37 / fm"
!

packageNameFor: aProjectID

^((aProjectID asString copy replaceAny:'/' with:$:) subStrings: $:) last


"
   bosch_dapasx_hw_schnittstellen  packageName
   bosch_dapasx_datenbasis packageName
   bosch_dapasx_parameter_system packageName
"

    "Created: / 08-08-2006 / 20:24:53 / fm"
    "Modified: / 09-08-2006 / 16:16:37 / fm"
    "Modified: / 11-08-2006 / 14:02:32 / cg"
!

parentProject

    ^(self parentProjectFor: self package)

"
    bosch_dapasx_hw_schnittstellen_Definition  parentProject
    DapasX_Datenbasis parentProject
"

    "Created: / 07-08-2006 / 20:18:27 / fm"
    "Modified: / 08-08-2006 / 10:47:37 / fm"
!

parentProjectFor: aProjectID

    ^(aProjectID subStrings: $/) first

"
    bosch_dapasx_hw_schnittstellen  parentProject
"

    "Created: / 07-08-2006 / 20:18:27 / fm"
    "Modified: / 08-08-2006 / 10:47:37 / fm"
    "Modified: / 11-08-2006 / 14:02:56 / cg"
!

requiredProjects

^self preRequisites, self subProjects
!

topRelativeMsdosPathToPackage:aPackageID 
    "Returns the path to the package as specified by aPackageID relative to the top directory"
    
    ^ aPackageID asString copy replaceAny:':/' with:$\

    "
     self topRelativePathToPackage:'stx:goodies/xml'
     self topRelativePathToPackage:'bosch:dapasx/kernel'
    "

    "Created: / 17-08-2006 / 14:16:28 / cg"
!

unixPathToPackage:aPackageID
    "Returns the path to stx counting the number of $/ and $: in the package name and adding for each one '../' to get the ST/X top directory"

    ^ self unixPathToTop , '/../' , (self unixTopRelativePathToPackage:aPackageID)

    "
     bosch_dapasx_kernel unixPathToPackage:'bosch:dapasx/kernel'
    "

    "Created: / 09-08-2006 / 16:35:22 / fm"
    "Modified: / 16-08-2006 / 18:55:41 / User"
    "Modified: / 17-08-2006 / 14:20:28 / cg"
!

unixPathToTop
    "Returns the path to stx counting the number of $/ and $: in the package name and adding for each one '../' to get the ST/X top directory"

    ^ (((1 to:(self package asCollectionOfSubstringsSeparatedByAny:':/') size)
        collect:[:n | '../']) asStringWith:'') , 'stx'    

    "
     bosch_dapasx_kernel unixPathToTop        
     stx_goodies_xml unixPathToTop  
    "

    "Created: / 09-08-2006 / 15:45:54 / fm"
    "Modified: / 17-08-2006 / 14:17:59 / cg"
!

unixTopRelativePathToPackage:aPackageID 
    "Returns the path to the package as specified by aPackageID relative to the top directory"
    
    ^ aPackageID asString copy replaceAny:':/' with:$/

    "
     self unixTopRelativePathToPackage:'stx:goodies/xml'
     self unixTopRelativePathToPackage:'bosch:dapasx/kernel'
    "

    "Created: / 17-08-2006 / 14:20:18 / cg"
! !

!ProjectDefinition class methodsFor:'defaults'!

defaultDescription
    ^ 'description'
! !

!ProjectDefinition class methodsFor:'description'!

autoloaded_classNames
    "classes listed here will NOT be compiled, but remain autoloaded.
     (i.e. excluded from the build process). Can be user-defined in my subclasses"

    ^#()

    "Created: / 07-08-2006 / 19:02:57 / fm"
    "Modified: / 07-08-2006 / 21:25:25 / fm"
    "Modified: / 17-08-2006 / 08:48:13 / cg"
!

classNames            
    "this is a stupid default, a correponding method with real names
     is generated in my subclasses"

    ^#()

    "Created: / 07-08-2006 / 19:02:57 / fm"
    "Modified: / 07-08-2006 / 21:25:25 / fm"
!

compiled_classNames          
    "this is a stupid default, a correponding method with real names
     is generated in my subclasses"

    ^#()

    "Created: / 07-08-2006 / 19:02:57 / fm"
    "Modified: / 07-08-2006 / 21:25:25 / fm"
!

compiled_classes
    ^ self compiled_classNames collect:[:eachName| (Smalltalk at:eachName asSymbol)]

    "Created: / 09-08-2006 / 16:28:15 / fm"
    "Modified: / 09-08-2006 / 18:02:28 / fm"
!

compiled_classesDo:aBlock
    self compiled_classes do:aBlock.

    "Created: / 09-08-2006 / 16:28:15 / fm"
    "Modified: / 09-08-2006 / 18:02:28 / fm"
!

description
"Returns a description string which will appear in nt.def and in the files info inside it's properties "

^''

    "Created: / 08-08-2006 / 11:15:01 / fm"
!

excluded_classNames
    "this is a stupid default, a correponding method with real names
     to be excluded from the build process can be user-defined in my subclasses"

    ^#()

    "Created: / 07-08-2006 / 19:02:57 / fm"
    "Modified: / 07-08-2006 / 21:25:25 / fm"
!

extensionMethodNames

    ^#()

    "Created: / 08-08-2006 / 11:07:08 / fm"
!

postLoadAction
    "raise an error: must be redefined in concrete subclass(es)"

    ^ self subclassResponsibility

    "Created: / 08-08-2006 / 11:07:40 / fm"
!

preUnloadAction
    "raise an error: must be redefined in concrete subclass(es)"

    ^ self subclassResponsibility

    "Created: / 08-08-2006 / 11:07:40 / fm"
!

prerequisiteProjects

    ^#()

    "Created: / 08-08-2006 / 21:17:34 / fm"
!

subProjects

    ^#()

    "Created: / 08-08-2006 / 11:08:23 / fm"
!

versionNumber
"Returns a version string which will appear in nt.def and in the files info inside it's properties "

^''

    "Created: / 08-08-2006 / 11:35:52 / fm"
! !

!ProjectDefinition class methodsFor:'file generation'!

allClassNames
    ^ (self compiled_classNames , self autoloaded_classNames , self excluded_classNames)
!

fileNamesToGenerate
    self subclassResponsibility
!

forEachFileNameAndGeneratedContentsDo:aTwoArgBlock 
    |pairs|

    pairs := OrderedCollection new.
    self forEachFileNameAndGeneratorMethodDo:[:fileName :generator | 
        |file|

        file := self perform:generator.
        pairs add:(Array with:fileName with:file)
    ].

    pairs pairsDo:aTwoArgBlock

    "Created: / 16-08-2006 / 18:37:52 / User"
!

forEachFileNameAndGeneratorMethodDo:aTwoArgBlock 
    |fileNamesAndSelectors|

    fileNamesAndSelectors := self fileNamesToGenerate asOrderedCollection.
    fileNamesAndSelectors 
                add:(Array 
                        with:self packageName , '.rc'
                        with:#'generate_packageName_dot_rc').
    fileNamesAndSelectors pairsDo:aTwoArgBlock
!

generateFile:filename
    filename = 'nt.mak' ifTrue:[
        ^ self generate_nt_dot_mak
    ].
    filename = 'Make.spec' ifTrue:[
        ^ self generate_make_dot_spec
    ].
    filename = 'bc.def' ifTrue:[
        ^ self generate_bc_dot_def
    ].
    filename = 'libInit.cc' ifTrue:[
        ^ self generate_libInit_dot_cc
    ].
    filename = 'modules.stx' ifTrue:[
        ^ self generate_modules_dot_stx
    ].
    self halt.
!

generate_abbrev_dot_stc
    ^ String 
        streamContents:[:s | 
            self allClassNames do:[:eachClassName | 
                |cls fn|

                cls := Smalltalk classNamed:eachClassName.
                cls autoload.
                s nextPutAll:eachClassName.
                s nextPutAll:' '.
                fn := cls classFilename asFilename withoutSuffix baseName.
                (fn includes:Character space) ifTrue:[
                    s nextPutAll:fn storeString.
                ] ifFalse:[
                    s nextPutAll:fn.
                ].
                s nextPutAll:' '.
                s nextPutAll:cls package.
                s nextPutAll:' '.
                s nextPutAll:cls category asString storeString.
                s nextPutAll:' '.
                s nextPutAll:(cls theMetaclass instVarNames size) printString.
                s cr.
            ]
        ]

    "
        DapasXProject generate_abbrev_dot_stc
        DapasX_Datenbasis generate_abbrev_dot_stc
        bosch_dapasx_interactiver_editor generate_abbrev_dot_stc
    "

    "Created: / 09-08-2006 / 11:24:39 / fm"
    "Modified: / 11-08-2006 / 14:01:51 / cg"
!

generate_bc_dot_def                         

    ^self replaceMappings: self bc_dot_def_mappings 
            in: self bc_dot_def

"
  DapasXProject generate_bc_dot_def
  DapasX_Datenbasis generate_bc_dot_def

"

    "Modified: / 09-08-2006 / 11:30:42 / fm"
!

generate_libInit_dot_cc

    ^self replaceMappings: self libInit_dot_cc_mappings 
            in: self libInit_dot_cc

"
  DapasXProject generate_libInit_dot_cc
  DapasX_Datenbasis generate_libInit_dot_cc

"

    "Created: / 08-08-2006 / 12:47:16 / fm"
    "Modified: / 09-08-2006 / 11:30:52 / fm"
!

generate_make_dot_proto   

    ^self replaceMappings: self make_dot_proto_mappings 
            in: self make_dot_proto

"
  DapasXProject generate_make_dot_proto
  DapasX_Datenbasis generate_make_dot_proto

"

    "Modified: / 09-08-2006 / 11:31:01 / fm"
!

generate_make_dot_spec

    ^self replaceMappings: self make_dot_spec_mappings 
            in: self make_dot_spec

"
  DapasXProject generate_make_dot_spec
  DapasX_Datenbasis generate_make_dot_spec
  bosch_dapasx_kernel_Definition generate_make_dot_spec

"

    "Modified: / 09-08-2006 / 11:31:09 / fm"
!

generate_modules_dot_stx

    ^self replaceMappings: self modules_dot_stx_mappings 
            in: self modules_dot_stx

"
  bosch_dapasx_application generate_modules_dot_stx

"

    "Modified: / 09-08-2006 / 11:31:09 / fm"
    "Modified: / 11-08-2006 / 14:01:56 / cg"
!

generate_nt_dot_def                           

    ^self replaceMappings: self nt_dot_def_mappings 
            in: self nt_dot_def

"
  DapasXProject generate_nt_dot_def
  DapasX_Datenbasis generate_nt_dot_def

"

    "Modified: / 09-08-2006 / 11:31:21 / fm"
!

generate_nt_dot_mak         

    ^self replaceMappings: self nt_dot_mak_mappings 
            in: self nt_dot_mak

"
  DapasXProject generate_nt_dot_mak
  DapasX_Datenbasis generate_nt_dot_mak

"

    "Modified: / 09-08-2006 / 11:46:14 / fm"
!

generate_packageName_dot_rc

    ^self replaceMappings: self packageName_dot_rc_mappings 
            in: self packageName_dot_rc

"
  bosch_dapasx_datenbasis generate_packageName_dot_rc
  bosch_dapasx_hw_schnittstellen  generate_packageName_dot_rc

"

    "Modified: / 09-08-2006 / 11:31:09 / fm"
    "Modified: / 11-08-2006 / 14:01:56 / cg"
! !

!ProjectDefinition class methodsFor:'file templates'!

packageName_dot_rc

^ 
'VS_VERSION_INFO VERSIONINFO
  FILEVERSION     0,1,1,1
  PRODUCTVERSION  0,1,1,1
  FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
  FILEFLAGS       VS_FF_PRERELEASE | VS_FF_SPECIALBUILD
  FILEOS          VOS_NT_WINDOWS32
  FILETYPE        VFT_DLL
  FILESUBTYPE     VS_USER_DEFINED

BEGIN
  BLOCK "StringFileInfo"
  BEGIN
    BLOCK "040904E4"
    BEGIN
      VALUE "CompanyName", "%(COMPANY_NAME)\0"
      VALUE "FileDescription", "%(FILE_DESCRIPTION)\0"
      VALUE "FileVersion", "%(FILE_VERSION)\0"
      VALUE "InternalName", "%(INTERNAL_NAME)\0"
      VALUE "LegalCopyright", "%(LEGAL_COPYRIGHT)\0"
      VALUE "ProductName", "%(PRODUCT_NAME)\0"
      VALUE "ProductVersion", "%(PRODUCT_VERSION)\0"
    END

  END

  BLOCK "VarFileInfo"
  BEGIN                               //  Language   |    Translation
    VALUE "Translation", 0x409, 0x4E4 // U.S. English, Windows Multilingual
  END
END
'


    "Created: / 08-08-2006 / 19:31:29 / fm"
    "Modified: / 09-08-2006 / 15:10:57 / fm"
! !

!ProjectDefinition class methodsFor:'loading'!

load
    self loadExtensions.
    self loadAllClasses.

    "Created: / 17-08-2006 / 01:01:41 / cg"
!

loadAllClasses
    |loadedClasses|

    loadedClasses := OrderedCollection new.

    self allClassNames do:[:className |
        |cls|

        cls := Smalltalk at:className asSymbol.
        (cls isNil or:[cls isLoaded not]) ifTrue:[
            cls := Smalltalk
                fileInClass:className 
                package:self package 
                initialize:false 
                lazy:false 
                silent:false.
            cls notNil ifTrue:[
                loadedClasses add:cls
            ].
        ].
    ].
    loadedClasses do:[:each |
        (each theMetaclass implements:#initialize) ifTrue:[
            each initialize
        ].
    ].

    "Created: / 17-08-2006 / 01:01:14 / cg"
!

loadExtensions
    Smalltalk loadExtensionsForPackage:self package.

    "Created: / 17-08-2006 / 00:21:39 / cg"
!

postAutoload
    self extensionMethodNames notEmptyOrNil ifTrue:[
        self loadExtensions
    ].

    "Created: / 17-08-2006 / 00:21:29 / cg"
! !

!ProjectDefinition class methodsFor:'mappings'!

bc_dot_def_mappings
    ^ (Dictionary new)
        at:#'DESCRIPTION'
            put:[
                    |d|

                    d := self description.
                    (d isEmptyOrNil ifTrue:[ self defaultDescription ] ifFalse:[ d ]) storeString.
                ];
        yourself

    "Created: / 09-08-2006 / 11:17:59 / fm"
!

packageName_dot_rc_mappings

^Dictionary new
    at: #'COMPANY_NAME' put: [self companyName];
    at: #'FILE_DESCRIPTION' put: [self fileDescription];
    at: #'FILE_VERSION' put: [self fileVersion];
    at: #'INTERNAL_NAME' put: [self internalName];
    at: #'LEGAL_COPYRIGHT' put: [self legalCopyright];
    at: #'PRODUCT_NAME' put: [self productName];
    at: #'PRODUCT_VERSION' put: [self productVersion];
    yourself

    "Created: / 09-08-2006 / 11:21:21 / fm"
!

replaceMappings: mappings in: fileTemplate
"Replaces the defined variable mappings found in a file template with the corresponding information"

^ fileTemplate bindWithArguments:mappings.

"
self replaceMappings: (self nt_dot_def_mappingsFor: self) in: self nt_dot_def  
"

    "Created: / 08-08-2006 / 11:44:27 / fm"
    "Modified: / 08-08-2006 / 12:46:13 / fm"
! !

!ProjectDefinition class methodsFor:'project information'!

companyName
    ^'eXept Software AG'
!

fileDescription
    ^self productName,' ',  self packageName
!

fileVersion
    ^self revision ? '0.1.1.1'
!

internalName
    ^self packageName
!

legalCopyright
    ^'Copyright eXept Software AG 2006 (until payment)'
!

productName
    ^'Product Name'
!

productVersion
    ^'0.1.1.1'
! !

!ProjectDefinition class methodsFor:'queries'!

definitionClassForPackage: aPackageID
    ^ self definitionClassForPackage:aPackageID createIfAbsent:false

    "Modified: / 17-08-2006 / 14:33:35 / cg"
!

definitionClassForPackage: aPackageID createIfAbsent: doCreateIfAbsent
    |packageDefinitionClassName class|

    packageDefinitionClassName := ProjectDefinition initialClassNameForDefinitionOf:aPackageID.
    class := Smalltalk classNamed:packageDefinitionClassName.
    class isNil ifTrue:[
        doCreateIfAbsent ifTrue:[
            ^ self newForPackage:aPackageID    
        ].
    ].
    ^ class

    "Created: / 17-08-2006 / 14:33:02 / cg"
!

definitionClassForPackage:newProjectID type:type createIfAbsent:createIfAbsent
    ^ (self definitionClassForType:type)
        definitionClassForPackage:newProjectID createIfAbsent:createIfAbsent

    "Created: / 17-08-2006 / 14:48:01 / cg"
!

definitionClassForType: type
    (type = 'Application') ifTrue:[ ^ ApplicationDefinition ].
    (type = 'Library') ifTrue:[ ^ LibraryDefinition ].
    self error.

    "Created: / 17-08-2006 / 14:46:28 / cg"
    "Modified: / 17-08-2006 / 17:20:57 / cg"
!

hasAllClassesLoaded
    self allClassNames do:[:nm |
        |cls|

        cls := Smalltalk classNamed:nm.
        (cls isNil or:[cls isLoaded not]) ifTrue:[^ false ].
    ].
    ^ true.

    "Created: / 17-08-2006 / 00:50:01 / cg"
    "Modified: / 17-08-2006 / 08:49:44 / cg"
!

hasAllExtensionsLoaded
    self extensionMethodNames pairWiseDo:[:className :selector |
        |cls|

        cls := Smalltalk at:className asSymbol.
        (cls isNil or:[cls isLoaded not]) ifTrue:[^ false ].
        (cls compiledMethodAt:selector) isNil ifTrue:[^ false ].
    ].
    ^ true.

    "Created: / 17-08-2006 / 00:50:01 / cg"
! !

!ProjectDefinition class methodsFor:'testing'!

isProjectDefinition
    ^ self ~~ ProjectDefinition

    "Created: / 10-08-2006 / 16:24:02 / cg"
    "Modified: / 17-08-2006 / 17:24:11 / cg"
! !

!ProjectDefinition class methodsFor:'update description'!

compileDescriptionMethods
    Class packageQuerySignal 
        answer:self package
        do:[
            self forEachMethodsCodeToCompileDo:[:code :category |
                self theMetaclass compilerClass
                    compile:code
                    forClass:self theMetaclass
                    inCategory:category
                    notifying:nil
                    install:true
                    skipIfSame:true
                    silent:false
        ].
    ].

"
    DapasXProject compileDescriptionMethods
    DapasX_Datenbasis compileDescriptionMethods
    bosch_dapasx_interactiver_editor compileDescriptionMethods
"

    "Created: / 09-08-2006 / 18:00:31 / fm"
    "Modified: / 11-08-2006 / 14:01:29 / cg"
    "Modified: / 16-08-2006 / 18:58:29 / User"
!

inconsistency:message
    Dialog warn:message

"
    self searchForNeverCompiledSuperclasses
    DapasX_Datenbasis searchForNeverCompiledSuperclasses  
"

    "Created: / 09-08-2006 / 16:32:31 / fm"
!

searchForClassesNamesWithProject

    ^self searchForClassesWithProject collect:[:each | each name]. 

"
    self searchForClassesNamesWithProject
"

    "Created: / 07-08-2006 / 21:37:06 / fm"
!

searchForClassesWithProject

    ^self searchForClassesWithProject: self package

"
    self searchForClassesWithProject
"

    "Created: / 07-08-2006 / 20:42:39 / fm"
    "Modified: / 07-08-2006 / 21:56:25 / fm"
!

searchForClassesWithProject: aProjectID

    ^ Smalltalk allClasses 
        select:[:cls | (cls package == aProjectID) ].

"
    self searchForClassesWithProject: #'bosch:dapasx'
    self searchForClassesWithProject: #'bosch:dapasx/datenbasis'
    self searchForClassesWithProject: #'bosch:dapasx/kernel'
"

    "Created: / 07-08-2006 / 20:42:39 / fm"
    "Modified: / 07-08-2006 / 21:56:25 / fm"
    "Modified: / 16-08-2006 / 18:50:48 / User"
!

searchForExtensionsForProject:aProjectID
    |methods|

    methods := IdentitySet new.
    Smalltalk allClassesDo:[:eachClass |
        |classPackage|

        classPackage := eachClass package.
        eachClass instAndClassMethodsDo:[:mthd |
            mthd package ~= classPackage ifTrue:[ 
                mthd package == aProjectID ifTrue:[
                    methods add:mthd 
                ]
            ].
        ].
    ].
    ^ methods
"
    self searchForExtensionsForProject:#'bosch:dapasx'
"

    "Created: / 07-08-2006 / 22:03:55 / fm"
!

searchForExtensionsWithProject
    ^ self searchForExtensionsForProject:self package

"
    self searchForExtensionsWithProject
    DapasXProject searchForExtensionsWithProject
    DapasX_Datenbasis searchForExtensionsWithProject

"

    "Created: / 07-08-2006 / 21:03:10 / fm"
    "Modified: / 09-08-2006 / 13:01:26 / fm"
!

searchForProjectsWhichProvideHeaderFiles
      |myPackageID requiredPackages|

      requiredPackages := Set new.
      myPackageID := self package.

      self compiled_classesDo:[:includedClass | 
            includedClass allSuperclassesDo:[:eachSuperClass |
                ((eachSuperClass package ~= myPackageID)
                and:[ (self moduleOfClass: eachSuperClass) ~= 'stx' ])
                    ifTrue:[
                        eachSuperClass package == Project noProjectID ifFalse:[
                            requiredPackages add:(eachSuperClass package).
                        ]
                    ]
            ]
      ].
      ^ requiredPackages

"
    self searchForProjectsWhichProvideHeaderFiles
    DapasX_Datenbasis searchForProjectsWhichProvideHeaderFiles  
"

    "Created: / 09-08-2006 / 16:26:37 / fm"
! !

!ProjectDefinition class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/ProjectDefinition.st,v 1.12 2006-08-17 15:24:39 cg Exp $'
! !