Skip to content

Commit

Permalink
ProfStef P9/10 updates
Browse files Browse the repository at this point in the history
  • Loading branch information
JanBliznicenko committed Sep 23, 2021
1 parent 66e37c8 commit cb4595a
Show file tree
Hide file tree
Showing 3 changed files with 18 additions and 16 deletions.
9 changes: 9 additions & 0 deletions src/ProfStef-Core/LessonView.class.st
Expand Up @@ -36,6 +36,14 @@ LessonView class >> menuOn: aBuilder [

]

{ #category : #accessing }
LessonView >> bindings [

"dynamic variable binding not needed for Lessons"

^ Dictionary new
]

{ #category : #gui }
LessonView >> buildText [
| scrolledText |
Expand Down Expand Up @@ -75,6 +83,7 @@ LessonView >> initialize [
window := self buildWindow.
shoutMorph := self buildText.
window addMorph: shoutMorph frame: (0 @ 0 corner: 1 @ 1).
window extent: 600 @ 450.
]

{ #category : #testing }
Expand Down
19 changes: 9 additions & 10 deletions src/ProfStef-Core/PharoSyntaxTutorial.class.st
Expand Up @@ -160,7 +160,7 @@ Blocks are anonymous methods that can be stored into variables and executed on d
Blocks are delimited by square brackets: []"
[GTPlayground open].
[StPlayground open].
"does not open a Browser because the block is not executed.
Expand All @@ -172,7 +172,7 @@ Here is a block that adds 2 to its argument (its argument is named x):"
[:x | x+2] value: 5.
[GTPlayground open] value.
[StPlayground open] value.
[:x | x+2] value: 10.
Expand Down Expand Up @@ -257,12 +257,11 @@ lesson:
Note you can run this tutorial again by evaluating: ''ProfStef go''.
''ProfStef previous'' returns to the previous lesson.
You can also Do it using the keyboard shortcut ''Ctrl + D''
(this varies according to your operating system/computer: it can be ''Cmd + D'' or ''Alt + D'').
You can also Do it using the keyboard shortcut ''Ctrl + D'' (or ''Cmd + D'' on MacOS).
Try to evaluate these expressions:"
GTPlayground open.
StPlayground open.
SmalltalkImage current aboutThisSystem.
Expand All @@ -283,9 +282,9 @@ For example, select the text below, open the menu and click on ''Inspect it'':"
1 / 2.
"You''ve seen the keyboard keys next to the ''Inspect it''? It indicates the Ctrl- (or Cmd- or Alt-) shortcut to execute this command.
"You''ve seen the keyboard keys next to the ''Inspect it''? It indicates the Ctrl- (or Cmd-) shortcut to execute this command.
Try ''Ctrl + I'' (or ''Cmd + I'' or ''Alt + I'') on the following expressions:"
Try ''Ctrl + I'' (or ''Cmd + I'') on the following expressions:"
DateAndTime today.
Expand Down Expand Up @@ -615,9 +614,9 @@ For example, select the text below, open the menu and click on ''Print it'':"
1 + 2.
"You''ve seen the keyboard keys next to the ''Print it''? It indicates the Ctrl- (or Cmd- or Alt-) shortcut to execute this command.
"You''ve seen the keyboard keys next to the ''Print it''? It indicates the Ctrl- (or Cmd-) shortcut to execute this command.
Try ''Ctrl + P'' (or ''Cmd + P'' or ''Alt + P'') on the following expressions:"
Try ''Ctrl + P'' (or ''Cmd + P'') on the following expressions:"
Date today.
Expand All @@ -639,7 +638,7 @@ lesson:
Take a look at method #ifFalse:ifTrue: source code of class True:"
(True>>#ifFalse:ifTrue:) definition.
(True>>#ifFalse:ifTrue:) sourceCode.
"Or just its comment:"
Expand Down
6 changes: 0 additions & 6 deletions src/ProfStef-Core/ProfStef.class.st
Expand Up @@ -116,12 +116,6 @@ ProfStef class >> goOn: aTutorialClass [
^ self default goOn: aTutorialClass.
]

{ #category : #navigating }
ProfStef class >> goToNextLesson [

self next
]

{ #category : #navigating }
ProfStef class >> last [

Expand Down

0 comments on commit cb4595a

Please sign in to comment.