Skip to content

Commit

Permalink
Some formatter action
Browse files Browse the repository at this point in the history
  • Loading branch information
Sohn123 committed Jul 28, 2022
1 parent fc5b0f4 commit 3bb3a86
Show file tree
Hide file tree
Showing 53 changed files with 87 additions and 88 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -2,11 +2,11 @@
offsetBy: aNumber

|n1 n2 n|

n1 := (self via - self start) normal.
n2 := (self end - self via) normal.
n := n1 + n2.

^ self class
from: self start + (aNumber * n1)
via: self via + (2 * aNumber * n / (n dotProduct: n))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,4 +2,4 @@
asBezier2Segments: pixelError

^ (self asBezier2Points: pixelError)
groupsOf: 3 atATimeCollect: [:a :b :c | Bezier2Segment controlPoints: { a . b . c }]
groupsOf: 3 atATimeCollect: [:a :b :c | Bezier2Segment controlPoints: {a . b . c}]
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
rendering
renderBezier2SegmentRun: segments fill: fillStyle stroke: strokeStyle strokeWidth: aNumber transform: aMatrix on: aCanvas

aCanvas preserveStateDuring: [:bc |
bc
aaLevel: 4;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ renderBezier3Segments: segments fill: fillStyle stroke: strokeStyle strokeWidth:
bezier2Run := SVGBezier2SegmentRun
fromBezier3Segments: segments
precision: aMatrix compositeScale r reciprocal.

self
renderBezier2SegmentRun: bezier2Run
fill: fillStyle
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
rendering
renderEllipse: anSVGEllipse on: aCanvas
"Render the given object on the canvas."

self
renderBezier3Segments: (Bezier3Segment
makeEllipseSegments: anSVGEllipse rectangle)
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
helpers
stitchedClosed
"Answer a version of the receiver where the ends of successive segments match."

|result avg|
result := self copy.
result segments ifEmpty: [^ result].
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
helpers
stroke: aNumber transform: aTransform

^ { ((self offsetBy: aNumber / 2) transformed: aTransform) points
. ((self offsetBy: aNumber / 2 negated) transformed: aTransform) points }
^ {((self offsetBy: aNumber / 2) transformed: aTransform) points
. ((self offsetBy: aNumber / 2 negated) transformed: aTransform) points}
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
helpers
containsPoint: aPoint

^ self visible and: [self bounds containsPoint: aPoint]
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
helpers
fullDrawOn: aCanvas
"Draw the full Morphic structure on the given Canvas"

self visible ifFalse: [^ self].
(self hasProperty: #errorOnDraw) ifTrue:[^ self drawErrorOn: aCanvas].
"Note: At some point we should generalize this into some sort of
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ initialization
setStyleFromSVG: anElement
"Set the dictionary of the style parameters from the element."

|svgStyle|
|svgStyle|
svgStyle := self styleFromSVG: anElement.
self style addAll: svgStyle.
SVGStyleComposer composeStyleFor: self with: svgStyle
Original file line number Diff line number Diff line change
Expand Up @@ -5,13 +5,13 @@ createFillFromSVGLinearGradient: anElement
|start end ramp transformation|
transformation := self transformFromSVGAttribute: (anElement attributeAt: 'gradientTransform').
ramp := self createRampFromSVGGradient: anElement.

start := (anElement attributeAt: 'x1' ifAbsent: 0) asSVGNumberOrPercentage @ (anElement attributeAt: 'y1' ifAbsent: 0) asSVGNumberOrPercentage.
end := (anElement attributeAt: 'x2' ifAbsent: 1) asSVGNumberOrPercentage @ (anElement attributeAt: 'y2' ifAbsent: 0) asSVGNumberOrPercentage.

start := transformation transformPoint: start.
end := transformation transformPoint: end.

self setFill: (anElement attributeAt: 'id')
to: ((SVGGradientFillStyle ramp: ramp)
originalElement: anElement;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,13 +5,13 @@ createFillFromSVGRadialGradient: anElement
|center radius ramp transformation origin direction|
transformation := self transformFromSVGAttribute: (anElement attributeAt: 'gradientTransform').
ramp := self createRampFromSVGGradient: anElement.

center := (anElement attributeAt: 'cx' ifAbsent: 0.5) asSVGNumberOrPercentage @ (anElement attributeAt: 'cy' ifAbsent: 0.5) asSVGNumberOrPercentage.
radius := (anElement attributeAt: 'r' ifAbsent: 0.5) asSVGNumberOrPercentage.

origin := transformation transformPoint: center.
direction := (transformation transformPoint: radius asPoint + center) - origin.

self setFill: (anElement attributeAt: 'id')
to: ((SVGGradientFillStyle ramp: ramp)
originalElement: anElement;
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,6 @@ applyStyleOf: aMorph on: anXMLElement
((key = 'stroke') or: [key = 'fill'])
ifTrue: [(value isColor)
ifTrue: [convertedValue := value asHTMLColor]
ifFalse: [ convertedValue := self urlForGradient: value]].
ifFalse: [convertedValue := self urlForGradient: value]].

anXMLElement attributeAt: key put: convertedValue asString]
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,6 @@ serializeGradientsOf: anSVGMorph on: anXMLElement
|defs|
defs := XMLElement new
name: 'defs'.
anSVGMorph fills do: [ :fill |
defs addElement: fill originalElement.].
anSVGMorph fills do: [:fill |
defs addElement: fill originalElement].
anXMLElement addElement: defs]
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
helpers
computePixelRampOfSize: length

"Compute the pixel ramp in the receiver"
|bits lastColor lastIndex nextIndex nextColor distance theta ramp step lastWord nextWord|

ramp := self colorRamp asSortedCollection: [:a1 :a2| a1 key < a2 key].
bits := Bitmap new: length.
lastColor := ramp first value.
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
as yet unclassified
fromDroppedFile: filename
"opens a Stream on a given file"

^ (self fromFile: filename) openInWorld
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
as yet unclassified
fromFile: filename
"Open an SVGMorph from the given file."

|s answer|
s := FileStream oldFileNamed: filename.
s ifNil: [^ nil].
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
as yet unclassified
fromString: aString
"creates SVGMorph from xml string"

^ self fromFileStream:(ReadStream on: aString)
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
helpers
styleIn: aComponent fromSVGStyle: svgStyle
"Answer a dictionary of the style parameters for the given svg style dictionary."

self subclassResponsibility
Original file line number Diff line number Diff line change
@@ -1,12 +1,12 @@
as yet unclassified
composeStyleFor: aSVGComponent with: aSVGStyle
| svgStyleComposer |

|svgStyleComposer|

svgStyleComposer := self new.

svgStyleComposer balloonStyle: aSVGComponent composedStyle.
svgStyleComposer svgStyle: aSVGStyle.

^ svgStyleComposer setStyles

Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
styling
addStyleAt: aKey defaultValue: aValue
addStyleAt: aKey defaultValue: aValue

(self svgStyle includesKey: aKey)
ifTrue: [self balloonStyle at: aKey put: (self svgStyle at: aKey).]
ifTrue: [self balloonStyle at: aKey put: (self svgStyle at: aKey)]
ifFalse: [(self balloonStyle includesKey: aKey)
ifFalse: [self balloonStyle at: aKey put: aValue]].
ifFalse: [self balloonStyle at: aKey put: aValue]]
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
accessing
balloonStyle: anObject

balloonStyle := anObject.
balloonStyle := anObject
Original file line number Diff line number Diff line change
@@ -1,3 +1,3 @@
styling
newFillOpacity
^ ((self svgStyle includesKey: 'opacity') or: [self svgStyle includesKey: 'fill-opacity']) or: [self svgStyle includesKey: 'fill'].
^ ((self svgStyle includesKey: 'opacity') or: [self svgStyle includesKey: 'fill-opacity']) or: [self svgStyle includesKey: 'fill']
Original file line number Diff line number Diff line change
@@ -1,3 +1,3 @@
styling
newStrokeOpacity
^ ((self svgStyle includesKey: 'opacity') or: [self svgStyle includesKey: 'stroke-opacity']) or: [self svgStyle includesKey: 'stroke'].
^ ((self svgStyle includesKey: 'opacity') or: [self svgStyle includesKey: 'stroke-opacity']) or: [self svgStyle includesKey: 'stroke']
Original file line number Diff line number Diff line change
Expand Up @@ -8,4 +8,4 @@ setDisplayVisibilityStyle
(self svgStyle includesKey: 'visibility')
ifTrue: [self balloonStyle at: 'visibility' put: ((self svgStyle at: 'visibility') withBlanksTrimmed = 'visible')]
ifFalse: [(self balloonStyle includesKey: 'visibility')
ifFalse: [self balloonStyle at: 'visibility' put: self defaultVisibility]].
ifFalse: [self balloonStyle at: 'visibility' put: self defaultVisibility]]
Original file line number Diff line number Diff line change
@@ -1,12 +1,11 @@
styling
setFillStyle
self

self
addStyleAt: 'opacity' defaultValue: self defaultOpacity;
addStyleAt: 'fill-opacity' defaultValue: self defaultFillOpacity;
addStyleAt: 'fill' defaultValue: self defaultFill;
addStyleAt: 'fill-rule' defaultValue: self defaultFillRule.
self newFillOpacity ifTrue: [ self balloonStyle at: 'fill' put: ((self balloonStyle at: 'fill')

self newFillOpacity ifTrue: [self balloonStyle at: 'fill' put: ((self balloonStyle at: 'fill')
alphaMixed: (self balloonStyle at: 'fill-opacity') * (self balloonStyle at: 'opacity'))]

Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
styling
setFontStyle

| textStyle|
|textStyle|
self addStyleAt: 'font-size' defaultValue: self defaultSVGTextSize.
(self svgStyle includesKey: 'font-family')
ifTrue: [textStyle := TextStyle named: (self svgStyle at: 'font-family').
Expand Down
Original file line number Diff line number Diff line change
@@ -1,11 +1,11 @@
styling
setStrokeStyle

self
self
addStyleAt: 'stroke-width' defaultValue: self defaultStrokeWidth;
addStyleAt: 'stroke-linecap' defaultValue: self defaultStrokeLinecap;
addStyleAt: 'stroke-opacity' defaultValue: self defaultStrokeOpacity;
addStyleAt: 'stroke' defaultValue: self defaultStroke.
self newStrokeOpacity ifTrue: [ self balloonStyle at: 'stroke' put: ((self balloonStyle at: 'stroke')

self newStrokeOpacity ifTrue: [self balloonStyle at: 'stroke' put: ((self balloonStyle at: 'stroke')
alphaMixed: (self balloonStyle at: 'stroke-opacity') * (self balloonStyle at: 'opacity'))]
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
styling
setStyles

self
self
setFontStyle;
setFillStyle;
setStrokeStyle;
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
accessing
svgStyle: anObject

svgStyle := anObject.
svgStyle := anObject
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ private
methodsLinesDo: aBlock

self methodTestObjects do: [:aSLMethodTestObject |
| lines |
|lines|
lines := aSLMethodTestObject sourceCode string lines.
((lines size >= 2) and: [lines second includesSubstring: '"@linter-ignore"'])
ifFalse: [
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ tests
testMethodNameIsLowerCase

self methodsLinesDo: [:lines |
| firstChar |
|firstChar|
firstChar := lines first first.
firstChar isLetter
ifTrue: [self assert: firstChar isLowercase]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,4 +4,4 @@ testSpaceAfterReturnCharacter

self methodsLinesDo: [:lines |
lines do: [:line |
self assert: ((line includes: $^) ==> [('\^[^ ]' asRegex search: line) not])]]
self assert: ((line includes: $^) ==> [('\^[^]' asRegex search: line) not])]]
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
testing
fetchClasses: aCollection

aCollection do: [ :aClass |
aCollection do: [:aClass |
aClass category ifNotNil: [
(self category: aClass category)
add: aClass name]]
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,9 @@ testBoundaryParsingLinear
|gradient end start |
self wantsToTestSunsetGradient.
gradient := (self subject fills at: 'sizedGradient').

start := 0.5 @ 0.
end := 0.9 @ 0.7.

self assert: start equals: gradient origin.
self assert: end-start equals: gradient direction
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
tests
testColorParsing

| colorRamp |
|colorRamp|
self wantsToTestSunsetGradient.
colorRamp := (self subject fills at: 'myGradient') colorRamp.

self assert: Color yellow equals: colorRamp first value.
self assert: 0 equals: colorRamp first key.
self assert: Color red equals: colorRamp second value.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,9 @@ testDefaultBoundariesLinear
|gradient end start |
self wantsToTestSunsetGradient.
gradient := (self subject fills at: 'myGradient').

start := 0.0 @ 0.
end := 1 @ 0.

self assert: start equals: gradient origin.
self assert: end-start equals: gradient direction
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,9 @@ testDefaultBoundariesRadial
|gradient direction start |
self wantsToTestSunsetGradient.
gradient := (self subject fills at: 'radialGradient1').

start := 0.5 @ 0.5.
direction := 0.5 @ 0.

self assert: start equals: gradient origin.
self assert: direction equals: gradient direction
Loading

0 comments on commit 3bb3a86

Please sign in to comment.