[PATCH 1/2] tooling: Introduce a new package for tooling helpers

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
11 messages Options
Reply | Threaded
Open this post in threaded view
|

[PATCH 1/2] tooling: Introduce a new package for tooling helpers

Holger Freyther
This will hold non UI tools to help with tooling. This can be linters,
the converter, package related tools. Beging with moving parts of the
gst-convert code into this package.

2013-03-30  Holger Hans Peter Freyther  <[hidden email]>

        * configure.ac: Introduce the Tooling package.

2013-03-30  Holger Hans Peter Freyther  <[hidden email]>

        * Makefile.frag: Added.
        * Parser/SourceClass.st: Added from scripts/Convert.st.
        * Parser/SourceComments.st: Added from scripts/Convert.st.
        * Parser/SourceEntity.st: Added from scripts/Convert.st.
        * Parser/SourceEval.st: Added from scripts/Convert.st.
        * Parser/Loader.st: Added from scripts/Convert.st.
        * README: Added.
        * TODO: Added.
        * package.xml: Added.
---
 .gitignore                                |    1 +
 ChangeLog                                 |    4 +
 configure.ac                              |    1 +
 packages/tooling/ChangeLog                |   11 ++
 packages/tooling/Makefile.frag            |    5 +
 packages/tooling/Parser/Loader.st         |  235 +++++++++++++++++++++++++++++
 packages/tooling/Parser/SourceClass.st    |   85 +++++++++++
 packages/tooling/Parser/SourceComments.st |   51 +++++++
 packages/tooling/Parser/SourceEntity.st   |   39 +++++
 packages/tooling/Parser/SourceEval.st     |   72 +++++++++
 packages/tooling/README                   |    2 +
 packages/tooling/TODO                     |    4 +
 packages/tooling/package.xml              |   11 ++
 13 files changed, 521 insertions(+)
 create mode 100644 packages/tooling/ChangeLog
 create mode 100644 packages/tooling/Makefile.frag
 create mode 100644 packages/tooling/Parser/Loader.st
 create mode 100644 packages/tooling/Parser/SourceClass.st
 create mode 100644 packages/tooling/Parser/SourceComments.st
 create mode 100644 packages/tooling/Parser/SourceEntity.st
 create mode 100644 packages/tooling/Parser/SourceEval.st
 create mode 100644 packages/tooling/README
 create mode 100644 packages/tooling/TODO
 create mode 100644 packages/tooling/package.xml

diff --git a/.gitignore b/.gitignore
index d0578bc..e1b96c9 100644
--- a/.gitignore
+++ b/.gitignore
@@ -66,6 +66,7 @@ packages/i18n/ref-add.sed
 packages/i18n/ref-del.sed
 packages/net/gnutls-wrapper
 packages/object-dumper/stamp-classes
+packages/tooling/stamp-classes
 snprintfv/snprintfv/compat.stamp
 
 tests/gst.im
diff --git a/ChangeLog b/ChangeLog
index 54683ff..ec896ef 100644
--- a/ChangeLog
+++ b/ChangeLog
@@ -1,3 +1,7 @@
+2013-03-30  Holger Hans Peter Freyther  <[hidden email]>
+
+ * configure.ac: Introduce the Tooling package.
+
 2013-03-31  Holger Hans Peter Freyther  <[hidden email]>
 
  * tests/stcompiler.ok: Update the test result.
diff --git a/configure.ac b/configure.ac
index 0ce4fed..d58028a 100644
--- a/configure.ac
+++ b/configure.ac
@@ -586,6 +586,7 @@ GST_PACKAGE_ENABLE([Sport], [sport])
 GST_PACKAGE_ENABLE([SUnit], [sunit])
 GST_PACKAGE_ENABLE([Swazoo], [swazoo-httpd])
 GST_PACKAGE_ENABLE([Sockets], [sockets], [], [gst_cv_sockets])
+GST_PACKAGE_ENABLE([Tooling], [tooling])
 GST_PACKAGE_ENABLE([VFSAddOns], [vfs], [], [], [Makefile])
 GST_PACKAGE_ENABLE([VisualGST], [visualgst])
 GST_PACKAGE_ENABLE([XML-XMLNodeBuilder], [xml/builder])
diff --git a/packages/tooling/ChangeLog b/packages/tooling/ChangeLog
new file mode 100644
index 0000000..d5d2a47
--- /dev/null
+++ b/packages/tooling/ChangeLog
@@ -0,0 +1,11 @@
+2013-03-30  Holger Hans Peter Freyther  <[hidden email]>
+
+ * Makefile.frag: Added.
+ * Parser/SourceClass.st: Added from scripts/Convert.st.
+ * Parser/SourceComments.st: Added from scripts/Convert.st.
+ * Parser/SourceEntity.st: Added from scripts/Convert.st.
+ * Parser/SourceEval.st: Added from scripts/Convert.st.
+ * Parser/Loader.st: Added from scripts/Convert.st.
+ * README: Added.
+ * TODO: Added.
+ * package.xml: Added.
diff --git a/packages/tooling/Makefile.frag b/packages/tooling/Makefile.frag
new file mode 100644
index 0000000..bb2a845
--- /dev/null
+++ b/packages/tooling/Makefile.frag
@@ -0,0 +1,5 @@
+Tooling_FILES = \
+packages/tooling/Parser/SourceEntity.st packages/tooling/Parser/SourceClass.st packages/tooling/Parser/SourceComments.st packages/tooling/Parser/SourceEval.st packages/tooling/Parser/Loader.st
+$(Tooling_FILES):
+$(srcdir)/packages/tooling/stamp-classes: $(Tooling_FILES)
+ touch $(srcdir)/packages/tooling/stamp-classes
diff --git a/packages/tooling/Parser/Loader.st b/packages/tooling/Parser/Loader.st
new file mode 100644
index 0000000..0c4e6a9
--- /dev/null
+++ b/packages/tooling/Parser/Loader.st
@@ -0,0 +1,235 @@
+"======================================================================
+|
+|   Smalltalk syntax conversion tool
+|
+|
+ ======================================================================"
+
+
+"======================================================================
+|
+| Copyright 2007, 2008, 2009 Free Software Foundation, Inc.
+| Written by Daniele Sciascia.
+|
+| This file is part of the GNU Smalltalk class library.
+|
+| The GNU Smalltalk class library is free software; you can redistribute it
+| and/or modify it under the terms of the GNU Lesser General Public License
+| as published by the Free Software Foundation; either version 2.1, or (at
+| your option) any later version.
+|
+| The GNU Smalltalk class library is distributed in the hope that it will be
+| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
+| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
+| General Public License for more details.
+|
+| You should have received a copy of the GNU Lesser General Public License
+| along with the GNU Smalltalk class library; see the file COPYING.LIB.
+| If not, write to the Free Software Foundation, 59 Temple Place - Suite
+| 330, Boston, MA 02110-1301, USA.
+|
+ ======================================================================"
+
+STInST.STClassLoader subclass: Loader [
+    | stuffToEmit classesToEmit createdNamespaces filter outStream rewriter |
+
+    <category: 'Tooling-Parser-Core'>
+    <comment: 'A class loader that creates a set of "SourceEntity"
+    based on the contents of the given file being loaded.
+    When the contents of the file are loaded, the responsibilty of
+    emitting code using the new syntax belongs to those various
+    entities that have been constructed.
+
+    TODO: Split the loading and converting'>
+
+
+    Loader class >> convertSqueakStream: in to: out [
+        <category: 'instance creation'>
+        ^self convertStream: in with: STInST.SqueakFileInParser to: out
+    ]
+
+    Loader class >> convertSIFStream: in to: out [
+        <category: 'instance creation'>
+        ^self convertStream: in with: STInST.SIFFileInParser to: out
+    ]
+
+    Loader class >> convertStream: in to: out [
+        <category: 'instance creation'>
+        ^self convertStream: in with: STInST.STFileInParser to: out
+    ]
+
+    Loader class >> convertStream: in with: aParserClass to: out [
+        <category: 'instance creation'>
+        ^self new convertStream: in with: aParserClass to: out
+    ]
+
+    initialize [
+        <category: 'initialization'>
+ super initialize.
+ filter := [ :class | [true] ].
+        stuffToEmit := OrderedSet new.
+        classesToEmit := Dictionary new.
+        createdNamespaces := OrderedSet new.
+    ]
+
+    convertStream: in with: aParserClass to: out onError: aBlock [
+        <category: 'operation'>
+        self
+    outStream: out;
+    parseSmalltalkStream: in with: aParserClass onError: aBlock;
+    doEmitStuff.
+    ]
+
+    convertStream: in with: aParserClass to: out [
+        <category: 'operation'>
+        self
+    outStream: out;
+    parseSmalltalkStream: in with: aParserClass;
+    doEmitStuff.
+    ]
+
+    filter: aBlock [
+        <category: 'accessing'>
+        filter := aBlock.
+    ]
+
+    outStream: out [
+        <category: 'accessing'>
+        outStream := out.
+    ]
+
+    rewrite: node [
+ ^rewriter isNil
+    ifTrue: [ node ]
+    ifFalse: [ rewriter executeTree: node; tree ].
+    ]
+
+    evaluate: node [
+        <category: 'overrides'>
+
+ | rewritten |
+ rewritten := self rewrite: node.
+ node comments isEmpty ifFalse: [
+    stuffToEmit add: (SourceComments comments: node comments source: node source) ].
+
+        ^super evaluate: rewritten
+    ]
+
+    addRule: searchString parser: aParserClass [
+ | tree rule |
+ tree := aParserClass parseRewriteExpression: searchString.
+ tree isMessage ifFalse: [ self error: 'expected ->' ].
+ tree selector = #-> ifFalse: [ self error: 'expected ->' ].
+ rule := RBStringReplaceRule
+    searchForTree: tree receiver
+    replaceWith: tree arguments first.
+
+ rewriter isNil ifTrue: [ rewriter := ParseTreeRewriter new ].
+ rewriter addRule: rule
+    ]
+
+    compile: node [
+        <category: 'collecting entities'>
+
+        | rewritten method |
+
+ rewritten := self rewrite: node.
+        method := self defineMethod: rewritten.
+        (classesToEmit includesKey: currentClass asClass)
+            ifTrue: [ self addMethod: method toLoadedClass: currentClass ]
+            ifFalse: [ self addMethod: method toExtensionClass: currentClass ].
+ ^method
+    ]
+
+    lastEval [
+        <category: 'collecting entities'>
+
+ | lastIsEval evalNamespace |
+
+        evalNamespace := currentNamespace = self defaultNamespace
+    ifTrue: [ nil ]
+    ifFalse: [ currentNamespace ].
+
+        lastIsEval := stuffToEmit notEmpty
+    and: [ (stuffToEmit last isKindOf: SourceEval)
+    and: [ stuffToEmit last namespace = evalNamespace ]].
+
+ ^lastIsEval
+    ifTrue: [ stuffToEmit last ]
+    ifFalse: [ stuffToEmit add: (SourceEval new namespace: evalNamespace) ]
+    ]
+
+    createNamespaces [
+ createdNamespaces do: [ :each || stmt |
+    stmt := RBMessageNode
+                receiver: (RBVariableNode named: (each superspace nameIn: self currentNamespace))
+                selector: #addSubspace:
+                arguments: { RBLiteralNode value: each name asSymbol }.
+    self lastEval addStatement: stmt
+ ].
+ createdNamespaces := OrderedSet new
+    ]
+
+    unknown: node [
+        <category: 'collecting entities'>
+
+ self createNamespaces.
+ self lastEval addStatement: node.
+        ^false
+    ]
+
+    doSubclass: receiver selector: selector arguments: argumentNodes [
+        <category: 'evaluating statements'>
+
+        | class emittedClass |
+
+ createdNamespaces remove: self currentNamespace ifAbsent: [ ].
+ self createNamespaces.
+
+        class := super defineSubclass: receiver
+                       selector: selector
+                       arguments: argumentNodes.
+
+        Notification signal: ('Parsing %1' % {class}).
+        emittedClass := SourceClass forClass: class.
+
+        classesToEmit at: class put: emittedClass.
+        stuffToEmit add: emittedClass.
+
+        ^false
+    ]
+
+    doAddNamespace: receiver selector: selector arguments: argumentNodes [
+ | ns |
+ super doAddNamespace: receiver selector: selector arguments: argumentNodes.
+
+        ns := (self resolveNamespace: receiver) at: argumentNodes first value.
+ createdNamespaces add: ns.
+ ^false
+    ]
+
+    doEmitStuff [
+        <category: 'emitting'>
+
+        stuffToEmit
+    do: [ :each | each emitTo: outStream filteredBy: filter ]
+    separatedBy: [ outStream nl; nextPut: 12 asCharacter; nl ].
+    ]
+
+    addMethod: aMethod toLoadedClass: aClass [
+        <category: 'collecting entities'>
+
+        (aClass isMetaclass)
+            ifTrue: [ (classesToEmit at: currentClass asClass) addClassMethod: aMethod ]
+            ifFalse: [ (classesToEmit at: currentClass) addMethod: aMethod ]
+    ]
+
+    addMethod: aMethod toExtensionClass: aClass [
+        <category: 'collecting entities'>
+
+        ((stuffToEmit size > 0)
+            and: [ (stuffToEmit last isKindOf: SourceClass) and: [ stuffToEmit last forClass = aClass ] ])
+                ifTrue: [ stuffToEmit last addMethod: aMethod ]
+                ifFalse: [ stuffToEmit add: ((SourceClass forExtension: currentClass) addMethod: aMethod) ]
+    ]
+]
diff --git a/packages/tooling/Parser/SourceClass.st b/packages/tooling/Parser/SourceClass.st
new file mode 100644
index 0000000..4258356
--- /dev/null
+++ b/packages/tooling/Parser/SourceClass.st
@@ -0,0 +1,85 @@
+"======================================================================
+|
+|   Smalltalk syntax conversion tool
+|
+|
+ ======================================================================"
+
+
+"======================================================================
+|
+| Copyright 2007, 2008, 2009 Free Software Foundation, Inc.
+| Written by Daniele Sciascia.
+|
+| This file is part of the GNU Smalltalk class library.
+|
+| The GNU Smalltalk class library is free software; you can redistribute it
+| and/or modify it under the terms of the GNU Lesser General Public License
+| as published by the Free Software Foundation; either version 2.1, or (at
+| your option) any later version.
+|
+| The GNU Smalltalk class library is distributed in the hope that it will be
+| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
+| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
+| General Public License for more details.
+|
+| You should have received a copy of the GNU Lesser General Public License
+| along with the GNU Smalltalk class library; see the file COPYING.LIB.
+| If not, write to the Free Software Foundation, 59 Temple Place - Suite
+| 330, Boston, MA 02110-1301, USA.
+|
+ ======================================================================"
+
+SourceEntity subclass: SourceClass [
+    | class methodsToEmit classMethodsToEmit isComplete |
+
+    <category: 'Tooling-Parser-Core'>
+    <comment: 'This class is responsible for emitting a class
+    by using a FormattingExporter.'>
+
+    SourceClass class >> forClass: aClass [
+ (aClass superclass notNil and: [
+    aClass superclass isDefined not ]) ifTrue: [
+        Warning signal:
+    ('superclass %1 is undefined' % {aClass superclass}) ].
+        ^super new initializeWithClass: aClass complete: true
+    ]
+
+    SourceClass class >> forExtension: aClass [
+ aClass isDefined ifFalse: [
+    Warning signal:
+ ('extensions for undefined class %1' % {aClass}) ].
+        ^super new initializeWithClass: aClass complete: false
+    ]
+
+    initializeWithClass: aClass complete: aBoolean [
+        class := aClass.
+        methodsToEmit := STInST.OrderedSet new.
+ classMethodsToEmit := STInST.OrderedSet new.
+ isComplete := aBoolean
+    ]
+
+    forClass [
+        ^class
+    ]
+
+    addMethod: aMethod [
+        methodsToEmit add: aMethod selector asSymbol.
+    ]
+
+    addClassMethod: aMethod [
+ classMethodsToEmit add: aMethod selector asSymbol.
+    ]
+
+    emitTo: aStream filteredBy: aBlock [
+ (aBlock value: class)
+    ifFalse: [
+        Notification signal: ('Skipping %1' % {class}).
+ ^self ].
+
+        Notification signal: ('Converting %1...' % {class}).
+        (STInST.FileOutExporter defaultExporter on: class to: aStream)
+            completeFileOut: isComplete;
+            fileOutSelectors: methodsToEmit classSelectors: classMethodsToEmit.
+    ]
+]
diff --git a/packages/tooling/Parser/SourceComments.st b/packages/tooling/Parser/SourceComments.st
new file mode 100644
index 0000000..5c62184
--- /dev/null
+++ b/packages/tooling/Parser/SourceComments.st
@@ -0,0 +1,51 @@
+"======================================================================
+|
+|   Smalltalk syntax conversion tool
+|
+|
+ ======================================================================"
+
+
+"======================================================================
+|
+| Copyright 2007, 2008, 2009 Free Software Foundation, Inc.
+| Written by Daniele Sciascia.
+|
+| This file is part of the GNU Smalltalk class library.
+|
+| The GNU Smalltalk class library is free software; you can redistribute it
+| and/or modify it under the terms of the GNU Lesser General Public License
+| as published by the Free Software Foundation; either version 2.1, or (at
+| your option) any later version.
+|
+| The GNU Smalltalk class library is distributed in the hope that it will be
+| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
+| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
+| General Public License for more details.
+|
+| You should have received a copy of the GNU Lesser General Public License
+| along with the GNU Smalltalk class library; see the file COPYING.LIB.
+| If not, write to the Free Software Foundation, 59 Temple Place - Suite
+| 330, Boston, MA 02110-1301, USA.
+|
+ ======================================================================"
+
+SourceEntity subclass: SourceComments [
+    | comments |
+    <category: 'Tooling-Parser-Core'>
+
+    SourceComments class >> comments: aCollection source: aString [
+ ^self new comments: (aCollection collect: [ :c |
+    aString copyFrom: c first to: c last ])
+    ]
+
+    emitTo: outStream filteredBy: aBlock [
+ comments do: [ :c |
+ STInST.FileOutExporter defaultExporter fileOutComment: c to: outStream.
+ outStream nl; nl]
+    ]
+
+    comments: anArray [
+ comments := anArray
+   ]
+]
diff --git a/packages/tooling/Parser/SourceEntity.st b/packages/tooling/Parser/SourceEntity.st
new file mode 100644
index 0000000..bbee944
--- /dev/null
+++ b/packages/tooling/Parser/SourceEntity.st
@@ -0,0 +1,39 @@
+"======================================================================
+|
+|   Parsing helper routines
+|
+|
+ ======================================================================"
+
+
+"======================================================================
+|
+| Copyright 2007, 2008, 2009 Free Software Foundation, Inc.
+| Written by Daniele Sciascia.
+|
+| This file is part of the GNU Smalltalk class library.
+|
+| The GNU Smalltalk class library is free software; you can redistribute it
+| and/or modify it under the terms of the GNU Lesser General Public License
+| as published by the Free Software Foundation; either version 2.1, or (at
+| your option) any later version.
+|
+| The GNU Smalltalk class library is distributed in the hope that it will be
+| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
+| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
+| General Public License for more details.
+|
+| You should have received a copy of the GNU Lesser General Public License
+| along with the GNU Smalltalk class library; see the file COPYING.LIB.
+| If not, write to the Free Software Foundation, 59 Temple Place - Suite
+| 330, Boston, MA 02110-1301, USA.
+|
+ ======================================================================"
+
+Object subclass: SourceEntity [
+    <category: 'Tooling-Parser-Core'>
+
+    emitTo: aStream filteredBy: aBlock [
+        self subclassResponsibility
+    ]
+]
diff --git a/packages/tooling/Parser/SourceEval.st b/packages/tooling/Parser/SourceEval.st
new file mode 100644
index 0000000..0df2d93
--- /dev/null
+++ b/packages/tooling/Parser/SourceEval.st
@@ -0,0 +1,72 @@
+"======================================================================
+|
+|   Smalltalk syntax conversion tool
+|
+|
+ ======================================================================"
+
+
+"======================================================================
+|
+| Copyright 2007, 2008, 2009 Free Software Foundation, Inc.
+| Written by Daniele Sciascia.
+|
+| This file is part of the GNU Smalltalk class library.
+|
+| The GNU Smalltalk class library is free software; you can redistribute it
+| and/or modify it under the terms of the GNU Lesser General Public License
+| as published by the Free Software Foundation; either version 2.1, or (at
+| your option) any later version.
+|
+| The GNU Smalltalk class library is distributed in the hope that it will be
+| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
+| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
+| General Public License for more details.
+|
+| You should have received a copy of the GNU Lesser General Public License
+| along with the GNU Smalltalk class library; see the file COPYING.LIB.
+| If not, write to the Free Software Foundation, 59 Temple Place - Suite
+| 330, Boston, MA 02110-1301, USA.
+|
+ ======================================================================"
+
+SourceEntity subclass: SourceEval [
+    | statements comments namespace |
+
+    <category: 'Tooling-Parser-Core'>
+    <comment: 'This class is responsible for emitting a set of
+    statements that should be inside an Eval declaration.'>
+
+    SourceEval class >> new [
+        ^super new initialize
+    ]
+
+    initialize [
+        statements := OrderedCollection new
+    ]
+
+    namespace [
+ ^namespace
+    ]
+
+    namespace: aNamespace [
+ namespace := aNamespace
+    ]
+
+    addStatement: aStatement [
+        statements add: aStatement
+    ]
+
+    emitTo: aStream filteredBy: aBlock [
+ statements isEmpty ifTrue: [ ^self ].
+ STInST.FileOutExporter defaultExporter
+    emitEval: [
+ | formatter |
+ formatter := STInST.RBFormatter new.
+ formatter indent: 1 while: [
+    formatter indent.
+            aStream nextPutAll: (formatter formatAll: statements) ]]
+    to: aStream
+    for: namespace.
+    ]
+]
diff --git a/packages/tooling/README b/packages/tooling/README
new file mode 100644
index 0000000..9c11254
--- /dev/null
+++ b/packages/tooling/README
@@ -0,0 +1,2 @@
+Random collection of tooling classes for GST. Used for import/export
+of GST to other dialects and the base for IDEs and similiar utilities.
diff --git a/packages/tooling/TODO b/packages/tooling/TODO
new file mode 100644
index 0000000..b1617dc
--- /dev/null
+++ b/packages/tooling/TODO
@@ -0,0 +1,4 @@
+* Make the Loader have a Converter subclass and use a Visitor instead
+  of the calls to emitTo:.
+
+* Remove "Emit" from variable names.
diff --git a/packages/tooling/package.xml b/packages/tooling/package.xml
new file mode 100644
index 0000000..f5b99d5
--- /dev/null
+++ b/packages/tooling/package.xml
@@ -0,0 +1,11 @@
+<package>
+    <name>Tooling</name>
+    <namespace>Tooling</namespace>
+    <prereq>Parser</prereq>
+
+    <filein>Parser/SourceEntity.st</filein>
+    <filein>Parser/SourceClass.st</filein>
+    <filein>Parser/SourceComments.st</filein>
+    <filein>Parser/SourceEval.st</filein>
+    <filein>Parser/Loader.st</filein>
+</package>
--
1.7.10.4


_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

[PATCH 2/2] tooling: Introduce a helper for a Monticello export

Holger Freyther
The category of classes and extensions should match the package
name. Create a small class that is checking this on a package and
print the errors.

2013-03-30  Holger Hans Peter Freyther  <[hidden email]>

        * Lint/Monticello.st: Added Monticello class for linting.
        * Parser/SourceClass.st: Reimplement >>#isSourceClass, >>#methodsToEmit,
                >>#classMethodsToEmit, #>>isComplete.
        * Parser/SourceEntity.st: Added >>#isSourceClass.
        * Parser/Loader.st: Add >>#stuffToEmit selector.
        * TODO: Add work item.
        * package.xml: Add the Lint/Monticello.st.
---
 packages/tooling/ChangeLog              |   10 ++
 packages/tooling/Lint/Monticello.st     |  159 +++++++++++++++++++++++++++++++
 packages/tooling/Makefile.frag          |    2 +-
 packages/tooling/Parser/Loader.st       |    5 +
 packages/tooling/Parser/SourceClass.st  |   20 ++++
 packages/tooling/Parser/SourceEntity.st |    4 +
 packages/tooling/TODO                   |   11 +++
 packages/tooling/package.xml            |    2 +
 8 files changed, 212 insertions(+), 1 deletion(-)
 create mode 100644 packages/tooling/Lint/Monticello.st

diff --git a/packages/tooling/ChangeLog b/packages/tooling/ChangeLog
index d5d2a47..65b30a1 100644
--- a/packages/tooling/ChangeLog
+++ b/packages/tooling/ChangeLog
@@ -1,5 +1,15 @@
 2013-03-30  Holger Hans Peter Freyther  <[hidden email]>
 
+ * Lint/Monticello.st: Added Monticello class for linting.
+ * Parser/SourceClass.st: Reimplement >>#isSourceClass, >>#methodsToEmit,
+ >>#classMethodsToEmit, #>>isComplete.
+ * Parser/SourceEntity.st: Added >>#isSourceClass.
+ * Parser/Loader.st: Add >>#stuffToEmit selector.
+ * TODO: Add work item.
+ * package.xml: Add the Lint/Monticello.st.
+
+2013-03-30  Holger Hans Peter Freyther  <[hidden email]>
+
  * Makefile.frag: Added.
  * Parser/SourceClass.st: Added from scripts/Convert.st.
  * Parser/SourceComments.st: Added from scripts/Convert.st.
diff --git a/packages/tooling/Lint/Monticello.st b/packages/tooling/Lint/Monticello.st
new file mode 100644
index 0000000..5bd2998
--- /dev/null
+++ b/packages/tooling/Lint/Monticello.st
@@ -0,0 +1,159 @@
+"======================================================================
+|
+|   Linting for Monticello export
+|
+|
+ ======================================================================"
+
+"======================================================================
+|
+| Copyright 2013 Free Software Foundation, Inc.
+| Written by Holger Hans Peter Freyther.
+|
+| This file is part of the GNU Smalltalk class library.
+|
+| The GNU Smalltalk class library is free software; you can redistribute it
+| and/or modify it under the terms of the GNU Lesser General Public License
+| as published by the Free Software Foundation; either version 2.1, or (at
+| your option) any later version.
+|
+| The GNU Smalltalk class library is distributed in the hope that it will be
+| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
+| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
+| General Public License for more details.
+|
+| You should have received a copy of the GNU Lesser General Public License
+| along with the GNU Smalltalk class library; see the file COPYING.LIB.
+| If not, write to the Free Software Foundation, 59 Temple Place - Suite
+| 330, Boston, MA 02110-1301, USA.
+|
+ ======================================================================"
+
+
+Tooling.SourceClass extend [
+    isComplete [
+        <category: 'accessing'>
+        ^ isComplete
+    ]
+
+    methodsToEmit [
+        <category: 'accessing'>
+        ^ methodsToEmit
+    ]
+
+    classMethodsToEmit [
+        <category: 'accessing'>
+        ^ classMethodsToEmit
+    ]
+
+    isComplete [
+        <category: 'accessing'>
+        ^ isComplete
+    ]
+]
+
+Object subclass: Monticello [
+    | loader package errors |
+    <category: 'Tooling-Lint-Monticello'>
+
+    Monticello class >> lint: aPackage [
+        "Work on a given package."
+        ^ self new
+            loadPackage: aPackage;
+            lint.
+    ]
+
+    loadPackage: aPackage [
+        package := aPackage.
+        loader := Tooling.Loader new.
+
+        self lintFiles: aPackage fileIns.
+        aPackage test ifNotNil: [
+            self lintFiles: aPackage test fileIns].
+    ]
+
+    lintFiles: aList [
+        | files |
+
+        files := package fullPathsOf: aList.
+        files do: [:each | | file |
+            file := each open: FileStream read.
+            loader parseSmalltalkStream: file with: STInST.GSTFileInParser.
+            file close.
+        ]
+    ]
+
+    loader [
+        <category: 'private'>
+        ^ loader
+    ]
+
+    lint [
+        <category: 'lint'>
+        "TODO: this should use the visitor..."
+        loader stuffToEmit do: [:each |
+            each isSourceClass ifTrue: [self lintClass: each]].
+    ]
+
+    lintClass: aClass [
+        <category: 'lint'>
+        aClass isComplete
+            ifTrue: [self lintCompleteClass: aClass]
+            ifFalse: [self lintExtension: aClass].
+    ]
+
+    lintCompleteClass: aClass [
+        <category: 'lint'>
+        "Check if the package name is in the category"
+        (aClass forClass category isNil)
+            ifTrue: [^self addError: 'Class does not have category'
+                                for: aClass forClass].
+        (aClass forClass category startsWith: package name)
+            ifFalse: [self addError: 'Class category does not begin with package name'
+                                for: aClass forClass].
+    ]
+
+    lintExtension: aClass [
+        <category: 'lint'>
+
+        aClass methodsToEmit do: [:each |
+            self lintExtensionMethod: each on: aClass].
+        aClass classMethodsToEmit do: [:each |
+            self lintExtensionMethod: each on: aClass ].
+    ]
+
+    lintExtensionMethod: aSymbol on: aClass [
+        | method |
+        <category: 'lint'>
+        method := aClass forClass >> aSymbol.
+
+        "Use aClass forClass asClass as ProxyClass>>#name will return nil"
+        (method methodCategory isNil)
+            ifTrue: [^self addError: 'Extension method needs category'
+                                for: aClass forClass asClass method: aSymbol].
+        (method methodCategory asLowercase startsWith: ('*', package name asLowercase))
+            ifFalse: [self addError: 'Method does not beging with *package-name'
+                                for: aClass forClass asClass method: aSymbol].
+    ]
+
+    addError: aString for: aClass method: aMethod [
+        <category: 'error-handling'>
+        self errors add: '%1 on %2>>%3' % {aString. aClass name asString. aMethod}.
+    ]
+
+    addError: aString for: aClass [
+        <category: 'error-handling'>
+        self errors add: '%1 on %2' % {aString. aClass name asString}.
+    ]
+
+    errors [
+        <category: 'error-handling'>
+        ^ errors ifNil: [errors := OrderedCollection new].
+    ]
+
+    printErrors [
+        <category: 'error-handling'>
+        self errors do: [:each |
+            Transcript nextPutAll: each; nl.]
+    ]
+]
diff --git a/packages/tooling/Makefile.frag b/packages/tooling/Makefile.frag
index bb2a845..833b5a7 100644
--- a/packages/tooling/Makefile.frag
+++ b/packages/tooling/Makefile.frag
@@ -1,5 +1,5 @@
 Tooling_FILES = \
-packages/tooling/Parser/SourceEntity.st packages/tooling/Parser/SourceClass.st packages/tooling/Parser/SourceComments.st packages/tooling/Parser/SourceEval.st packages/tooling/Parser/Loader.st
+packages/tooling/Parser/SourceEntity.st packages/tooling/Parser/SourceClass.st packages/tooling/Parser/SourceComments.st packages/tooling/Parser/SourceEval.st packages/tooling/Parser/Loader.st packages/tooling/Lint/Monticello.st
 $(Tooling_FILES):
 $(srcdir)/packages/tooling/stamp-classes: $(Tooling_FILES)
  touch $(srcdir)/packages/tooling/stamp-classes
diff --git a/packages/tooling/Parser/Loader.st b/packages/tooling/Parser/Loader.st
index 0c4e6a9..887e62b 100644
--- a/packages/tooling/Parser/Loader.st
+++ b/packages/tooling/Parser/Loader.st
@@ -232,4 +232,9 @@ STInST.STClassLoader subclass: Loader [
                 ifTrue: [ stuffToEmit last addMethod: aMethod ]
                 ifFalse: [ stuffToEmit add: ((SourceClass forExtension: currentClass) addMethod: aMethod) ]
     ]
+
+    stuffToEmit [
+        <category: 'accessing'>
+        ^ stuffToEmit
+    ]
 ]
diff --git a/packages/tooling/Parser/SourceClass.st b/packages/tooling/Parser/SourceClass.st
index 4258356..776bcec 100644
--- a/packages/tooling/Parser/SourceClass.st
+++ b/packages/tooling/Parser/SourceClass.st
@@ -82,4 +82,24 @@ SourceEntity subclass: SourceClass [
             completeFileOut: isComplete;
             fileOutSelectors: methodsToEmit classSelectors: classMethodsToEmit.
     ]
+
+    isSourceClass [
+        <category: 'accessing'>
+        ^ true
+    ]
+
+    methodsToEmit [
+        <category: 'accessing'>
+        ^ methodsToEmit
+    ]
+
+    classMethodsToEmit [
+        <category: 'accessing'>
+        ^ classMethodsToEmit
+    ]
+
+    isComplete [
+        <category: 'accessing'>
+        ^ isComplete
+    ]
 ]
diff --git a/packages/tooling/Parser/SourceEntity.st b/packages/tooling/Parser/SourceEntity.st
index bbee944..c6c735c 100644
--- a/packages/tooling/Parser/SourceEntity.st
+++ b/packages/tooling/Parser/SourceEntity.st
@@ -36,4 +36,8 @@ Object subclass: SourceEntity [
     emitTo: aStream filteredBy: aBlock [
         self subclassResponsibility
     ]
+
+    isSourceClass [
+        ^ false
+    ]
 ]
diff --git a/packages/tooling/TODO b/packages/tooling/TODO
index b1617dc..4014c0b 100644
--- a/packages/tooling/TODO
+++ b/packages/tooling/TODO
@@ -2,3 +2,14 @@
   of the calls to emitTo:.
 
 * Remove "Emit" from variable names.
+
+* The following is shown as a a single class
+  Object subclass: Foo [
+        signal []
+  ]
+
+  Foo extend [
+        signalTwo []
+  ]
+
+  It should be two SourceClass
diff --git a/packages/tooling/package.xml b/packages/tooling/package.xml
index f5b99d5..8359efe 100644
--- a/packages/tooling/package.xml
+++ b/packages/tooling/package.xml
@@ -8,4 +8,6 @@
     <filein>Parser/SourceComments.st</filein>
     <filein>Parser/SourceEval.st</filein>
     <filein>Parser/Loader.st</filein>
+
+    <filein>Lint/Monticello.st</filein>
 </package>
--
1.7.10.4


_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH 1/2] tooling: Introduce a new package for tooling helpers

Paolo Bonzini-2
In reply to this post by Holger Freyther
Il 05/05/2013 11:25, Holger Hans Peter Freyther ha scritto:

> This will hold non UI tools to help with tooling. This can be linters,
> the converter, package related tools. Beging with moving parts of the
> gst-convert code into this package.
>
> 2013-03-30  Holger Hans Peter Freyther  <[hidden email]>
>
> * configure.ac: Introduce the Tooling package.
>
> 2013-03-30  Holger Hans Peter Freyther  <[hidden email]>
>
> * Makefile.frag: Added.
> * Parser/SourceClass.st: Added from scripts/Convert.st.
> * Parser/SourceComments.st: Added from scripts/Convert.st.
> * Parser/SourceEntity.st: Added from scripts/Convert.st.
> * Parser/SourceEval.st: Added from scripts/Convert.st.
> * Parser/Loader.st: Added from scripts/Convert.st.
> * README: Added.
> * TODO: Added.
> * package.xml: Added.
> ---
>  .gitignore                                |    1 +
>  ChangeLog                                 |    4 +
>  configure.ac                              |    1 +
>  packages/tooling/ChangeLog                |   11 ++
>  packages/tooling/Makefile.frag            |    5 +
>  packages/tooling/Parser/Loader.st         |  235 +++++++++++++++++++++++++++++
>  packages/tooling/Parser/SourceClass.st    |   85 +++++++++++
>  packages/tooling/Parser/SourceComments.st |   51 +++++++
>  packages/tooling/Parser/SourceEntity.st   |   39 +++++
>  packages/tooling/Parser/SourceEval.st     |   72 +++++++++
>  packages/tooling/README                   |    2 +
>  packages/tooling/TODO                     |    4 +
>  packages/tooling/package.xml              |   11 ++

s/tooling/sttools/g

s/Tooling/STTools/g

Or perhaps even move RB* to a new package, and all the rest of stinst to
this new package?

Paolo

>  13 files changed, 521 insertions(+)
>  create mode 100644 packages/tooling/ChangeLog
>  create mode 100644 packages/tooling/Makefile.frag
>  create mode 100644 packages/tooling/Parser/Loader.st
>  create mode 100644 packages/tooling/Parser/SourceClass.st
>  create mode 100644 packages/tooling/Parser/SourceComments.st
>  create mode 100644 packages/tooling/Parser/SourceEntity.st
>  create mode 100644 packages/tooling/Parser/SourceEval.st
>  create mode 100644 packages/tooling/README
>  create mode 100644 packages/tooling/TODO
>  create mode 100644 packages/tooling/package.xml
>
> diff --git a/.gitignore b/.gitignore
> index d0578bc..e1b96c9 100644
> --- a/.gitignore
> +++ b/.gitignore
> @@ -66,6 +66,7 @@ packages/i18n/ref-add.sed
>  packages/i18n/ref-del.sed
>  packages/net/gnutls-wrapper
>  packages/object-dumper/stamp-classes
> +packages/tooling/stamp-classes
>  snprintfv/snprintfv/compat.stamp
>  
>  tests/gst.im
> diff --git a/ChangeLog b/ChangeLog
> index 54683ff..ec896ef 100644
> --- a/ChangeLog
> +++ b/ChangeLog
> @@ -1,3 +1,7 @@
> +2013-03-30  Holger Hans Peter Freyther  <[hidden email]>
> +
> + * configure.ac: Introduce the Tooling package.
> +
>  2013-03-31  Holger Hans Peter Freyther  <[hidden email]>
>  
>   * tests/stcompiler.ok: Update the test result.
> diff --git a/configure.ac b/configure.ac
> index 0ce4fed..d58028a 100644
> --- a/configure.ac
> +++ b/configure.ac
> @@ -586,6 +586,7 @@ GST_PACKAGE_ENABLE([Sport], [sport])
>  GST_PACKAGE_ENABLE([SUnit], [sunit])
>  GST_PACKAGE_ENABLE([Swazoo], [swazoo-httpd])
>  GST_PACKAGE_ENABLE([Sockets], [sockets], [], [gst_cv_sockets])
> +GST_PACKAGE_ENABLE([Tooling], [tooling])
>  GST_PACKAGE_ENABLE([VFSAddOns], [vfs], [], [], [Makefile])
>  GST_PACKAGE_ENABLE([VisualGST], [visualgst])
>  GST_PACKAGE_ENABLE([XML-XMLNodeBuilder], [xml/builder])
> diff --git a/packages/tooling/ChangeLog b/packages/tooling/ChangeLog
> new file mode 100644
> index 0000000..d5d2a47
> --- /dev/null
> +++ b/packages/tooling/ChangeLog
> @@ -0,0 +1,11 @@
> +2013-03-30  Holger Hans Peter Freyther  <[hidden email]>
> +
> + * Makefile.frag: Added.
> + * Parser/SourceClass.st: Added from scripts/Convert.st.
> + * Parser/SourceComments.st: Added from scripts/Convert.st.
> + * Parser/SourceEntity.st: Added from scripts/Convert.st.
> + * Parser/SourceEval.st: Added from scripts/Convert.st.
> + * Parser/Loader.st: Added from scripts/Convert.st.
> + * README: Added.
> + * TODO: Added.
> + * package.xml: Added.
> diff --git a/packages/tooling/Makefile.frag b/packages/tooling/Makefile.frag
> new file mode 100644
> index 0000000..bb2a845
> --- /dev/null
> +++ b/packages/tooling/Makefile.frag
> @@ -0,0 +1,5 @@
> +Tooling_FILES = \
> +packages/tooling/Parser/SourceEntity.st packages/tooling/Parser/SourceClass.st packages/tooling/Parser/SourceComments.st packages/tooling/Parser/SourceEval.st packages/tooling/Parser/Loader.st
> +$(Tooling_FILES):
> +$(srcdir)/packages/tooling/stamp-classes: $(Tooling_FILES)
> + touch $(srcdir)/packages/tooling/stamp-classes
> diff --git a/packages/tooling/Parser/Loader.st b/packages/tooling/Parser/Loader.st
> new file mode 100644
> index 0000000..0c4e6a9
> --- /dev/null
> +++ b/packages/tooling/Parser/Loader.st
> @@ -0,0 +1,235 @@
> +"======================================================================
> +|
> +|   Smalltalk syntax conversion tool
> +|
> +|
> + ======================================================================"
> +
> +
> +"======================================================================
> +|
> +| Copyright 2007, 2008, 2009 Free Software Foundation, Inc.
> +| Written by Daniele Sciascia.
> +|
> +| This file is part of the GNU Smalltalk class library.
> +|
> +| The GNU Smalltalk class library is free software; you can redistribute it
> +| and/or modify it under the terms of the GNU Lesser General Public License
> +| as published by the Free Software Foundation; either version 2.1, or (at
> +| your option) any later version.
> +|
> +| The GNU Smalltalk class library is distributed in the hope that it will be
> +| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
> +| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
> +| General Public License for more details.
> +|
> +| You should have received a copy of the GNU Lesser General Public License
> +| along with the GNU Smalltalk class library; see the file COPYING.LIB.
> +| If not, write to the Free Software Foundation, 59 Temple Place - Suite
> +| 330, Boston, MA 02110-1301, USA.
> +|
> + ======================================================================"
> +
> +STInST.STClassLoader subclass: Loader [
> +    | stuffToEmit classesToEmit createdNamespaces filter outStream rewriter |
> +
> +    <category: 'Tooling-Parser-Core'>
> +    <comment: 'A class loader that creates a set of "SourceEntity"
> +    based on the contents of the given file being loaded.
> +    When the contents of the file are loaded, the responsibilty of
> +    emitting code using the new syntax belongs to those various
> +    entities that have been constructed.
> +
> +    TODO: Split the loading and converting'>
> +
> +
> +    Loader class >> convertSqueakStream: in to: out [
> +        <category: 'instance creation'>
> +        ^self convertStream: in with: STInST.SqueakFileInParser to: out
> +    ]
> +
> +    Loader class >> convertSIFStream: in to: out [
> +        <category: 'instance creation'>
> +        ^self convertStream: in with: STInST.SIFFileInParser to: out
> +    ]
> +
> +    Loader class >> convertStream: in to: out [
> +        <category: 'instance creation'>
> +        ^self convertStream: in with: STInST.STFileInParser to: out
> +    ]
> +
> +    Loader class >> convertStream: in with: aParserClass to: out [
> +        <category: 'instance creation'>
> +        ^self new convertStream: in with: aParserClass to: out
> +    ]
> +
> +    initialize [
> +        <category: 'initialization'>
> + super initialize.
> + filter := [ :class | [true] ].
> +        stuffToEmit := OrderedSet new.
> +        classesToEmit := Dictionary new.
> +        createdNamespaces := OrderedSet new.
> +    ]
> +
> +    convertStream: in with: aParserClass to: out onError: aBlock [
> +        <category: 'operation'>
> +        self
> +    outStream: out;
> +    parseSmalltalkStream: in with: aParserClass onError: aBlock;
> +    doEmitStuff.
> +    ]
> +
> +    convertStream: in with: aParserClass to: out [
> +        <category: 'operation'>
> +        self
> +    outStream: out;
> +    parseSmalltalkStream: in with: aParserClass;
> +    doEmitStuff.
> +    ]
> +
> +    filter: aBlock [
> +        <category: 'accessing'>
> +        filter := aBlock.
> +    ]
> +
> +    outStream: out [
> +        <category: 'accessing'>
> +        outStream := out.
> +    ]
> +
> +    rewrite: node [
> + ^rewriter isNil
> +    ifTrue: [ node ]
> +    ifFalse: [ rewriter executeTree: node; tree ].
> +    ]
> +
> +    evaluate: node [
> +        <category: 'overrides'>
> +
> + | rewritten |
> + rewritten := self rewrite: node.
> + node comments isEmpty ifFalse: [
> +    stuffToEmit add: (SourceComments comments: node comments source: node source) ].
> +
> +        ^super evaluate: rewritten
> +    ]
> +
> +    addRule: searchString parser: aParserClass [
> + | tree rule |
> + tree := aParserClass parseRewriteExpression: searchString.
> + tree isMessage ifFalse: [ self error: 'expected ->' ].
> + tree selector = #-> ifFalse: [ self error: 'expected ->' ].
> + rule := RBStringReplaceRule
> +    searchForTree: tree receiver
> +    replaceWith: tree arguments first.
> +
> + rewriter isNil ifTrue: [ rewriter := ParseTreeRewriter new ].
> + rewriter addRule: rule
> +    ]
> +
> +    compile: node [
> +        <category: 'collecting entities'>
> +
> +        | rewritten method |
> +
> + rewritten := self rewrite: node.
> +        method := self defineMethod: rewritten.
> +        (classesToEmit includesKey: currentClass asClass)
> +            ifTrue: [ self addMethod: method toLoadedClass: currentClass ]
> +            ifFalse: [ self addMethod: method toExtensionClass: currentClass ].
> + ^method
> +    ]
> +
> +    lastEval [
> +        <category: 'collecting entities'>
> +
> + | lastIsEval evalNamespace |
> +
> +        evalNamespace := currentNamespace = self defaultNamespace
> +    ifTrue: [ nil ]
> +    ifFalse: [ currentNamespace ].
> +
> +        lastIsEval := stuffToEmit notEmpty
> +    and: [ (stuffToEmit last isKindOf: SourceEval)
> +    and: [ stuffToEmit last namespace = evalNamespace ]].
> +
> + ^lastIsEval
> +    ifTrue: [ stuffToEmit last ]
> +    ifFalse: [ stuffToEmit add: (SourceEval new namespace: evalNamespace) ]
> +    ]
> +
> +    createNamespaces [
> + createdNamespaces do: [ :each || stmt |
> +    stmt := RBMessageNode
> +                receiver: (RBVariableNode named: (each superspace nameIn: self currentNamespace))
> +                selector: #addSubspace:
> +                arguments: { RBLiteralNode value: each name asSymbol }.
> +    self lastEval addStatement: stmt
> + ].
> + createdNamespaces := OrderedSet new
> +    ]
> +
> +    unknown: node [
> +        <category: 'collecting entities'>
> +
> + self createNamespaces.
> + self lastEval addStatement: node.
> +        ^false
> +    ]
> +
> +    doSubclass: receiver selector: selector arguments: argumentNodes [
> +        <category: 'evaluating statements'>
> +
> +        | class emittedClass |
> +
> + createdNamespaces remove: self currentNamespace ifAbsent: [ ].
> + self createNamespaces.
> +
> +        class := super defineSubclass: receiver
> +                       selector: selector
> +                       arguments: argumentNodes.
> +
> +        Notification signal: ('Parsing %1' % {class}).
> +        emittedClass := SourceClass forClass: class.
> +
> +        classesToEmit at: class put: emittedClass.
> +        stuffToEmit add: emittedClass.
> +
> +        ^false
> +    ]
> +
> +    doAddNamespace: receiver selector: selector arguments: argumentNodes [
> + | ns |
> + super doAddNamespace: receiver selector: selector arguments: argumentNodes.
> +
> +        ns := (self resolveNamespace: receiver) at: argumentNodes first value.
> + createdNamespaces add: ns.
> + ^false
> +    ]
> +
> +    doEmitStuff [
> +        <category: 'emitting'>
> +
> +        stuffToEmit
> +    do: [ :each | each emitTo: outStream filteredBy: filter ]
> +    separatedBy: [ outStream nl; nextPut: 12 asCharacter; nl ].
> +    ]
> +
> +    addMethod: aMethod toLoadedClass: aClass [
> +        <category: 'collecting entities'>
> +
> +        (aClass isMetaclass)
> +            ifTrue: [ (classesToEmit at: currentClass asClass) addClassMethod: aMethod ]
> +            ifFalse: [ (classesToEmit at: currentClass) addMethod: aMethod ]
> +    ]
> +
> +    addMethod: aMethod toExtensionClass: aClass [
> +        <category: 'collecting entities'>
> +
> +        ((stuffToEmit size > 0)
> +            and: [ (stuffToEmit last isKindOf: SourceClass) and: [ stuffToEmit last forClass = aClass ] ])
> +                ifTrue: [ stuffToEmit last addMethod: aMethod ]
> +                ifFalse: [ stuffToEmit add: ((SourceClass forExtension: currentClass) addMethod: aMethod) ]
> +    ]
> +]
> diff --git a/packages/tooling/Parser/SourceClass.st b/packages/tooling/Parser/SourceClass.st
> new file mode 100644
> index 0000000..4258356
> --- /dev/null
> +++ b/packages/tooling/Parser/SourceClass.st
> @@ -0,0 +1,85 @@
> +"======================================================================
> +|
> +|   Smalltalk syntax conversion tool
> +|
> +|
> + ======================================================================"
> +
> +
> +"======================================================================
> +|
> +| Copyright 2007, 2008, 2009 Free Software Foundation, Inc.
> +| Written by Daniele Sciascia.
> +|
> +| This file is part of the GNU Smalltalk class library.
> +|
> +| The GNU Smalltalk class library is free software; you can redistribute it
> +| and/or modify it under the terms of the GNU Lesser General Public License
> +| as published by the Free Software Foundation; either version 2.1, or (at
> +| your option) any later version.
> +|
> +| The GNU Smalltalk class library is distributed in the hope that it will be
> +| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
> +| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
> +| General Public License for more details.
> +|
> +| You should have received a copy of the GNU Lesser General Public License
> +| along with the GNU Smalltalk class library; see the file COPYING.LIB.
> +| If not, write to the Free Software Foundation, 59 Temple Place - Suite
> +| 330, Boston, MA 02110-1301, USA.
> +|
> + ======================================================================"
> +
> +SourceEntity subclass: SourceClass [
> +    | class methodsToEmit classMethodsToEmit isComplete |
> +
> +    <category: 'Tooling-Parser-Core'>
> +    <comment: 'This class is responsible for emitting a class
> +    by using a FormattingExporter.'>
> +
> +    SourceClass class >> forClass: aClass [
> + (aClass superclass notNil and: [
> +    aClass superclass isDefined not ]) ifTrue: [
> +        Warning signal:
> +    ('superclass %1 is undefined' % {aClass superclass}) ].
> +        ^super new initializeWithClass: aClass complete: true
> +    ]
> +
> +    SourceClass class >> forExtension: aClass [
> + aClass isDefined ifFalse: [
> +    Warning signal:
> + ('extensions for undefined class %1' % {aClass}) ].
> +        ^super new initializeWithClass: aClass complete: false
> +    ]
> +
> +    initializeWithClass: aClass complete: aBoolean [
> +        class := aClass.
> +        methodsToEmit := STInST.OrderedSet new.
> + classMethodsToEmit := STInST.OrderedSet new.
> + isComplete := aBoolean
> +    ]
> +
> +    forClass [
> +        ^class
> +    ]
> +
> +    addMethod: aMethod [
> +        methodsToEmit add: aMethod selector asSymbol.
> +    ]
> +
> +    addClassMethod: aMethod [
> + classMethodsToEmit add: aMethod selector asSymbol.
> +    ]
> +
> +    emitTo: aStream filteredBy: aBlock [
> + (aBlock value: class)
> +    ifFalse: [
> +        Notification signal: ('Skipping %1' % {class}).
> + ^self ].
> +
> +        Notification signal: ('Converting %1...' % {class}).
> +        (STInST.FileOutExporter defaultExporter on: class to: aStream)
> +            completeFileOut: isComplete;
> +            fileOutSelectors: methodsToEmit classSelectors: classMethodsToEmit.
> +    ]
> +]
> diff --git a/packages/tooling/Parser/SourceComments.st b/packages/tooling/Parser/SourceComments.st
> new file mode 100644
> index 0000000..5c62184
> --- /dev/null
> +++ b/packages/tooling/Parser/SourceComments.st
> @@ -0,0 +1,51 @@
> +"======================================================================
> +|
> +|   Smalltalk syntax conversion tool
> +|
> +|
> + ======================================================================"
> +
> +
> +"======================================================================
> +|
> +| Copyright 2007, 2008, 2009 Free Software Foundation, Inc.
> +| Written by Daniele Sciascia.
> +|
> +| This file is part of the GNU Smalltalk class library.
> +|
> +| The GNU Smalltalk class library is free software; you can redistribute it
> +| and/or modify it under the terms of the GNU Lesser General Public License
> +| as published by the Free Software Foundation; either version 2.1, or (at
> +| your option) any later version.
> +|
> +| The GNU Smalltalk class library is distributed in the hope that it will be
> +| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
> +| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
> +| General Public License for more details.
> +|
> +| You should have received a copy of the GNU Lesser General Public License
> +| along with the GNU Smalltalk class library; see the file COPYING.LIB.
> +| If not, write to the Free Software Foundation, 59 Temple Place - Suite
> +| 330, Boston, MA 02110-1301, USA.
> +|
> + ======================================================================"
> +
> +SourceEntity subclass: SourceComments [
> +    | comments |
> +    <category: 'Tooling-Parser-Core'>
> +
> +    SourceComments class >> comments: aCollection source: aString [
> + ^self new comments: (aCollection collect: [ :c |
> +    aString copyFrom: c first to: c last ])
> +    ]
> +
> +    emitTo: outStream filteredBy: aBlock [
> + comments do: [ :c |
> + STInST.FileOutExporter defaultExporter fileOutComment: c to: outStream.
> + outStream nl; nl]
> +    ]
> +
> +    comments: anArray [
> + comments := anArray
> +   ]
> +]
> diff --git a/packages/tooling/Parser/SourceEntity.st b/packages/tooling/Parser/SourceEntity.st
> new file mode 100644
> index 0000000..bbee944
> --- /dev/null
> +++ b/packages/tooling/Parser/SourceEntity.st
> @@ -0,0 +1,39 @@
> +"======================================================================
> +|
> +|   Parsing helper routines
> +|
> +|
> + ======================================================================"
> +
> +
> +"======================================================================
> +|
> +| Copyright 2007, 2008, 2009 Free Software Foundation, Inc.
> +| Written by Daniele Sciascia.
> +|
> +| This file is part of the GNU Smalltalk class library.
> +|
> +| The GNU Smalltalk class library is free software; you can redistribute it
> +| and/or modify it under the terms of the GNU Lesser General Public License
> +| as published by the Free Software Foundation; either version 2.1, or (at
> +| your option) any later version.
> +|
> +| The GNU Smalltalk class library is distributed in the hope that it will be
> +| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
> +| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
> +| General Public License for more details.
> +|
> +| You should have received a copy of the GNU Lesser General Public License
> +| along with the GNU Smalltalk class library; see the file COPYING.LIB.
> +| If not, write to the Free Software Foundation, 59 Temple Place - Suite
> +| 330, Boston, MA 02110-1301, USA.
> +|
> + ======================================================================"
> +
> +Object subclass: SourceEntity [
> +    <category: 'Tooling-Parser-Core'>
> +
> +    emitTo: aStream filteredBy: aBlock [
> +        self subclassResponsibility
> +    ]
> +]
> diff --git a/packages/tooling/Parser/SourceEval.st b/packages/tooling/Parser/SourceEval.st
> new file mode 100644
> index 0000000..0df2d93
> --- /dev/null
> +++ b/packages/tooling/Parser/SourceEval.st
> @@ -0,0 +1,72 @@
> +"======================================================================
> +|
> +|   Smalltalk syntax conversion tool
> +|
> +|
> + ======================================================================"
> +
> +
> +"======================================================================
> +|
> +| Copyright 2007, 2008, 2009 Free Software Foundation, Inc.
> +| Written by Daniele Sciascia.
> +|
> +| This file is part of the GNU Smalltalk class library.
> +|
> +| The GNU Smalltalk class library is free software; you can redistribute it
> +| and/or modify it under the terms of the GNU Lesser General Public License
> +| as published by the Free Software Foundation; either version 2.1, or (at
> +| your option) any later version.
> +|
> +| The GNU Smalltalk class library is distributed in the hope that it will be
> +| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
> +| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
> +| General Public License for more details.
> +|
> +| You should have received a copy of the GNU Lesser General Public License
> +| along with the GNU Smalltalk class library; see the file COPYING.LIB.
> +| If not, write to the Free Software Foundation, 59 Temple Place - Suite
> +| 330, Boston, MA 02110-1301, USA.
> +|
> + ======================================================================"
> +
> +SourceEntity subclass: SourceEval [
> +    | statements comments namespace |
> +
> +    <category: 'Tooling-Parser-Core'>
> +    <comment: 'This class is responsible for emitting a set of
> +    statements that should be inside an Eval declaration.'>
> +
> +    SourceEval class >> new [
> +        ^super new initialize
> +    ]
> +
> +    initialize [
> +        statements := OrderedCollection new
> +    ]
> +
> +    namespace [
> + ^namespace
> +    ]
> +
> +    namespace: aNamespace [
> + namespace := aNamespace
> +    ]
> +
> +    addStatement: aStatement [
> +        statements add: aStatement
> +    ]
> +
> +    emitTo: aStream filteredBy: aBlock [
> + statements isEmpty ifTrue: [ ^self ].
> + STInST.FileOutExporter defaultExporter
> +    emitEval: [
> + | formatter |
> + formatter := STInST.RBFormatter new.
> + formatter indent: 1 while: [
> +    formatter indent.
> +            aStream nextPutAll: (formatter formatAll: statements) ]]
> +    to: aStream
> +    for: namespace.
> +    ]
> +]
> diff --git a/packages/tooling/README b/packages/tooling/README
> new file mode 100644
> index 0000000..9c11254
> --- /dev/null
> +++ b/packages/tooling/README
> @@ -0,0 +1,2 @@
> +Random collection of tooling classes for GST. Used for import/export
> +of GST to other dialects and the base for IDEs and similiar utilities.
> diff --git a/packages/tooling/TODO b/packages/tooling/TODO
> new file mode 100644
> index 0000000..b1617dc
> --- /dev/null
> +++ b/packages/tooling/TODO
> @@ -0,0 +1,4 @@
> +* Make the Loader have a Converter subclass and use a Visitor instead
> +  of the calls to emitTo:.
> +
> +* Remove "Emit" from variable names.
> diff --git a/packages/tooling/package.xml b/packages/tooling/package.xml
> new file mode 100644
> index 0000000..f5b99d5
> --- /dev/null
> +++ b/packages/tooling/package.xml
> @@ -0,0 +1,11 @@
> +<package>
> +    <name>Tooling</name>
> +    <namespace>Tooling</namespace>
> +    <prereq>Parser</prereq>
> +
> +    <filein>Parser/SourceEntity.st</filein>
> +    <filein>Parser/SourceClass.st</filein>
> +    <filein>Parser/SourceComments.st</filein>
> +    <filein>Parser/SourceEval.st</filein>
> +    <filein>Parser/Loader.st</filein>
> +</package>
>


_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH 2/2] tooling: Introduce a helper for a Monticello export

Paolo Bonzini-2
In reply to this post by Holger Freyther
Il 05/05/2013 11:25, Holger Hans Peter Freyther ha scritto:

> The category of classes and extensions should match the package
> name. Create a small class that is checking this on a package and
> print the errors.
>
> 2013-03-30  Holger Hans Peter Freyther  <[hidden email]>
>
> * Lint/Monticello.st: Added Monticello class for linting.
> * Parser/SourceClass.st: Reimplement >>#isSourceClass, >>#methodsToEmit,
> >>#classMethodsToEmit, #>>isComplete.
> * Parser/SourceEntity.st: Added >>#isSourceClass.
> * Parser/Loader.st: Add >>#stuffToEmit selector.
> * TODO: Add work item.
> * package.xml: Add the Lint/Monticello.st.

A bit immature perhaps?

But the Parser/* changes can go in.

Paolo

> ---
>  packages/tooling/ChangeLog              |   10 ++
>  packages/tooling/Lint/Monticello.st     |  159 +++++++++++++++++++++++++++++++
>  packages/tooling/Makefile.frag          |    2 +-
>  packages/tooling/Parser/Loader.st       |    5 +
>  packages/tooling/Parser/SourceClass.st  |   20 ++++
>  packages/tooling/Parser/SourceEntity.st |    4 +
>  packages/tooling/TODO                   |   11 +++
>  packages/tooling/package.xml            |    2 +
>  8 files changed, 212 insertions(+), 1 deletion(-)
>  create mode 100644 packages/tooling/Lint/Monticello.st
>
> diff --git a/packages/tooling/ChangeLog b/packages/tooling/ChangeLog
> index d5d2a47..65b30a1 100644
> --- a/packages/tooling/ChangeLog
> +++ b/packages/tooling/ChangeLog
> @@ -1,5 +1,15 @@
>  2013-03-30  Holger Hans Peter Freyther  <[hidden email]>
>  
> + * Lint/Monticello.st: Added Monticello class for linting.
> + * Parser/SourceClass.st: Reimplement >>#isSourceClass, >>#methodsToEmit,
> + >>#classMethodsToEmit, #>>isComplete.
> + * Parser/SourceEntity.st: Added >>#isSourceClass.
> + * Parser/Loader.st: Add >>#stuffToEmit selector.
> + * TODO: Add work item.
> + * package.xml: Add the Lint/Monticello.st.
> +
> +2013-03-30  Holger Hans Peter Freyther  <[hidden email]>
> +
>   * Makefile.frag: Added.
>   * Parser/SourceClass.st: Added from scripts/Convert.st.
>   * Parser/SourceComments.st: Added from scripts/Convert.st.
> diff --git a/packages/tooling/Lint/Monticello.st b/packages/tooling/Lint/Monticello.st
> new file mode 100644
> index 0000000..5bd2998
> --- /dev/null
> +++ b/packages/tooling/Lint/Monticello.st
> @@ -0,0 +1,159 @@
> +"======================================================================
> +|
> +|   Linting for Monticello export
> +|
> +|
> + ======================================================================"
> +
> +"======================================================================
> +|
> +| Copyright 2013 Free Software Foundation, Inc.
> +| Written by Holger Hans Peter Freyther.
> +|
> +| This file is part of the GNU Smalltalk class library.
> +|
> +| The GNU Smalltalk class library is free software; you can redistribute it
> +| and/or modify it under the terms of the GNU Lesser General Public License
> +| as published by the Free Software Foundation; either version 2.1, or (at
> +| your option) any later version.
> +|
> +| The GNU Smalltalk class library is distributed in the hope that it will be
> +| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
> +| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
> +| General Public License for more details.
> +|
> +| You should have received a copy of the GNU Lesser General Public License
> +| along with the GNU Smalltalk class library; see the file COPYING.LIB.
> +| If not, write to the Free Software Foundation, 59 Temple Place - Suite
> +| 330, Boston, MA 02110-1301, USA.
> +|
> + ======================================================================"
> +
> +
> +Tooling.SourceClass extend [
> +    isComplete [
> +        <category: 'accessing'>
> +        ^ isComplete
> +    ]
> +
> +    methodsToEmit [
> +        <category: 'accessing'>
> +        ^ methodsToEmit
> +    ]
> +
> +    classMethodsToEmit [
> +        <category: 'accessing'>
> +        ^ classMethodsToEmit
> +    ]
> +
> +    isComplete [
> +        <category: 'accessing'>
> +        ^ isComplete
> +    ]
> +]
> +
> +Object subclass: Monticello [
> +    | loader package errors |
> +    <category: 'Tooling-Lint-Monticello'>
> +
> +    Monticello class >> lint: aPackage [
> +        "Work on a given package."
> +        ^ self new
> +            loadPackage: aPackage;
> +            lint.
> +    ]
> +
> +    loadPackage: aPackage [
> +        package := aPackage.
> +        loader := Tooling.Loader new.
> +
> +        self lintFiles: aPackage fileIns.
> +        aPackage test ifNotNil: [
> +            self lintFiles: aPackage test fileIns].
> +    ]
> +
> +    lintFiles: aList [
> +        | files |
> +
> +        files := package fullPathsOf: aList.
> +        files do: [:each | | file |
> +            file := each open: FileStream read.
> +            loader parseSmalltalkStream: file with: STInST.GSTFileInParser.
> +            file close.
> +        ]
> +    ]
> +
> +    loader [
> +        <category: 'private'>
> +        ^ loader
> +    ]
> +
> +    lint [
> +        <category: 'lint'>
> +        "TODO: this should use the visitor..."
> +        loader stuffToEmit do: [:each |
> +            each isSourceClass ifTrue: [self lintClass: each]].
> +    ]
> +
> +    lintClass: aClass [
> +        <category: 'lint'>
> +        aClass isComplete
> +            ifTrue: [self lintCompleteClass: aClass]
> +            ifFalse: [self lintExtension: aClass].
> +    ]
> +
> +    lintCompleteClass: aClass [
> +        <category: 'lint'>
> +        "Check if the package name is in the category"
> +        (aClass forClass category isNil)
> +            ifTrue: [^self addError: 'Class does not have category'
> +                                for: aClass forClass].
> +        (aClass forClass category startsWith: package name)
> +            ifFalse: [self addError: 'Class category does not begin with package name'
> +                                for: aClass forClass].
> +    ]
> +
> +    lintExtension: aClass [
> +        <category: 'lint'>
> +
> +        aClass methodsToEmit do: [:each |
> +            self lintExtensionMethod: each on: aClass].
> +        aClass classMethodsToEmit do: [:each |
> +            self lintExtensionMethod: each on: aClass ].
> +    ]
> +
> +    lintExtensionMethod: aSymbol on: aClass [
> +        | method |
> +        <category: 'lint'>
> +        method := aClass forClass >> aSymbol.
> +
> +        "Use aClass forClass asClass as ProxyClass>>#name will return nil"
> +        (method methodCategory isNil)
> +            ifTrue: [^self addError: 'Extension method needs category'
> +                                for: aClass forClass asClass method: aSymbol].
> +        (method methodCategory asLowercase startsWith: ('*', package name asLowercase))
> +            ifFalse: [self addError: 'Method does not beging with *package-name'
> +                                for: aClass forClass asClass method: aSymbol].
> +    ]
> +
> +    addError: aString for: aClass method: aMethod [
> +        <category: 'error-handling'>
> +        self errors add: '%1 on %2>>%3' % {aString. aClass name asString. aMethod}.
> +    ]
> +
> +    addError: aString for: aClass [
> +        <category: 'error-handling'>
> +        self errors add: '%1 on %2' % {aString. aClass name asString}.
> +    ]
> +
> +    errors [
> +        <category: 'error-handling'>
> +        ^ errors ifNil: [errors := OrderedCollection new].
> +    ]
> +
> +    printErrors [
> +        <category: 'error-handling'>
> +        self errors do: [:each |
> +            Transcript nextPutAll: each; nl.]
> +    ]
> +]
> diff --git a/packages/tooling/Makefile.frag b/packages/tooling/Makefile.frag
> index bb2a845..833b5a7 100644
> --- a/packages/tooling/Makefile.frag
> +++ b/packages/tooling/Makefile.frag
> @@ -1,5 +1,5 @@
>  Tooling_FILES = \
> -packages/tooling/Parser/SourceEntity.st packages/tooling/Parser/SourceClass.st packages/tooling/Parser/SourceComments.st packages/tooling/Parser/SourceEval.st packages/tooling/Parser/Loader.st
> +packages/tooling/Parser/SourceEntity.st packages/tooling/Parser/SourceClass.st packages/tooling/Parser/SourceComments.st packages/tooling/Parser/SourceEval.st packages/tooling/Parser/Loader.st packages/tooling/Lint/Monticello.st
>  $(Tooling_FILES):
>  $(srcdir)/packages/tooling/stamp-classes: $(Tooling_FILES)
>   touch $(srcdir)/packages/tooling/stamp-classes
> diff --git a/packages/tooling/Parser/Loader.st b/packages/tooling/Parser/Loader.st
> index 0c4e6a9..887e62b 100644
> --- a/packages/tooling/Parser/Loader.st
> +++ b/packages/tooling/Parser/Loader.st
> @@ -232,4 +232,9 @@ STInST.STClassLoader subclass: Loader [
>                  ifTrue: [ stuffToEmit last addMethod: aMethod ]
>                  ifFalse: [ stuffToEmit add: ((SourceClass forExtension: currentClass) addMethod: aMethod) ]
>      ]
> +
> +    stuffToEmit [
> +        <category: 'accessing'>
> +        ^ stuffToEmit
> +    ]
>  ]
> diff --git a/packages/tooling/Parser/SourceClass.st b/packages/tooling/Parser/SourceClass.st
> index 4258356..776bcec 100644
> --- a/packages/tooling/Parser/SourceClass.st
> +++ b/packages/tooling/Parser/SourceClass.st
> @@ -82,4 +82,24 @@ SourceEntity subclass: SourceClass [
>              completeFileOut: isComplete;
>              fileOutSelectors: methodsToEmit classSelectors: classMethodsToEmit.
>      ]
> +
> +    isSourceClass [
> +        <category: 'accessing'>
> +        ^ true
> +    ]
> +
> +    methodsToEmit [
> +        <category: 'accessing'>
> +        ^ methodsToEmit
> +    ]
> +
> +    classMethodsToEmit [
> +        <category: 'accessing'>
> +        ^ classMethodsToEmit
> +    ]
> +
> +    isComplete [
> +        <category: 'accessing'>
> +        ^ isComplete
> +    ]
>  ]
> diff --git a/packages/tooling/Parser/SourceEntity.st b/packages/tooling/Parser/SourceEntity.st
> index bbee944..c6c735c 100644
> --- a/packages/tooling/Parser/SourceEntity.st
> +++ b/packages/tooling/Parser/SourceEntity.st
> @@ -36,4 +36,8 @@ Object subclass: SourceEntity [
>      emitTo: aStream filteredBy: aBlock [
>          self subclassResponsibility
>      ]
> +
> +    isSourceClass [
> +        ^ false
> +    ]
>  ]
> diff --git a/packages/tooling/TODO b/packages/tooling/TODO
> index b1617dc..4014c0b 100644
> --- a/packages/tooling/TODO
> +++ b/packages/tooling/TODO
> @@ -2,3 +2,14 @@
>    of the calls to emitTo:.
>  
>  * Remove "Emit" from variable names.
> +
> +* The following is shown as a a single class
> +  Object subclass: Foo [
> +        signal []
> +  ]
> +
> +  Foo extend [
> +        signalTwo []
> +  ]
> +
> +  It should be two SourceClass
> diff --git a/packages/tooling/package.xml b/packages/tooling/package.xml
> index f5b99d5..8359efe 100644
> --- a/packages/tooling/package.xml
> +++ b/packages/tooling/package.xml
> @@ -8,4 +8,6 @@
>      <filein>Parser/SourceComments.st</filein>
>      <filein>Parser/SourceEval.st</filein>
>      <filein>Parser/Loader.st</filein>
> +
> +    <filein>Lint/Monticello.st</filein>
>  </package>
>


_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH 2/2] tooling: Introduce a helper for a Monticello export

Holger Freyther
On Sat, May 11, 2013 at 07:23:48PM +0200, Paolo Bonzini wrote:
> Il 05/05/2013 11:25, Holger Hans Peter Freyther ha scritto:

> A bit immature perhaps?

yes, but isn't this the point of development versions? The goal
is to have a gst-lint (or have it integrated with gst-package
--test) but it is a long journery, e.g. STInST is not capable
of parsing everything of the GST code yet (one example is the
Glib/GTK subnamespace handling).

holger

_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH 2/2] tooling: Introduce a helper for a Monticello export

Paolo Bonzini-2
Il 11/05/2013 20:19, Holger Hans Peter Freyther ha scritto:
> On Sat, May 11, 2013 at 07:23:48PM +0200, Paolo Bonzini wrote:
>> Il 05/05/2013 11:25, Holger Hans Peter Freyther ha scritto:
>
>> A bit immature perhaps?
>
> yes, but isn't this the point of development versions?

No, that's the point of branches. :)

Development versions are for possibly buggy code that already has a
relatively final shape.

Paolo

 The goal

> is to have a gst-lint (or have it integrated with gst-package
> --test) but it is a long journery, e.g. STInST is not capable
> of parsing everything of the GST code yet (one example is the
> Glib/GTK subnamespace handling).
>
> holger
>
> _______________________________________________
> help-smalltalk mailing list
> [hidden email]
> https://lists.gnu.org/mailman/listinfo/help-smalltalk
>


_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH 2/2] tooling: Introduce a helper for a Monticello export

Holger Freyther
On Sun, May 12, 2013 at 11:28:22AM +0200, Paolo Bonzini wrote:

> No, that's the point of branches. :)
>
> Development versions are for possibly buggy code that already has a
> relatively final shape.

API is just another form of bug. Code and API matures when it is
used, to be used one needs some exposure. Now the master branch
does not have a lot of exposure, a private branch of mine will even
see fewer people trying it (by accident). :)

Any way, the point is taken and I will continue to work on these
changes.

kind regards
        holger

_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH 1/2] tooling: Introduce a new package for tooling helpers

Holger Freyther
In reply to this post by Paolo Bonzini-2
On Sat, May 11, 2013 at 07:22:22PM +0200, Paolo Bonzini wrote:
> Il 05/05/2013 11:25, Holger Hans Peter Freyther ha scritto:

> s/tooling/sttools/g
>
> s/Tooling/STTools/g

done. travis-ci is running make check/make distcheck and I will
push to master once the built is done.
>
> Or perhaps even move RB* to a new package, and all the rest of stinst to
> this new package?

RB + Bracket parsing? My next step is to make gst-package use
the tooling code.

_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH 1/2] tooling: Introduce a new package for tooling helpers

Paolo Bonzini-2
Il 14/05/2013 15:29, Holger Hans Peter Freyther ha scritto:

> On Sat, May 11, 2013 at 07:22:22PM +0200, Paolo Bonzini wrote:
>> Il 05/05/2013 11:25, Holger Hans Peter Freyther ha scritto:
>
>> s/tooling/sttools/g
>>
>> s/Tooling/STTools/g
>
> done. travis-ci is running make check/make distcheck and I will
> push to master once the built is done.
>>
>> Or perhaps even move RB* to a new package, and all the rest of stinst to
>> this new package?
>
> RB + Bracket parsing? My next step is to make gst-package use
> the tooling code.

Even all the rest of file-in parsing.

Note that gst-package shouldn't have any mandatory dependency outside
the kernel, or you have a bootstrapping problem.  NetClients is loaded
without reporting errors.

Paolo

_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH 1/2] tooling: Introduce a new package for tooling helpers

Holger Freyther
On Tue, May 14, 2013 at 03:39:33PM +0200, Paolo Bonzini wrote:

> Even all the rest of file-in parsing.

okay.

>
> Note that gst-package shouldn't have any mandatory dependency outside
> the kernel, or you have a bootstrapping problem.  NetClients is loaded
> without reporting errors.

my bad. gst-convert. It already depends on the Parser package so STTools
will be fine too.

_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH 1/2] tooling: Introduce a new package for tooling helpers

Paolo Bonzini-2
Il 14/05/2013 15:42, Holger Hans Peter Freyther ha scritto:

> On Tue, May 14, 2013 at 03:39:33PM +0200, Paolo Bonzini wrote:
>
>> Even all the rest of file-in parsing.
>
> okay.
>
>>
>> Note that gst-package shouldn't have any mandatory dependency outside
>> the kernel, or you have a bootstrapping problem.  NetClients is loaded
>> without reporting errors.
>
> my bad. gst-convert. It already depends on the Parser package so STTools
> will be fine too.

Sure, gst-convert is fine.

Paolo


_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk