2016-09-15 20:45 GMT+02:00 stepharo <[email protected]>:

> Hi all
>
> I want something similar in the spirit to PythonDocTest
> https://docs.python.org/2/library/doctest.html
>
> I'm talking about
>
> basename
>     "Returns the base of the basename,
>         i.e.
>         /foo/gloops.taz basename is 'gloops.taz'
>         / basename is '/'"
>
> Pragmas do not work well i.e.,
> basename
>     "Returns the base of the basename"
>      <expr: '''/foo/gloops.taz'' asFileReference basename' result:
> 'gloops.taz'>
>
>
> We should invent a syntax to be put inside comments and that we can easily
> parse because we need to improve
> the use and discovery of the library.
>
> I was thinking about
>
> basename
>     "Returns the base of the basename"
>     "
>     '/foo/gloops.taz' asFileReference basename
>     >>> 'gloops.taz'
>     "
>
> Do you have any idea?
>
> I cannot not do anything and just complain that our methods are not that
> well documented.
> We as a community should take this and build an super cool system.
>
> I tried and defined >>> on Object to see if it works!
>
> Object >>> aResultingObject
>     "If the method comment contains >>> then it is a pharo documentated
> test. We can check that it is true."
>
>     "
>     '/foo/gloops.taz' asFileReference basename
>    >>> 'gloops.taz'
>     "
>
>     ^ self = aResultingObject
>
>
Ok, this is a quick hack ( do not look at the code :), yes using regex here
is a bit fragil)

You can add code in comments between backticks (`)
The formatter will highlight the text like smalltalk code (or not if it is
not valid code).
+ an icon styler with an icon showing a warning icon for faulty code or an
information icon otherwise
you can click on the icon,

if the code is an association

expression -> result

it executes the expression and compares it with the result, (with
assert:equals: ) opens debugger if it fails and does
nothing otherwise

if the code is just an expression, it opens an inspector.

This is just one way to do some tests and experiments with this idea, don
't yet know if this is a good idea or if
we can / should find a better way to connect code with examples.

first result, I find expressions in comments, highlighted as code,
confusing :)

(file in attached cs in a recent pharo 6.0 and look at the method
AbstractFileReference>>#baseName . Or
add an expression with backticks in a method comment
` your code here `




>
> Stef
>
>
>
'From Pharo6.0 of 13 May 2016 [Latest update: #60225] on 15 September 2016 at 
10:27:15.932951 pm'!
IconStyler subclass: #ExampleIconStyler
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Reflectivity-Tools-Breakpoints'!

!AbstractFileReference methodsFor: 'accessing' stamp: 'NicolaiHess 9/15/2016 
22:25'!
basename
        "Returns the basename, i.e. /foo/gloops.taz basename is 'gloops.taz'
        ` '/foo/gloops.taz' asFileReference basename -> 'gloops.taz'.` <- 
suceeds, no output
        ` '/foo/gloops.taz' asFileReference basename -> 'gloops.ta'.`   <- 
fails, shows asserter
        ` '/foo/gloops.taz' asFileReference basename` < opens inspector
        
        "
        ^ self fullPath basename! !


!ExampleIconStyler methodsFor: 'as yet unclassified' stamp: 'NicolaiHess 
9/15/2016 14:37'!
iconBlock: aNode
        ^ (self exampleIsFaulty: aNode)
                ifTrue: [ self notifySourceError: aNode ]
                ifFalse: [self runExampleBlock: aNode]! !

!ExampleIconStyler methodsFor: 'as yet unclassified' stamp: 'NicolaiHess 
9/15/2016 14:38'!
iconFor: aNode
        ^ (self exampleIsFaulty: aNode)
                ifTrue: [ self iconProvider iconNamed: #smallWarning ]
                ifFalse: [ self iconProvider iconNamed: #smallInfo ]! !

!ExampleIconStyler methodsFor: 'as yet unclassified' stamp: 'NicolaiHess 
9/15/2016 14:35'!
exampleIsFaulty: aNode
        ^ aNode comments
                anySatisfy: [ :commentNode | commentNode exampleNodes 
anySatisfy:[:node |
                                node value isFaulty ]]! !

!ExampleIconStyler methodsFor: 'as yet unclassified' stamp: 'NicolaiHess 
9/15/2016 14:39'!
notifySourceError: aNode
        ^ [ | examples faultyExample |
        examples := aNode comments flatCollect: #exampleNodes.
        faultyExample := examples detect: [ :example | example value isFaulty ].
        RBParser parseExpression: faultyExample value source ]! !

!ExampleIconStyler methodsFor: 'as yet unclassified' stamp: 'NicolaiHess 
9/15/2016 12:53'!
shouldStyleNode: aNode
        ^ (aNode isMethod and: [ aNode comments isEmpty not ])
                and: [ aNode comments anySatisfy: [ :commentNode | commentNode 
exampleNodes isNotEmpty ] ]! !

!ExampleIconStyler methodsFor: 'as yet unclassified' stamp: 'NicolaiHess 
9/15/2016 14:44'!
iconLabel: aNode
"3+4"
        ^ (self exampleIsFaulty: aNode)
                ifTrue: [ 'Faulty Example' ]
                ifFalse: [ 'Runnable Examle' ]! !

!ExampleIconStyler methodsFor: 'as yet unclassified' stamp: 'NicolaiHess 
9/15/2016 14:37'!
runExampleBlock: aNode
        ^ [ | examples |
        examples := aNode comments flatCollect: #exampleNodes.
        examples
                collect: [ :example | 
                        | result |
                        result := Smalltalk compiler evaluate: example value 
formattedCode.
                        (result isKindOf: Association)
                                ifFalse: [ result inspect ]
                                ifTrue: [ TestAsserter new assert: result key 
equals: result value ] ] ]! !


!RBComment methodsFor: 'accessing' stamp: 'NicolaiHess 9/15/2016 22:25'!
exampleNodes
        | a |
   a := '`(([$#'']`)|[^`])+`' asRegex matchingRangesIn: self contents.  
        ^ a
                collect: [ :text | 
                        | i node |
                        i := text first + 1 to: text last - 1.
                        node := RBParser parseFaultyExpression: (self contents 
copyFrom: i first to: i last ).
                        node doSemanticAnalysis.
                        i -> node ]! !


!RubSHTextStylerST80 methodsFor: 'visiting rb nodes' stamp: 'NicolaiHess 
9/15/2016 12:50'!
visitMethodNode: aMethodNode
        | link |
        aMethodNode comments do: [ :comment | self addStyle: #comment from: 
comment start to: comment stop ].
                aMethodNode comments do:[:k |
                |enodes| 
                enodes := k exampleNodes.
                        enodes do:[:ar |
                        |inode tt|
                        inode := ar value.
                        tt := inode source asText.
                        self class new style: tt ast: inode.
                        tt withIndexDo:[:char :ij ||index|
                                index := ij -1 + k start.
                                charAttr from: (ar key first + index)
                                to: (ar key first + index) put: (tt 
attributesAt: ij)]]].
        aMethodNode arguments do: [ :argument | self addStyle: #patternArg 
forNode: argument ].
        link := TextMethodLink selector: aMethodNode selector.
        aMethodNode selectorParts
                with: aMethodNode keywordsPositions
                do:
                        [ :keyword :position | 
                        self
                                addStyle: #patternKeyword
                                attribute: link
                                from: position
                                to: position + keyword size - 1 ].
        aMethodNode pragmas do: [ :each | self visitNode: each ].
        self visitNode: aMethodNode body! !

Reply via email to