[View]  [Edit]  [Lock]  [References]  [Attachments]  [History]  [Home]  [Changes]  [Search]  [Help] 

mobile[app] 03 - Swiki testing tool

Description

The tool let you select pages in this swiki and load/evaluate the code embedded in the pages, from a system runnning S8 (with access to this swiki).

How to run this tool?

  1. Open the U8 environment with media tools
  2. Evaluate the following expression (showIt/doIt) in a workspace
    SwikiCodeRobot @> 'swiki:s8-media/SwikiTestingTool'

How we built this tool?

This tool is built from a draft specificacion of the UI.
The draft is used to implement the UI as an spec of Mobile framework.
The Mobile framework is loaded in the system (if not already present) and the UI is instantiated from the spec.

Draft of the UI

Uploaded Image: draft1.jpg

Implementation

"Ensure Mobile framework is loaded and verify we are running in a supported platform"
	(SwikiCodeRobot @ #mobile) process: #s8-media tagged: #core.


"Creating SwikiTool  Model"
Object
	subclass: #SwikiTool
	instanceVariableNames: ' categoryNames tags swikiName pages'
	category: #Swiki !

SwikiTool buildAccessors: #(
        tags
        #( swikiName initialize '''s8-media''' )
        #( categoryNames initialize '''test''' )
	#( pages initialize #Array )
)!

! SwikiTool  methodsFor: #specs !
platformPath
	" Private - Return the path for folder of platform files. "

	^''! !

! SwikiTool  methodsFor: #specs !
resourcesPath
	" Private - Return the path for folder of resources. 
	if apply include /images/ here"

	^'http://swiki.smalltalking.net/s8-media/uploads/150/'! !

 !  SwikiTool  methodsFor: #robot !
searchPages
	" Search pages according to filters. "
	
	| categoriesArray tagsArray |
        self pages: Array new. 
	categoriesArray := (self categoryNames asArrayOfSubstringsSeparatedBy: $,) collect: [:each | each trimBlanks].
	tagsArray := (self tags asArrayOfSubstringsSeparatedBy: $,) collect: [:each | each trimBlanks].
        categoriesArray do: [ :each|
               SwikiCodeRobot @ each
			withPagesIn: self swikiName tagged: tagsArray
			do: [:thePages| self pages addAll: thePages ].        
          ].
          "self print: self pages."! !

 !  SwikiTool  methodsFor: #robot !
process
	" Process current tool pages "

	| robot |
        robot := SwikiCodeRobot new.
        robot processPages: self pages  in: self swikiName.! !

Object
	subclass: #TranscriptStreamFilter
	instanceVariableNames: 'stream textWidget'
	classVariableNames: ''
	category: #Swiki !
TranscriptStreamFilter buildAccessors!

 ! TranscriptStreamFilter methodsFor: #io !
cr
	self textWidget notNil ifTrue: [
		self textWidget addText: String cr.
	].
	self stream cr! !

! TranscriptStreamFilter methodsFor: #io !
flush
	^self stream flush ! !

 ! TranscriptStreamFilter methodsFor: #io !
nextPutAll: aString
	self textWidget notNil ifTrue: [
		self textWidget addText: aString asString.
	].
	^self stream nextPutAll: aString asString! !

 ! TranscriptStreamFilter methodsFor: #accessing !
stream
	stream isNil ifTrue: [ stream := String new stream ].
	^stream! !


"Compiling spec and open the UI"
| spec tab swikiPagesView processingPagesView |

processingPagesView := (
 (#class -> #MobileEditor ),
 	(#configuration -> (
  	(#listeners -> ( (#needsTitle -> [:coordinator | 'Processing Pages']),
  	 					(#built: -> [:coordinator | |filter|
  	 					 		filter := TranscriptStreamFilter new
  	 					 					stream: Transcript current stream;
  	 					 					textWidget: coordinator @ #transcriptEcho;
  	 					 					yourself.
  	 					 		Transcript current stream: filter.
  	 					 		self printingWith: [:aString| [ Transcript nextPutAll: aString ] on: Error do: [:err| Transcript nextPutAll: err ] ]  do: [
  	 								coordinator applicationModel process ].
                                                                 Transcript current stream: filter stream; flush.
  	 						]) 
  	 				)),
  	  (#navigationBar -> (
        (#right ->
          (#next -> [:coordinator | coordinator--'comments-save' ] )
        )
   	 )),
 	(#widgets -> (
           (#transcriptEcho -> (
				(#type -> #textArea ),
				(#configuration ->(
					(#order -> 1),
					(#listeners -> (
						(#needsText -> ['Proccessing Pages in s8-media'] )
					))
				))
			)) 
                ))
 	)),
        (#listeners -> (
				(#built: -> [:coordinator | self print: 'HELLO PROCESSING PAGE' ])
    		)) 
).


swikiPagesView := (
 (#class -> #MobileEditor ),
 (#configuration -> (
  (#listeners -> ( (#needsTitle -> [:coordinator | 'Swiki Testing']),
  	 					(#built: -> [:coordinator | self print: 'Built: ', coordinator]) )),
  (#navigationBar -> (
        (#right ->
          (#right -> [:coordinator | coordinator--'comments-save'. coordinator thread next: (coordinator newTemplateAt: #Processing)  ] )
        )
    )),
 (#widgets -> (
           (#pages -> (
				(#type -> #list ),
				(#configuration ->(
					(#order -> 1),
					(#listeners -> (
						(#needsTitle -> ['Swiki Pages in s8-media'] ),
						(#needsItems -> [:coordinator | coordinator applicationModel pages ] ),
						(#configureCell:for:in:coordinator: -> [:cell :item :aList :coordinator |
							coordinator configure: cell title: '#',item first description: item second
						]),
						(#selected: -> [:item :coordinator |
							coordinator application openPage: item in: coordinator
						])
					))
				))
			)) 
                ))
 ))
).
tab :=  (
     	(#tool -> 'swiki' ),
     	(#coordinator -> 
     		(
    			(#class -> #MobileEditor ),
      			(#configuration -> 
      				(
         				(#title -> 'Swiki Testing'),
         				(#navigationBar -> (
          					(#right ->
            					(#right -> [:coordinator | 
            						(coordinator @ #swikiField) done.
            						(coordinator @ #categoryField) done.
            						(coordinator @ #tagsField) done.
            						
            						coordinator applicationModel 
            							swikiName: (coordinator @ #swikiField) text trimBlanks;
            							categoryNames: (coordinator @ #categoryField) text trimBlanks;
            							tags: (coordinator @ #tagsField) text trimBlanks;
                                                                searchPages;
            							yourself.
            						coordinator thread next: (coordinator newTemplateAt: #SwikiPages) ])
          					))
         				),
         				(#widgets -> (
           					
             				(#swikiLabel -> (
            					(#type -> #label ),
            					(#configuration -> (
               						(#order -> 1 ), 
               						(#height -> 40), 
               						"(#backgroundColor -> 'white'),"
               						(#text -> 'Swiki')",
               						(#color -> 'blue')"
                				)) 
                			)),
                                          (#swikiField -> (
            					(#type -> #textField ),
            					(#configuration -> (
               						(#order -> 2 ),
               						(#height -> 40),
               						(#defaultText -> 's8-media'),
               						(#width -> 300), 
                					(#background -> 'white'),
                					(#color -> 'black'),
                					(#keyboardType -> 'numberPad'),
                					(#border -> 'roundedRect'),
                					(#autocapitalizationType -> #none),
                					(#autocorrectionType -> #none),
                					(#spellCheckingType -> #none),
                					(#returnKeyType -> #done),
               						(#listeners -> (
                						(#done: -> [:coordinator :field | coordinator applicationModel swikiName: (coordinator @ #swikiField) text ])
                
     								)) 
     							))  
     						)),

                                          (#separator -> (
            					(#type -> #line ),
            					(#configuration -> (
               						(#order -> 3 ),
               						(#height -> 10), 
                					(#background -> 'blue') 
                				  )) 
                			     )),
				           (#categoryLabel -> (
            					(#type -> #label ),
            					(#configuration -> (
               						(#order -> 4 ), 
               						(#height -> 40), 
               						"(#backgroundColor -> 'white'),"
               						(#text -> 'Category')",
               						(#color -> 'blue')"
                				)) 
                			)),
                                          (#categoryField -> (
            					(#type -> #textField ),
            					(#configuration -> (
               						(#order -> 5 ),
               						(#height -> 40),
               						(#defaultText -> 'Test'),
               						(#width -> 300), 
                					(#background -> 'white'),
                					(#color -> 'black'),
                					(#keyboardType -> 'numberPad'),
                					(#border -> 'roundedRect'),
                					(#autocapitalizationType -> #none),
                					(#autocorrectionType -> #none),
                					(#spellCheckingType -> #none),
                					(#returnKeyType -> #done),
               						(#listeners -> (
                						(#done: -> [:coordinator :field | coordinator applicationModel swikiName: (coordinator @ #categoryField) text ])
                
     								)) 
     							))  
     						)),

                                          (#separator2 -> (
            					(#type -> #line ),
            					(#configuration -> (
               						(#order -> 6 ),
               						(#height -> 10), 
                					(#background -> 'blue') 
                				 )) 
                			     )),
                                            (#tagsLabel -> (
            					(#type -> #label ),
            					(#configuration -> (
               						(#order -> 7 ), 
               						(#height -> 40), 
               						"(#backgroundColor -> 'white'),"
               						(#text -> 'Tags')",
               						(#color -> 'blue')"
                				)) 
                			)),
                                          (#tagsField -> (
            					(#type -> #textField ),
            					(#configuration -> (
               						(#order -> 8 ),
               						(#height -> 40),
               						(#defaultText -> 's8-media'),
               						(#width -> 500), 
                					(#background -> 'white'),
                					(#color -> 'black'),
                					(#keyboardType -> 'numberPad'),
                					(#border -> 'roundedRect'),
                					(#autocapitalizationType -> #none),
                					(#autocorrectionType -> #none),
                					(#spellCheckingType -> #none),
                					(#returnKeyType -> #done),
               						(#listeners -> (
                						(#done: -> [:coordinator :field | coordinator applicationModel swikiName: (coordinator @ #swikiField) text ])
                
     								)) 
     							))  
     						)),
                                          (#separator3 -> (
            					(#type -> #line ),
            					(#configuration -> (
               						(#order ->9 ),
               						(#height -> 70), 
                					(#background -> 'blue') 
                				)) 
                			   ))	
                	)),
         				
			(#listeners -> (
				(#built: -> [:coordinator | self print: coordinator applicationModel toString. (coordinator @ #swikiField) text: (coordinator applicationModel swikiName). 
                                   (coordinator @ #categoryField) text: (coordinator applicationModel categoryNames)])
    		)) 
    	)
      ) 
    )
	) 
    ).
spec := (
 (#threads -> ((1 -> tab)) ),
(#templates -> (
   (#SwikiPages -> swikiPagesView),
   (#Processing -> processingPagesView)
 )),
 (#listeners -> (#needsModel -> [ SwikiTool new  yourself. ]))
) json.


[MobileApplication open: spec ] valueDeferred: 100.