Skip to content

Commit

Permalink
link model
Browse files Browse the repository at this point in the history
  • Loading branch information
pavel-krivanek committed Jul 16, 2018
1 parent 85f74fb commit 03ba156
Show file tree
Hide file tree
Showing 12 changed files with 111 additions and 15 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,63 @@
specs
defaultSpec

<spec: #default>

| fontWidth labelsWidth rowHeight checkboxWidth |
fontWidth := (StandardFonts defaultFont widthOfString: 'M').
labelsWidth := fontWidth * 8.
rowHeight := self inputTextHeight.
checkboxWidth := fontWidth * 2.

^ SpecLayout composed
newRow: [ :mainRow |
mainRow newColumn: [ :col |

col newRow: [ : row |
row add: #nameLabel right: labelsWidth.
row add: #nameTextInput ]
height: rowHeight.

col newRow: [ :row |
row add: #vmLabel right: labelsWidth.
row add: #vmInput ]
height: rowHeight.

col newRow: [ :row |
row add: #templateLabel right: labelsWidth.
row add: #templateInput ]
height: rowHeight.

col newRow: [ :row |
row add: #locationLabel right: labelsWidth.
row add: #locationInput ]
height: rowHeight.

col newRow: [ :row | ]. "fill the rest"

].

mainRow newColumn: [ :col |

col newRow: [ :row |
row add: #lastModificationLabel right: labelsWidth.
row add: #lastModificationInput ]
height: rowHeight.

col newRow: [ :row |
row add: #tagsLabel right: labelsWidth.
row add: #tagsInput ]
height: rowHeight.


col newRow: [ :row |
row add: #commentLabel right: labelsWidth.
row add: #commentInput ]
height: rowHeight*2.

col newRow: [ :row | ]. "fill the rest"

]].



Original file line number Diff line number Diff line change
@@ -1,9 +1,14 @@
initialization
fillFormWithWorkingModel

self nameTextInput text: self workingModel asString.
"self surnameTextInput text: self workingModel asString.
self number1Input text: self workingModel asString.
self number2Input text: self workingModel asString."
self workingModel ifNil: [ ^ self ].

self nameTextInput text: self workingModel name asString.
self vmInput text: self workingModel vm asString.
self templateInput text: self workingModel template asString.
self lastModificationInput text: self workingModel lastModification asString.
self tagsInput text: 'no tags support'.
self commentInput text: 'no comments support'.
self locationInput text: 'no location support'.


Original file line number Diff line number Diff line change
Expand Up @@ -3,25 +3,32 @@ initializeWidgets

nameLabel := self newLabel label: 'name:'.
nameTextInput := self newTextInput autoAccept: true.
nameTextInput enabled: false.

vmLabel := self newLabel label: 'VM version:'.
vmInput := self newTextInput autoAccept: true.

vmInput enabled: false.

templateLabel := self newLabel label: 'template:'.
templateInput := self newTextInput autoAccept: true.
templateInput enabled: false.


lastModificationLabel := self newLabel label: 'modified:'.
lastModificationInput := self newTextInput autoAccept: true.

lastModificationInput enabled: false.

tagsLabel := self newLabel label: 'tags:'.
tagsInput := self newTextInput autoAccept: true.
tagsInput enabled: false.

commentLabel := self newLabel label: 'comment:'.
commentInput := self newTextInput autoAccept: true.
commentInput enabled: false.

locationLabel := self newLabel label: 'location:'.
locationInput := self newTextInput autoAccept: true.

locationInput enabled: false.

self focusOrder
add: nameTextInput;
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,11 @@
specs
defaultSpec
<spec: #default>
^ SpecLayout composed newColumn: [ :column | column add: #imagesTable ]

^ SpecLayout composed
newColumn: [ :column |
column add: #imagesTable.
column addSplitter.
column add: #propertyPanel ];
yourself.

Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
actions
copySelectedImage
PhLCopyImageCommand new
setContext: self context;
setModel: self context;
execute
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
actions
deleteSelectedImage
PhLDeleteImageCommand new
setContext: self context;
setModel: self context;
execute.
self refresh
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
actions
firstlySelectedImage

^ imagesTable morph selectedItems size = 1
ifTrue: [ imagesTable morph selectedItems anyOne ]
ifFalse: [ nil ]
Original file line number Diff line number Diff line change
Expand Up @@ -11,5 +11,6 @@ initializeImageTable: aTableMorph
add: #vm width: 50;
add: #template width: 300;
add: #'last modification' accessing: #lastModification width: 100;
onAnnouncement: FTSelectionChanged do: [ :ann | self selectionChanged: ann];
onAnnouncement: FTStrongSelectionChanged do: [ :ann | self launchSelectedImageWithSettings ].
aTableMorph showRowIndex width: 50
Original file line number Diff line number Diff line change
@@ -1,8 +1,10 @@
initialization
initializeWidgets

propertyPanel := (self instantiate: PhLImagePresenter on: self).

self initializeToolbar.
self initializeStatusbar.
self initializeBody
self initializeBody.

propertyPanel := (self instantiate: PhLImagePresenter on: self firstlySelectedImage).


Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
actions
launchSelectedImageWithSettings
PhLLaunchImageCommand new
setContext: self context;
setModel: self context;
execute
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
actions
launchSelectedImageWithoutSettings
PhLLaunchImageWithoutSettingCommand new
setContext: self context;
setModel: self context;
execute
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
actions
selectionChanged: anAnnouncement

imagesTable morph selectedItems size = 1 ifTrue: [
propertyPanel model: imagesTable morph selectedItems anyOne ].

0 comments on commit 03ba156

Please sign in to comment.