⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 klib386.s.cpp

📁 一个简单的操作系统minix的核心代码
💻 CPP
📖 第 1 页 / 共 2 页
字号:
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
				src/kernel/klib386.s	 	 
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

08100	#
08101	! sections
08102	
08103	.sect .text; .sect .rom; .sect .data; .sect .bss
08104	
08105	#include <minix/config.h>
08106	#include <minix/const.h>
08107	#include "const.h"
08108	#include "sconst.h"
08109	#include "protect.h"
08110	
08111	! This file contains a number of assembly code utility routines needed by the
08112	! kernel.  They are:
08113	
08114	.define _monitor        ! exit Minix and return to the monitor
08115	.define _check_mem      ! check a block of memory, return the valid size
08116	.define _cp_mess        ! copies messages from source to destination
08117	.define _exit           ! dummy for library routines
08118	.define __exit          ! dummy for library routines
08119	.define ___exit         ! dummy for library routines
08120	.define ___main         ! dummy for GCC
08121	.define _in_byte        ! read a byte from a port and return it
08122	.define _in_word        ! read a word from a port and return it
08123	.define _out_byte       ! write a byte to a port
08124	.define _out_word       ! write a word to a port
08125	.define _port_read      ! transfer data from (disk controller) port to memory
08126	.define _port_read_byte ! likewise byte by byte
08127	.define _port_write     ! transfer data from memory to (disk controller) port
08128	.define _port_write_byte ! likewise byte by byte
08129	.define _lock           ! disable interrupts
08130	.define _unlock         ! enable interrupts
08131	.define _enable_irq     ! enable an irq at the 8259 controller
08132	.define _disable_irq    ! disable an irq
08133	.define _phys_copy      ! copy data from anywhere to anywhere in memory
08134	.define _mem_rdw        ! copy one word from [segment:offset]
08135	.define _reset          ! reset the system
08136	.define _mem_vid_copy   ! copy data to video ram
08137	.define _vid_vid_copy   ! move data in video ram
08138	.define _level0         ! call a function at level 0
08139	
08140	! The routines only guarantee to preserve the registers the C compiler
08141	! expects to be preserved (ebx, esi, edi, ebp, esp, segment registers, and
08142	! direction bit in the flags).
08143	
08144	! imported variables
08145	
08146	.sect .bss
08147	.extern _mon_return, _mon_sp
08148	.extern _irq_use
08149	.extern _blank_color
08150	.extern _ext_memsize
08151	.extern _gdt
08152	.extern _low_memsize
08153	.extern _sizes
08154	.extern _vid_seg
08155	.extern _vid_size
08156	.extern _vid_mask
08157	.extern _level0_func
08158	
08159	.sect .text
08160	!*===========================================================================*
08161	!*                              monitor                                      *
08162	!*===========================================================================*
08163	! PUBLIC void monitor();
08164	! Return to the monitor.
08165	
08166	_monitor:
08167	        mov     eax, (_reboot_code)     ! address of new parameters
08168	        mov     esp, (_mon_sp)          ! restore monitor stack pointer
08169	    o16 mov     dx, SS_SELECTOR         ! monitor data segment
08170	        mov     ds, dx
08171	        mov     es, dx
08172	        mov     fs, dx
08173	        mov     gs, dx
08174	        mov     ss, dx
08175	        pop     edi
08176	        pop     esi
08177	        pop     ebp
08178	    o16 retf                            ! return to the monitor
08179	
08180	
08181	!*===========================================================================*
08182	!*                              check_mem                                    *
08183	!*===========================================================================*
08184	! PUBLIC phys_bytes check_mem(phys_bytes base, phys_bytes size);
08185	! Check a block of memory, return the amount valid.
08186	! Only every 16th byte is checked.
08187	! An initial size of 0 means everything.
08188	! This really should do some alias checks.
08189	
08190	CM_DENSITY      =       16
08191	CM_LOG_DENSITY  =       4
08192	TEST1PATTERN    =       0x55            ! memory test pattern 1
08193	TEST2PATTERN    =       0xAA            ! memory test pattern 2
08194	
08195	CHKM_ARGS       =       4 + 4 + 4       ! 4 + 4
08196	!                       ds ebx eip      base size
08197	
08198	_check_mem:
08199	        push    ebx
08200	        push    ds
08201	    o16 mov     ax, FLAT_DS_SELECTOR
08202	        mov     ds, ax
08203	        mov     eax, CHKM_ARGS(esp)
08204	        mov     ebx, eax
08205	        mov     ecx, CHKM_ARGS+4(esp)
08206	        shr     ecx, CM_LOG_DENSITY
08207	cm_loop:
08208	        movb    dl, TEST1PATTERN
08209	        xchgb   dl, (eax)               ! write test pattern, remember original
08210	        xchgb   dl, (eax)               ! restore original, read test pattern
08211	        cmpb    dl, TEST1PATTERN        ! must agree if good real memory
08212	        jnz     cm_exit                 ! if different, memory is unusable
08213	        movb    dl, TEST2PATTERN
08214	        xchgb   dl, (eax)
08215	        xchgb   dl, (eax)
08216	        add     eax, CM_DENSITY
08217	        cmpb    dl, TEST2PATTERN
08218	        loopz   cm_loop
08219	cm_exit:
08220	        sub     eax, ebx
08221	        pop     ds
08222	        pop     ebx
08223	        ret
08224	
08225	
08226	!*===========================================================================*
08227	!*                              cp_mess                                      *
08228	!*===========================================================================*
08229	! PUBLIC void cp_mess(int src, phys_clicks src_clicks, vir_bytes src_offset,
08230	!                     phys_clicks dst_clicks, vir_bytes dst_offset);
08231	! This routine makes a fast copy of a message from anywhere in the address
08232	! space to anywhere else.  It also copies the source address provided as a
08233	! parameter to the call into the first word of the destination message.
08234	!
08235	! Note that the message size, "Msize" is in DWORDS (not bytes) and must be set
08236	! correctly.  Changing the definition of message in the type file and not
08237	! changing it here will lead to total disaster.
08238	
08239	CM_ARGS =       4 + 4 + 4 + 4 + 4       ! 4 + 4 + 4 + 4 + 4
08240	!               es  ds edi esi eip      proc scl sof dcl dof
08241	
08242	        .align  16
08243	_cp_mess:
08244	        cld
08245	        push    esi
08246	        push    edi
08247	        push    ds
08248	        push    es
08249	
08250	        mov     eax, FLAT_DS_SELECTOR
08251	        mov     ds, ax
08252	        mov     es, ax
08253	
08254	        mov     esi, CM_ARGS+4(esp)             ! src clicks
08255	        shl     esi, CLICK_SHIFT
08256	        add     esi, CM_ARGS+4+4(esp)           ! src offset
08257	        mov     edi, CM_ARGS+4+4+4(esp)         ! dst clicks
08258	        shl     edi, CLICK_SHIFT
08259	        add     edi, CM_ARGS+4+4+4+4(esp)       ! dst offset
08260	
08261	        mov     eax, CM_ARGS(esp)       ! process number of sender
08262	        stos                            ! copy number of sender to dest message
08263	        add     esi, 4                  ! do not copy first word
08264	        mov     ecx, Msize - 1          ! remember, first word does not count
08265	        rep
08266	        movs                            ! copy the message
08267	
08268	        pop     es
08269	        pop     ds
08270	        pop     edi
08271	        pop     esi
08272	        ret                             ! that is all folks!
08273	
08274	
08275	!*===========================================================================*
08276	!*                              exit                                         *
08277	!*===========================================================================*
08278	! PUBLIC void exit();
08279	! Some library routines use exit, so provide a dummy version.
08280	! Actual calls to exit cannot occur in the kernel.
08281	! GNU CC likes to call ___main from main() for nonobvious reasons.
08282	
08283	_exit:
08284	__exit:
08285	___exit:
08286	        sti
08287	        jmp     ___exit
08288	
08289	___main:
08290	        ret
08291	
08292	
08293	!*===========================================================================*
08294	!*                              in_byte                                      *
08295	!*===========================================================================*
08296	! PUBLIC unsigned in_byte(port_t port);
08297	! Read an (unsigned) byte from the i/o port  port  and return it.
08298	
08299	        .align  16
08300	_in_byte:
08301	        mov     edx, 4(esp)             ! port
08302	        sub     eax, eax
08303	        inb     dx                      ! read 1 byte
08304	        ret
08305	
08306	
08307	!*===========================================================================*
08308	!*                              in_word                                      *
08309	!*===========================================================================*
08310	! PUBLIC unsigned in_word(port_t port);
08311	! Read an (unsigned) word from the i/o port  port  and return it.
08312	
08313	        .align  16
08314	_in_word:
08315	        mov     edx, 4(esp)             ! port
08316	        sub     eax, eax
08317	    o16 in      dx                      ! read 1 word
08318	        ret
08319	
08320	
08321	!*===========================================================================*
08322	!*                              out_byte                                     *
08323	!*===========================================================================*
08324	! PUBLIC void out_byte(port_t port, u8_t value);
08325	! Write  value  (cast to a byte)  to the I/O port  port.
08326	
08327	        .align  16
08328	_out_byte:
08329	        mov     edx, 4(esp)             ! port
08330	        movb    al, 4+4(esp)            ! value
08331	        outb    dx                      ! output 1 byte
08332	        ret
08333	
08334	
08335	!*===========================================================================*
08336	!*                              out_word                                     *
08337	!*===========================================================================*
08338	! PUBLIC void out_word(Port_t port, U16_t value);
08339	! Write  value  (cast to a word)  to the I/O port  port.
08340	
08341	        .align  16
08342	_out_word:
08343	        mov     edx, 4(esp)             ! port
08344	        mov     eax, 4+4(esp)           ! value
08345	    o16 out     dx                      ! output 1 word
08346	        ret
08347	
08348	
08349	!*===========================================================================*
08350	!*                              port_read                                    *
08351	!*===========================================================================*
08352	! PUBLIC void port_read(port_t port, phys_bytes destination, unsigned bytcount);
08353	! Transfer data from (hard disk controller) port to memory.
08354	
08355	PR_ARGS =       4 + 4 + 4               ! 4 + 4 + 4
08356	!               es edi eip              port dst len
08357	
08358	        .align  16
08359	_port_read:
08360	        cld
08361	        push    edi
08362	        push    es
08363	        mov     ecx, FLAT_DS_SELECTOR
08364	        mov     es, cx
08365	        mov     edx, PR_ARGS(esp)       ! port to read from
08366	        mov     edi, PR_ARGS+4(esp)     ! destination addr
08367	        mov     ecx, PR_ARGS+4+4(esp)   ! byte count
08368	        shr     ecx, 1                  ! word count
08369	        rep                             ! (hardware cannot handle dwords)
08370	    o16 ins                             ! read everything
08371	        pop     es
08372	        pop     edi
08373	        ret
08374	
08375	
08376	!*===========================================================================*
08377	!*                              port_read_byte                               *
08378	!*===========================================================================*
08379	! PUBLIC void port_read_byte(port_t port, phys_bytes destination,
08380	!                                               unsigned bytcount);
08381	! Transfer data from port to memory.
08382	
08383	PR_ARGS_B =     4 + 4 + 4               ! 4 + 4 + 4
08384	!               es edi eip              port dst len
08385	
08386	_port_read_byte:
08387	        cld
08388	        push    edi
08389	        push    es
08390	        mov     ecx, FLAT_DS_SELECTOR
08391	        mov     es, cx
08392	        mov     edx, PR_ARGS_B(esp)
08393	        mov     edi, PR_ARGS_B+4(esp)
08394	        mov     ecx, PR_ARGS_B+4+4(esp)
08395	        rep
08396	        insb
08397	        pop     es
08398	        pop     edi
08399	        ret
08400	
08401	
08402	!*===========================================================================*
08403	!*                              port_write                                   *
08404	!*===========================================================================*
08405	! PUBLIC void port_write(port_t port, phys_bytes source, unsigned bytcount);
08406	! Transfer data from memory to (hard disk controller) port.
08407	
08408	PW_ARGS =       4 + 4 + 4               ! 4 + 4 + 4
08409	!               es edi eip              port src len
08410	
08411	        .align  16
08412	_port_write:
08413	        cld
08414	        push    esi
08415	        push    ds
08416	        mov     ecx, FLAT_DS_SELECTOR
08417	        mov     ds, cx
08418	        mov     edx, PW_ARGS(esp)       ! port to write to
08419	        mov     esi, PW_ARGS+4(esp)     ! source addr
08420	        mov     ecx, PW_ARGS+4+4(esp)   ! byte count
08421	        shr     ecx, 1                  ! word count
08422	        rep                             ! (hardware cannot handle dwords)
08423	    o16 outs                            ! write everything
08424	        pop     ds
08425	        pop     esi
08426	        ret
08427	
08428	
08429	!*===========================================================================*
08430	!*                              port_write_byte                              *
08431	!*===========================================================================*
08432	! PUBLIC void port_write_byte(port_t port, phys_bytes source,
08433	!                                               unsigned bytcount);
08434	! Transfer data from memory to port.
08435	
08436	PW_ARGS_B =     4 + 4 + 4               ! 4 + 4 + 4
08437	!               es edi eip              port src len

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -