* cormen book
[mascara-docs.git] / i86 / mtx-16-bit / mtx / samples / SERIAL / ts.x
blob1b6874600612eff90a7f1b6ac0860d4ef8a91d52
1                 BOOTSEG = 0x1000
2 .globl begtext, begdata, begbss                      !! needed by linker
4 !               IMPORTS and EXPORTS
5 .globl _resetVideo,_getc,_putc,_diskr,_setes,_inces 
6 .globl _main,_prints                                 
7 .globl _tswitch,_running,_scheduler
9 .globl _int80h,_kcinth
10 .globl _goUmode
11 .globl _get_byte,_put_byte
12 .globl _proc, _procsize
13 .globl _color
14 .globl _lock, _unlock,_restore, _in_byte, _out_byte
15 .globl _inkmode
16 .globl _tinth, _thandler
17 .globl _kbinth,_kbhandler
18 .globl _s0inth, _s0handler
19 .globl _s1inth, _s1handler
21 .text                                                !! these tell as:  
22 begtext:                                             !! text,data,bss segments
23 .data                                                !! are all the same.
24 begdata:
25 .bss
26 begbss:
27 .text                                                
29         mov     ax,cs                   ! establish segments 
30         mov     ds,ax                   ! we know ES,CS=0x1000. Let DS=CS  
31         mov     ss,ax                   ! SS = CS ===> all point to 0x1000
32         mov     es,ax
34         mov     sp,#_proc               ! SP -> proc[0].kstack HIGH end
35         add     sp,_procsize
37         mov     ax,#0x0003
38         int     #0x10
40         call _main                      ! call main[] in C
42 ! if ever return, just hang     
43         mov   ax, #msg
44         push  ax
45         call  _prints
46 dead:   jmp   dead
47 msg:    .asciz "BACK TO ASSEMBLY AND HANG\n\r"    
48         
49 !*************************************************************
50 !     KCW  added functions for MT system
51 !************************************************************
52 _tswitch:
53           push   ax
54           push   bx
55           push   cx
56           push   dx
57           push   bp
58           push   si
59           push   di
60           pushf
61           mov    bx, _running
62           mov    2[bx], sp
64 find:     call   _scheduler
66 resume:   mov    bx, _running
67           mov    sp, 2[bx]
68           popf
69           pop    di
70           pop    si
71           pop    bp
72           pop    dx
73           pop    cx
74           pop    bx
75           pop    ax
76           ret
78 USS =  4
79 USP =  6
81 ! as86 macro: parameters are ?1 ?2, etc 
82 ! as86 -m -l listing src (generates listing with macro expansion)
84          MACRO INTH
85           push ax
86           push bx
87           push cx
88           push dx
89           push bp
90           push si
91           push di
92           push es
93           push ds
95           push cs
96           pop  ds
98           inc _inkmode          ! enter Kmode : ++inkmode
99           cmp _inkmode,#1       ! if inkmode == 1 ==> interrupt was in Umode
100           jg  ?1                ! imode>1 : was in Kmode: bypass saving uss,usp
102           ! was in Umode: save interrupted (SS,SP) into proc
103           mov si,_running       ! ready to access proc
104           mov USS[si],ss        ! save SS  in proc.USS
105           mov USP[si],sp        ! save SP  in proc.USP
107           ! change DS,ES,SS to Kernel segment
108           mov  di,ds            ! stupid !!        
109           mov  es,di            ! CS=DS=SS=ES in Kmode
110           mov  ss,di
112           mov  sp, _running     ! sp -> running's kstack[] high end
113           add  sp, _procsize
115 ?1:       call  _?1             ! call handler in C
117           br    _ireturn        ! return to interrupted point
119          MEND
122 _int80h: INTH kcinth
123 _tinth:  INTH thandler
124 _kbinth: INTH kbhandler
125 _s0inth: INTH s0handler
126 _s1inth: INTH s1handler
128 !*===========================================================================*
129 !*              _ireturn  and  goUmode()                                     *
130 !*===========================================================================*
131 ! ustack contains    flag,ucs,upc, ax,bx,cx,dx,bp,si,di,es,ds
132 ! uSS and uSP are in proc
133 _ireturn:
134 _goUmode:
135         cli
136         dec _inkmode            ! --inkmode
137         cmp _inkmode,#0         ! inkmode==0 means was in Umode
138         jg  xkmode
140 ! restore uSS, uSP from running PROC
141         mov si,_running         ! si -> proc
142         mov ax,USS[si]
143         mov ss,ax               ! restore SS
144         mov sp,USP[si]          ! restore SP
145 xkmode:                         
146         pop ds
147         pop es
148         pop di
149         pop si
150         pop bp
151         pop dx
152         pop cx
153         pop bx
154         pop ax 
155         iret
157         
158         !--------------------------------
159         ! resetVideo[] : clear screen, home cursor
160         !--------------------------------
161 _resetVideo:    
162         mov     ax, #0x0012             ! 640x480 color
163         int     0x10                    ! call BIOS to do it
164         mov     ax, #0x0200             ! Home the cursor
165         xor     bx, bx
166         xor     dx, dx
167         int     0x10                    ! call BIOS to home cursor 
168         ret 
170        !---------------------------------------
171        ! int diskr[cyl, head, sector, buf] 
172        !            4     6     8     10
173        !---------------------------------------
174 _diskr:                             
175         push  bp
176         mov   bp,sp
177         
178         movb  dl, #0x00        ! drive 0=fd0
179         movb  dh, 6[bp]        ! head
180         movb  cl, 8[bp]        ! sector
181         incb  cl               ! inc sector by 1 to suit BIOS
182         movb  ch, 4[bp]        ! cyl
183         mov   ax, #0x0202      ! READ 2 sectors 
184         mov   bx, 10[bp]       ! put buf value in BX ==> addr=[ES,BX]
185         int  0x13              ! call BIOS to read the block 
186         jb   error             ! to error if CarryBit is on [read failed]
188         mov   sp,bp
189         pop   bp
190         ret
192         !---------------------------------------------
193         !  char getc[]   function: returns a char
194         !---------------------------------------------
195 !_getc:
196         xorb   ah,ah           ! clear ah
197         int    0x16            ! call BIOS to get a char in AX
198         ret 
200         !----------------------------------------------
201         ! void putc[char c]  function: print a char
202         !----------------------------------------------
203 !_putc:           
204         push   bp
205         mov    bp,sp
206         
207         movb   al,4[bp]        ! get the char into aL
208         movb   ah,#14          ! aH = 14
210         mov    bx,_color       ! bL = color B Cyan C Red  
211         int    0x10            ! call BIOS to display the char
213         mov    sp,bp
214         pop    bp
215         ret
216                 
217         
218 _setes:  push  bp
219          mov   bp,sp
220         
221          mov   ax,4[bp]        
222          mov   es,ax
224          mov   sp,bp
225          pop   bp
226          ret
228 _inces:                        ! inces[] inc ES by 0x40, or 1K
229          mov   ax,es
230          add   ax,#0x40
231          mov   es,ax
232          ret
234         !------------------------------
235         !       error & reboot
236         !------------------------------
237 error:
238         mov  bx, #bad
239         push bx
240         call _prints
241         
242         int  0x19                       ! reboot
243 bad:    .asciz  "Error!"
246 !*===========================================================================*
247 !*                              get_byte                                     *
248 !*===========================================================================*
249 ! This routine is used to fetch a byte from anywhere in memory.
250 ! The call is:
251 !     c = get_byte[segment, offset]
252 ! where
253 !     'segment' is the value to put in es
254 !     'offset'  is the offset from the es value
255 _get_byte:
256         push bp                 ! save bp
257         mov bp,sp               ! we need to access parameters
259         push es                 ! save es
260         push bx
262         mov es,4[bp]            ! load es with segment value
263         mov bx,6[bp]            ! load bx with offset from segment
264         seg es                  ! go get the byte
265         movb al,[bx]            ! al = byte
266         xorb ah,ah              ! ax = byte
268         pop bx
269         pop es                  ! restore es
271         mov bp,sp
272         pop bp                  ! restore bp
273         ret                     ! return to caller
276 !*===========================================================================*
277 !*                              put_byte                                     *
278 !*===========================================================================*
279 ! This routine is used to put a word to anywhere in memory.
280 ! The call is:
281 !           put_byte[char,segment,offset]
282 ! where
283 !     char is a byte
284 !     'segment' is a segment
285 !     'offset'  is the offset from the segment
286 _put_byte:
287         push bp                 ! save bp
288         mov  bp,sp              ! we need to access parameters
290         push es                 ! save es
291         push bx
293         mov  es,6[bp]           ! load es with segment value
294         mov  bx,8[bp]           ! load bx with offset from segment
295         movb al,4[bp]           ! load byte in aL
296         seg  es                 ! go put the byte to [ES, BX]
297         movb  [bx],al           ! there it goes
299         pop  bx                 ! restore bx
300         pop  es                 ! restore es
302         mov  bp,sp
303         pop  bp                 ! restore bp
304         ret                     ! return to caller
305 !*===========================================================================*
306 !*                       old_flag=lock()                                     *
307 !*===========================================================================*
308 ! Disable CPU interrupts.
309 _lock:  
310         pushf                   ! save flags on stack
311         cli                     ! disable interrupts
312         pop ax                  ! pop saved flag into ax
313         ret                     ! return old_flag
316 !*===========================================================================*
317 !*                              unlock                                       *
318 !*===========================================================================*
319 ! Enable CPU interrupts.
320 _unlock:
321         sti                     ! enable interrupts
322         ret                     ! return to caller
324 !*===========================================================================*
325 !*                              restore(old_flag)                            *
326 !*===========================================================================*
327 ! Restore enable/disable bit to the value it had before last lock.
328 _restore:
329         push bp
330         mov  bp,sp
331        
332         push 4[bp]
333         popf                    ! restore old_flag
335         mov  sp,bp
336         pop  bp
337         ret                     ! return to caller
340 !*===========================================================================*
341 !*                              in_byte                                      *
342 !*===========================================================================*
343 ! PUBLIC unsigned in_byte[port_t port];
344 ! Read an [unsigned] byte from the i/o port  port  and return it.
346 _in_byte:
347         push    bp
348         mov     bp,sp
349         mov     dx,4[bp]
350         in      ax,dx                   ! input 1 byte
351         subb    ah,ah           ! unsign extend
352         pop     bp
353         ret
355 !*===========================================================================*
356 !*                              out_byte                                     *
357 !*==============================================================
358 ! out_byte[port_t port, int value];
359 ! Write  value  [cast to a byte]  to the I/O port  port.
361 _out_byte:
362         push    bp
363         mov     bp,sp
364         mov     dx,4[bp]
365         mov     ax,6[bp]
366         outb    dx,al           ! output 1 byte
367         pop     bp
368         ret