-
Notifications
You must be signed in to change notification settings - Fork 71
/
FakeStdinStream.class.st
94 lines (81 loc) · 2.25 KB
/
FakeStdinStream.class.st
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
"
Fake Standard input using a dialog to prompt for a line of input at a time.
"
Class {
#name : #FakeStdinStream,
#superclass : #WriteStream,
#instVars : [
'atEnd',
'simulator'
],
#pools : [
'VMBasicConstants'
],
#category : #'VMMaker-JITSimulation'
}
{ #category : #'instance creation' }
FakeStdinStream class >> for: aCogVMSimulator [
^(self basicNew simulator: aCogVMSimulator)
on: (String new: 80) from: 1 to: 0
"self new next"
]
{ #category : #'instance creation' }
FakeStdinStream class >> new [
^super on: (String new: 80) from: 1 to: 0
"self new next"
]
{ #category : #testing }
FakeStdinStream >> atEnd [
^atEnd ifNil: [atEnd := false]
]
{ #category : #accessing }
FakeStdinStream >> atEnd: aBoolean [
atEnd := aBoolean
]
{ #category : #accessing }
FakeStdinStream >> close [
atEnd := true
]
{ #category : #testing }
FakeStdinStream >> isFakeStdinStream [
^true
]
{ #category : #accessing }
FakeStdinStream >> next [
"Answer the next object in the Stream represented by the receiver.
If there are no more elements in the stream fill up the buffer by prompting for input"
| inputLine next |
position >= readLimit ifTrue:
[
inputLine := UIManager default
request: 'Input please!'
initialAnswer: ''.
inputLine ifNil: [self atEnd: true. ^nil].
collection size <= inputLine size ifTrue:
[collection := collection species new: inputLine size + 1].
collection
replaceFrom: 1 to: inputLine size with: inputLine startingAt: 1;
at: (readLimit := inputLine size + 1) put: Character lf.
position := 0 ].
next := collection at: (position := position + 1).
^next
" This does it with workspaces:
| ws r s |
s := Semaphore new.
ws := Workspace new contents: ''.
ws acceptAction: [:t| r := t asString. s signal].
[ws openLabel: 'Yo!'; shouldStyle: false.
(ws dependents detect: [:dep | dep isKindOf: PluggableTextMorph] ifNone: [nil]) ifNotNil:
[:textMorph| textMorph acceptOnCR: true; hasUnacceptedEdits: true]] fork.
Processor activeProcess == Project uiProcess
ifTrue: [[r isNil] whileTrue: [World doOneCycle]]
ifFalse: [s wait].
ws topView delete.
s wait. s signal.
r"
]
{ #category : #'initialize-release' }
FakeStdinStream >> simulator: aCogVMSimulator [
simulator := aCogVMSimulator.
atEnd := false
]