getColoredSource??

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

getColoredSource??

Howard Oh
I'm building a class that converts RTF to HTML in my D4, so that I can
post colored smalltalk source codes to a Web site easily.

I couldn't find #getColoredSource in D6. Where do I start from to do
the same thing in D6?


Best Regards,
Howard


Reply | Threaded
Open this post in threaded view
|

Re: getColoredSource??

Christopher J. Demers
"Howard Oh" <[hidden email]> wrote in message
news:[hidden email]...
> I'm building a class that converts RTF to HTML in my D4, so that I can
> post colored smalltalk source codes to a Web site easily.
>
> I couldn't find #getColoredSource in D6. Where do I start from to do
> the same thing in D6?

Dolphin 6 uses Scintilla instead of the Windows Rich Text control.  I don't
know if RTF colored source is still available, perhaps someone else can
comment on that.  I know that in the Scite editor, based on Scintilla there
is a way to save colored sources as both HTML and RTF.  I _think_ that
functionality is built into Scite rather than Scintilla (though I would love
to be wrong).  It may be worth your while to look into how Scite exports
colored HTML and RTF.

Chris


Reply | Threaded
Open this post in threaded view
|

Re: getColoredSource??

Ian Bartholomew-21
Howard/Chris,

> Dolphin 6 uses Scintilla instead of the Windows Rich Text control.  I
> don't know if RTF colored source is still available, perhaps someone else
> can comment on that.

There isn't any way to get coloured source out of the D6 image as it stands.
This has been asked before and Blair indicated that, with the way Scintilla
worked, it would be a bit difficult to implement.  His suggestion was to use
the parse tree available in Dolphin to create a document with colour
information - either RTF, HTML or XML format.

I had a quick look at this and the easiest way seemed to be to work with the
RBConfigurableFormatter.  I was looking at subclassing it, copying all the
methods that wrote to the codeStream instVar (where it accumulates it's
formatted output) and modifying them to insert tags (of my own choosing)
into the output to indicate colour and stryle changes.  I was then going to
run the output from the formatter through a tool that created a correctly
coloured RTF document.

As you can tell from the "had" and "was" above I never actually got round to
writing it. The only thing I wanted it for was to produce "nicely" formatted
printouts of a complete class and, to be honest, the ones you get from just
printing workspaces containing the code were good enough.

--
Ian

Use the Reply-To address to contact me (limited validity).
Mail sent to the From address is ignored.


Reply | Threaded
Open this post in threaded view
|

Re: getColoredSource??

Ian Bartholomew-21
In reply to this post by Christopher J. Demers
I  wrote ...

> As you can tell from the "had" and "was" above I never actually got round
> to writing it.

Well I have now,  and it was surprisingly easy - something that I find
rather worrying!

I've uploaded a package (2.2 KiB) to

http://www.idb.me.uk\files\colourer.zip

It unzips to a single package which should file into a D6 Pro image.  It
will generate one overwrite error, there's an existing method
(RichTextEdit>>color:) that needs a slight tweak to work.

Evaluate the code in the Package comment and you should end up with WordPad
(the Dolphin clone) open on a document containing all the class and instance
methods from Object formatted in the correct colours.  From there it can be
edited, saved (remember to name the file .rtf), printed or whatever.

ToDo:
Work out how to include class definitions.
Make sure that all the code is using the correct colours.  I find it quite
difficult scanning two documents to make sure the colour matches and might
have missed something.

Feedback is encouraged!

--
Ian

Use the Reply-To address to contact me (limited validity).
Mail sent to the From address is ignored.


Reply | Threaded
Open this post in threaded view
|

Re: getColoredSource??

Chris Uppal-3
In reply to this post by Christopher J. Demers
Ian, Howard,

> Well I have now,  and it was surprisingly easy - something that I find
> rather worrying!

Shows how easy it is to hack OO code (Hi Jeff ;-)

Just for interest here's another, rather different, approach which just
occurred to me.  With the
appended class filed-in, you can say:

    "get the source for a random method"
    source := (ScintillaStyler compiledMethodAt: #stylingStartBefore:in:)
                        getSource.

    "and a styler for styling methods"
    styler := SmalltalkMethodStyler new.

    "use a fake scintilla view to fool the styler into styling the text"
    fake := FakeScintillaView
                   text: source
                   styler: styler.

and then:

    fake styles

will answer a RunArray containing a ScintillaTextStyle for each character
position in source.

Or:

    fake styledText.

will answer an Array containing (in order) each fragment (word) of text with
the corresponding style.

It's one Hell of a hack, but quite fun in a perverted sort of way, and does
have the advantage of picking up the configured styles ;-)

Note: not tested, not commented, not supported in any way...

    -- chris

============ FakeScintillaView.cls =============
"Filed out from Dolphin Smalltalk X6"!

Object subclass: #FakeScintillaView
 instanceVariableNames: 'text runLengths runStyles styleMask stylesByName
stylesById'
 classVariableNames: ''
 poolDictionaries: ''
 classInstanceVariableNames: ''!
FakeScintillaView guid: (GUID fromString:
'{6CDA2881-20EC-49E0-A7F9-68A9B275EB44}')!
FakeScintillaView comment: 'Use like:

 "get the source for a random method"
 source := (ScintillaStyler compiledMethodAt: #stylingStartBefore:in:)
getSource.

 "and a styler for styling methods"
 styler := SmalltalkMethodStyler new.

 "use a fake scintilla view to fool the styler into styling the text"
 fake := FakeScintillaView
   text: source
   styler: styler.

and then:

 fake styles.

will answer a RunArray containing a ScintillaTextStyle for each character
position in source.

Or:

 fake styledText.

will answer an Array containing (in order) each fragment (word) of text with
the corresponding style.'!
!FakeScintillaView categoriesForClass!Kernel-Objects! !
!FakeScintillaView methodsFor!

braceChars: anIdentityDictionaryOfString!

characterAt: anInteger

 ^ text at: anInteger.!

extraStyleBits: anInteger!

invertStylesByName

 | map |

 map := LookupTable new.
 stylesByName do:
  [:each || id |
  id := each id bitAnd: styleMask.
  map at:id put: each].

 ^ map.
 !

makeStylesByName

 | map |

 map := IdentityDictionary new.
 SmalltalkWorkspace textStyles do: [:each | map at: each name put: each copy].

 ^ map.
 !

plainTextFrom: anInteger to: anInteger2
 ^ text copyFrom: anInteger to: anInteger2.!

styleBits: anInteger

 styleMask := 1 << anInteger - 1.
 stylesById := self invertStylesByName.!

styledText

 | in out |

 in := text readStream.
 out:= Array writeStream.
 self styles runsAndValuesDo:
  [:run : style || word |
  word := in next: run.
  out nextPut: (word -> style)].

 ^ out contents.!

styleNamed: aSymbol

 ^ stylesByName
  at: aSymbol
  ifAbsent: [].!

styleNext: anInteger mask: anotherInteger

 runLengths nextPut: anInteger.
 runStyles nextPut: (stylesById at: (anotherInteger bitAnd: styleMask)).!

styler: aScintillaStyler

 aScintillaStyler
  prepareToStyleView: self;
  colorTextFrom: 1 to: text size in: self.
!

styles

 ^ RunArray
  runs:runLengths contents
  values: runStyles contents.!

text: aString
 text := aString.
 runLengths := Array writeStream.
 runStyles := Array writeStream.
 styleMask := 16rFFFFFFFF.
 stylesByName := self makeStylesByName.
 stylesById := nil.! !
!FakeScintillaView categoriesFor: #braceChars:!private! !
!FakeScintillaView categoriesFor: #characterAt:!public! !
!FakeScintillaView categoriesFor: #extraStyleBits:!private! !
!FakeScintillaView categoriesFor: #invertStylesByName!private! !
!FakeScintillaView categoriesFor: #makeStylesByName!private! !
!FakeScintillaView categoriesFor: #plainTextFrom:to:!public! !
!FakeScintillaView categoriesFor: #styleBits:!private! !
!FakeScintillaView categoriesFor: #styledText!public! !
!FakeScintillaView categoriesFor: #styleNamed:!public! !
!FakeScintillaView categoriesFor: #styleNext:mask:!private! !
!FakeScintillaView categoriesFor: #styler:!private! !
!FakeScintillaView categoriesFor: #styles!public! !
!FakeScintillaView categoriesFor: #text:!private! !

!FakeScintillaView class methodsFor!

text: aString styler: aScintillaStyler

 ^ (self basicNew)
  text: aString;
  styler: aScintillaStyler;
  yourself.! !
!FakeScintillaView class categoriesFor: #text:styler:!public! !


Reply | Threaded
Open this post in threaded view
|

Re: getColoredSource??

Ian Bartholomew-21
Chris,

> It's one Hell of a hack, but quite fun in a perverted sort of way, and
> does
> have the advantage of picking up the configured styles ;-)

My method was a hack as well - but this one is much, much nicer :-)

Add one method to FakeScintillaView

rtfText
 | converter |
 converter := RichText rtfConverter.
 converter text: String new.
 self styledText
  do:
   [:each |
   each value name == #normal
    ifFalse:
     [converter isBold: each value isBold == true.
     converter isItalic: each value isItalic == true.
     converter color: each value forecolor].
   converter replaceSelection: each key].
 ^converter rtfText

and you can then do

rtp := WordPad show.
(rtp view viewNamed: 'document') rtfText: fake rtfText

Really neat

Ummm, can I borrow it, pretty please.

--
Ian

Use the Reply-To address to contact me (limited validity).
Mail sent to the From address is ignored.


Reply | Threaded
Open this post in threaded view
|

Re: getColoredSource??

Chris Uppal-3
In reply to this post by Chris Uppal-3
Ian,

> rtp := WordPad show.
> (rtp view viewNamed: 'document') rtfText: fake rtfText

Yes, very nice.


> Ummm, can I borrow it, pretty please.

Please take it; with my complements.

BTW: I tested it a little more than just the one method I'd tried to date and
find that it needs an extra method:
================
plainTextRange: anInterval

    ^ self
            plainTextFrom: anInterval start
            to: anInterval stop.
================

With that it can process all the methods in this image without walkbacks (but
not necessarily without malfunctioning in less obvious ways).

    -- chris


Reply | Threaded
Open this post in threaded view
|

Re: getColoredSource??

Ian Bartholomew-21
OK, last word on this subject today :-)

I've just uploaded a new package to my web site (2.7 KiB)

http://www.idb.me.uk/files/documentclass.zip

It contains a package which works in a base D6.02, either Pro or Community
edition, and produces a formatted document containing a class' comment,
definition and methods.  The document can be automatically opened in an
editor (the WordPad clone sample supplied with Dolphin) or just returned as
a rtf string.

DocumentClass edit: aClass - opens WordPad on the class

DocumentClass on: aClass - answers a rtf string

No options are available, if you want it to do something in a different way
you will have to edit the source.

Many thanks again to Chris Uppal for providing the FakeScintillaView class.

--
Ian

Use the Reply-To address to contact me (limited validity).
Mail sent to the From address is ignored.


Reply | Threaded
Open this post in threaded view
|

Re: getColoredSource??

Blair McGlashan-4
In reply to this post by Chris Uppal-3
"Chris Uppal" <[hidden email]> wrote in message
news:44899705$0$656$[hidden email]...

> Ian, Howard,
>
>> Well I have now,  and it was surprisingly easy - something that I find
>> rather worrying!
>
> Shows how easy it is to hack OO code (Hi Jeff ;-)
>
> Just for interest here's another, rather different, approach which just
> occurred to me.  With the
> appended class filed-in, you can say:
>
>    "get the source for a random method"
>    source := (ScintillaStyler compiledMethodAt: #stylingStartBefore:in:)
>                        getSource.
>
>    "and a styler for styling methods"
>    styler := SmalltalkMethodStyler new.
>
>    "use a fake scintilla view to fool the styler into styling the text"
>    fake := FakeScintillaView
>                   text: source
>                   styler: styler.
>
> and then:
>
>    fake styles
>
> will answer a RunArray containing a ScintillaTextStyle for each character
> position in source.
>
> Or:
>
>    fake styledText.
>
> will answer an Array containing (in order) each fragment (word) of text
> with
> the corresponding style.
>
> It's one Hell of a hack, but quite fun in a perverted sort of way, and
> does
> have the advantage of picking up the configured styles ;-)
>

We use a very similar technique to test the operation of the styler. The
interface used by the styler on the ScintillaView for the actual styling
could be defined into a protocol that separates it out from all the other
view related stuff, so it seems like a perfectly legitimate technique to me
:-). Our MockScintillaView is below in case it helps any.

Regards

Blair

-----------------
Object subclass: #MockScintillaView
 instanceVariableNames: 'lastStyled tokens text currentTextStyles
styleIdMap'
 classVariableNames: ''
 poolDictionaries: 'ScintillaConstants'
 classInstanceVariableNames: ''!
MockScintillaView guid: (GUID fromString:
'{50616A84-12E3-4960-B005-82A37278383B}')!
MockScintillaView comment: 'To set up:

 mock := MockScintillaView new.
 mock textStyles: SmalltalkWorkspace defaultTextStyles

Then to style:

 styler := SmalltalkMethodStyler new.
 text := (Object>>#printString) getSource.
 mock text: text.
 styler
  colorTextFrom: 1
  to: text size
  in: mock.
 "Now can access the ''tokens''"
 mock tokens'!

!MockScintillaView methodsFor!

applyStyle: aSymbol toNext: anInteger
 self styleNext: anInteger mask: ((self styleNamed: aSymbol) ifNil: [0]
ifNotNil: [:style | style id])!

characterAt: anInteger
 ^text at: anInteger!

maxStyle
 ^31!

plainTextFrom: startInteger to: stopInteger
 ^text copyFrom: startInteger to: stopInteger!

plainTextRange: anInterval
 ^self plainTextFrom: anInterval start to: anInterval stop!

setCurrentTextStyles: aCollection
 | newStylesByName allocatedStyles newStylesById availableStyles count |
 count := aCollection size.
 allocatedStyles := OrderedCollection new: count.
 aCollection do: [:each | each id ifNotNil: [:id | allocatedStyles add:
id]].
 availableStyles := ((1 to: STYLE_DEFAULT - 1) , (STYLE_LASTPREDEFINED + 1
to: self maxStyle)
    difference: allocatedStyles) readStream.
 newStylesByName := IdentityDictionary new: count.
 newStylesById := IdentityDictionary new: count.
 aCollection do:
   [:each |
   each id isNil ifTrue: [each id: availableStyles next].
   newStylesByName at: each name put: each.
   newStylesById at: each id put: each].
 newStylesByName at: #normal ifAbsentPut: [ScintillaTextStyle normal].
 currentTextStyles := newStylesByName.
 styleIdMap := newStylesById!

startStylingFrom: anInteger
 lastStyled := anInteger - 1!

styleNamed: aSymbol
 "Answer a <ScintillaTextStyle> being the named style, or nil if the name is
not recognised."

 ^currentTextStyles at: aSymbol ifAbsent: []!

styleNext: anInteger mask: anInteger2
 | range |
 range := lastStyled + 1 to: lastStyled + anInteger.
 range isEmpty ifTrue: [^self].
 range stop > text size ifTrue: [^BoundsError signal: range stop].
 (tokens notEmpty and: [(tokens last at: 2) == anInteger2])
  ifTrue: [(tokens last at: 1) stop: range stop]
  ifFalse: [tokens addLast: (Array with: range with: anInteger2)].
 lastStyled := range stop!

styleWithId: anInteger
 ^styleIdMap at: anInteger
  ifAbsent:
   [(ScintillaTextStyle new)
    name: anInteger;
    yourself]!

stylingPosition
 ^lastStyled + 1!

text: aString
 text := aString.
 lastStyled := 0.
 tokens := OrderedCollection new!

textLength
 ^text size!

textStyles: aSet
 self setCurrentTextStyles: aSet!

tokens
 | answer lastStyle |
 answer := OrderedCollection new.
 lastStyle := nil.
 tokens do:
   [:each |
   | id style |
   id := each last bitAnd: self maxStyle.
   style := id == 0 ifTrue: [#whitespace] ifFalse: [(self styleWithId: id)
name].
   lastStyle == style
    ifTrue:
     [| last |
     last := answer last.
     last at: 1 put: (last first start to: each first stop).
     last at: 3 put: (self plainTextRange: last first)]
    ifFalse:
     [lastStyle := style.
     answer addLast: (Array
        with: each first
        with: style
        with: (self plainTextRange: each first))]].
 ^answer! !
!MockScintillaView categoriesFor: #applyStyle:toNext:!public!styling! !
!MockScintillaView categoriesFor: #characterAt:!public! !
!MockScintillaView categoriesFor: #maxStyle!public! !
!MockScintillaView categoriesFor: #plainTextFrom:to:!public! !
!MockScintillaView categoriesFor: #plainTextRange:!accessing!public! !
!MockScintillaView categoriesFor: #setCurrentTextStyles:!private!style
definition! !
!MockScintillaView categoriesFor: #startStylingFrom:!public! !
!MockScintillaView categoriesFor: #styleNamed:!accessing!public!styling! !
!MockScintillaView categoriesFor: #styleNext:mask:!public! !
!MockScintillaView categoriesFor: #styleWithId:!accessing!public!style
definition! !
!MockScintillaView categoriesFor: #stylingPosition!accessing!public! !
!MockScintillaView categoriesFor: #text:!public! !
!MockScintillaView categoriesFor: #textLength!public! !
!MockScintillaView categoriesFor: #textStyles:!public! !
!MockScintillaView categoriesFor: #tokens!public! !


Reply | Threaded
Open this post in threaded view
|

Re: getColoredSource??

Chris Uppal-3
Blair,

> The
> interface used by the styler on the ScintillaView for the actual styling
> could be defined into a protocol that separates it out from all the other
> view related stuff, so it seems like a perfectly legitimate technique to
> me :-).

I suspect that some of the more anal-retentive academic types would insist that
I wait for the protocol to be defined before using it -- I doubt if they'd
consider "run it under the debugger and patch in any methods which turn out to
be missing", to be an adequately robust example of Programming To The
Interface.

;-)

More seriously, it does suggest that there might be mileage in defining a real
protocol for the interaction between Scintilla styler and stylee -- it depends
on how fluid you expect that relationship to be in future.  Not something I'm
asking for, mind, just something to consider.

    -- chris