Object subclass: #PNBaseClass instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'PetriNet'! !PNBaseClass methodsFor: 'initialize' stamp: 'pk 4/17/2004 11:37'! initialize "Implicitne vraci self" ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! PNBaseClass class instanceVariableNames: ''! !PNBaseClass class methodsFor: 'instance creation' stamp: 'pk 4/17/2004 11:38'! new "Konstruktor se standardni inicializaci predka. Od Squeaku 3.7 zbytedne" ^ super basicNew initialize. ! ! PNBaseClass subclass: #PNLink instanceVariableNames: 'from to ' classVariableNames: '' poolDictionaries: '' category: 'PetriNet'! !PNLink commentStamp: 'pk 4/17/2004 11:48' prior: 0! Propojeni v Petriho siti Structure: from PNTransition nebo PNPlace -- pocatecni element to PNTransition nebo PNPlace -- cilovy element ! !PNLink methodsFor: 'accessing' stamp: 'pk 4/13/2004 09:35'! from ^ from. ! ! !PNLink methodsFor: 'accessing' stamp: 'pk 4/17/2004 11:39'! from: anElement from := anElement. ! ! !PNLink methodsFor: 'accessing' stamp: 'pk 4/13/2004 09:35'! to ^ to. ! ! !PNLink methodsFor: 'accessing' stamp: 'pk 4/17/2004 11:40'! to: anElement to := anElement. ! ! !PNLink methodsFor: 'printing' stamp: 'pk 4/17/2004 13:02'! printOn: aStream aStream nextPutAll: ('link(',from asOop asString, ' - ', to asOop asString, ')').! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! PNLink class instanceVariableNames: ''! !PNLink class methodsFor: 'instance creation' stamp: 'pk 4/17/2004 11:39'! from: start to: end "Vytvoreni propojeni mezi dvema elementy Petriho site (prechod/misto)" | link | (start = end) ifTrue: [ self notify: 'Nezle propojit stejny prvek'. ^ nil. ]. link := self new. link from: start. link to: end. start isTransition ifTrue: [ start addOutput: link. ]. end isTransition ifTrue: [ end addInput: link. ]. ^ link.! ! PNBaseClass subclass: #PNPlace instanceVariableNames: 'marks ' classVariableNames: '' poolDictionaries: '' category: 'PetriNet'! !PNPlace commentStamp: 'pk 4/17/2004 11:50' prior: 0! Misto v Petriho siti Structure: marks Number -- pocet znacek v miste ! !PNPlace methodsFor: 'accessing' stamp: 'pk 4/17/2004 11:50'! marks "vrati pocet znacek" ^ marks.! ! !PNPlace methodsFor: 'accessing' stamp: 'pk 4/17/2004 11:51'! marks: count "Nastavi pocet znacek" marks := count.! ! !PNPlace methodsFor: 'testing' stamp: 'pk 4/13/2004 19:55'! isTransition ^false.! ! !PNPlace methodsFor: 'initialize' stamp: 'pk 4/13/2004 09:44'! initialize super initialize. self marks: 0.! ! !PNPlace methodsFor: 'printing' stamp: 'pk 4/17/2004 13:02'! printOn: aStream aStream nextPutAll: ('place[',self asOop asString,'](', self marks asString, ')'). ! ! !PNPlace methodsFor: 'marks' stamp: 'pk 4/13/2004 09:47'! addMark "prida znacku do mista" marks := marks + 1.! ! !PNPlace methodsFor: 'marks' stamp: 'pk 4/17/2004 11:51'! ready "Je misto pripravene vydat znacku?" ^ (marks > 0).! ! !PNPlace methodsFor: 'marks' stamp: 'pk 4/17/2004 11:51'! readyAccept "Je misto pripravene prijmout znacku?" ^ true.! ! !PNPlace methodsFor: 'marks' stamp: 'pk 4/17/2004 11:52'! removeMark "Odstarni jednu znacku z mista" marks > 0 ifTrue: [ marks := marks - 1 ]! ! PNBaseClass subclass: #PNTransition instanceVariableNames: 'input output enabled ' classVariableNames: '' poolDictionaries: '' category: 'PetriNet'! !PNTransition commentStamp: 'pk 4/17/2004 11:55' prior: 0! Prechod v Petriho siti Structure: input Set of PNLink -- mnozina vstupnich propojeni output Set of PNLink -- mnozina vystupnich propojeni enabled Boolean -- proveditelnost prechodu Nejdrive se provadi zjisteni proveditelnosti prechodu (simulateTransition) a az pote se vykonava vlastni prechod (performTransition) ! !PNTransition methodsFor: 'testing' stamp: 'pk 4/13/2004 09:23'! isTransition ^true.! ! !PNTransition methodsFor: 'initialize' stamp: 'pk 4/13/2004 09:06'! initialize super initialize. input := Set new. output := Set new.! ! !PNTransition methodsFor: 'building' stamp: 'pk 4/13/2004 09:23'! addInput: aLink "prida propojeni na vstup" input add: aLink.! ! !PNTransition methodsFor: 'building' stamp: 'pk 4/13/2004 09:23'! addOutput: aLink "prida propojeni na vystup" output add: aLink.! ! !PNTransition methodsFor: 'performation' stamp: 'pk 4/17/2004 11:58'! canPerformTransition "zjisti proveditelnost prechodu" input do: [:link | link from ready ifFalse: [ ^false. ] ]. output do: [:link | link to readyAccept ifFalse: [ ^false. ] ]. ^ true. ! ! !PNTransition methodsFor: 'performation' stamp: 'pk 4/17/2004 11:57'! performTransition "provede prechod v zavislosti na jeho proveditelnosti" enabled ifTrue: [ input do: [:link | link from removeMark]. output do: [:link | link to addMark] ]! ! !PNTransition methodsFor: 'performation' stamp: 'pk 4/17/2004 11:56'! reset "zrusi nasteveni proveditelnosti prechodu" enabled := nil. ! ! !PNTransition methodsFor: 'performation' stamp: 'pk 4/17/2004 11:56'! simulateTransition "nastavi proveditelnost prechodu" enabled := self canPerformTransition! ! !PNTransition methodsFor: 'printing' stamp: 'pk 4/17/2004 13:03'! printOn: aStream aStream nextPutAll: ('transition[',self asOop asString,'](in=', input size asString, ', out=', output size asString,')').! ! PNBaseClass subclass: #PetriNet instanceVariableNames: 'places transitions links ' classVariableNames: '' poolDictionaries: '' category: 'PetriNet'! !PetriNet commentStamp: 'pk 4/17/2004 12:10' prior: 0! Petriho sit PetriNet example1 Structure: places Dictionary of PNPlace -- mista transitions Dictionary of PNTransition -- prechody links Set of PNLink -- propojeni ! !PetriNet methodsFor: 'initialize' stamp: 'pk 4/13/2004 20:25'! initialize super initialize. places := Dictionary new. transitions := Dictionary new. links := Set new.! ! !PetriNet methodsFor: 'building' stamp: 'pk 4/17/2004 12:13'! addLinkFrom: symFrom to: symTo "prida propojeni" | from to link | (transitions includesKey: symFrom) ifTrue: [ from := transitions at: symFrom ]. (transitions includesKey: symTo) ifTrue: [ to := transitions at: symTo ]. (places includesKey: symFrom) ifTrue: [ from := places at: symFrom ]. (places includesKey: symTo) ifTrue: [ to := places at: symTo ]. ((from = nil) or: [ to = nil]) ifTrue: [ self notify: 'Nezle vytvorit propojeni'. ^ self. ]. link := PNLink from: from to: to. links add: link.! ! !PetriNet methodsFor: 'building' stamp: 'pk 4/17/2004 12:13'! addLinks: aCollection "prida kolekci propojeni" aCollection do: [:link | self addLinkFrom: (link first) to: (link second ). ].! ! !PetriNet methodsFor: 'building' stamp: 'pk 4/17/2004 12:14'! addMarks: aCollection "nastavi znacky" aCollection do: [:symbol | (places at: symbol) addMark. ].! ! !PetriNet methodsFor: 'building' stamp: 'pk 4/17/2004 12:14'! addPlace: aSymbol "prida misto" places at: aSymbol put: PNPlace new.! ! !PetriNet methodsFor: 'building' stamp: 'pk 4/17/2004 12:14'! addPlaces: aCollection "prida kolekci mist" aCollection do: [:place | self addPlace: place ].! ! !PetriNet methodsFor: 'building' stamp: 'pk 4/17/2004 12:14'! addTransition: aSymbol "prida prechod" transitions at: aSymbol put: PNTransition new.! ! !PetriNet methodsFor: 'building' stamp: 'pk 4/17/2004 12:14'! addTransitions: aCollection "prida kolekci prechodu" aCollection do: [:transition | self addTransition: transition ].! ! !PetriNet methodsFor: 'performing' stamp: 'pk 4/17/2004 12:59'! printOn: aStream aStream nextPutAll: ( 'Petri net places: ', (places asString), ' transitions: ', (transitions asString), ' links:', (links asString)) ! ! !PetriNet methodsFor: 'performing' stamp: 'pk 4/17/2004 12:13'! step "provede krok Petriho site" transitions do: [:transition | transition reset ]. transitions do: [:transition | transition simulateTransition. ]. transitions do: [:transition | transition performTransition. ].! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! PetriNet class instanceVariableNames: ''! !PetriNet class methodsFor: 'examples' stamp: 'pk 4/17/2004 12:12'! example1 | net | net := PetriNet new. net addPlaces: #(p1 p2 p3 p4 p5). net addTransitions: #(c1 c2 c3). net addLinks: #((p1 c1) (p2 c1) (p3 c1) (c1 p4) (c1 p5) (p4 c2) (c2 p1) (p5 c3) (c3 p3)). net addMarks: #(p1 p2 p3). net step.! !