Subversion Repositories Kolibri OS

Compare Revisions

Regard whitespace Rev 3907 → Rev 3908

/kernel/branches/Kolibri-acpi/core/apic.inc
41,15 → 41,6
IOAPIC_ARB equ 0x2
IOAPIC_REDTBL equ 0x10
 
IPI_INIT equ (0x5 shl 8)
IPI_START equ (0x6 shl 8)
IPI_LEVEL_ASSERT equ (0x1 shl 14)
SHORTHAND_ALL_EXCL equ (0x3 shl 18)
 
CMD_IPI_INIT equ (IPI_INIT+SHORTHAND_ALL_EXCL)
 
 
 
align 4
APIC_init:
mov [irq_mode], IRQ_PIC
91,7 → 82,7
@@:
mov ebx, eax
call IOAPIC_read
mov ah, 0x09; Delivery Mode: Lowest Priority, Destination Mode: Logical
mov ah, 0x08; Delivery Mode: Fixed, Destination Mode: Logical
mov al, cl
add al, 0x20; vector
or eax, 0x10000; Mask Interrupt
193,19 → 184,19
 
; LAPIC timer
; pre init
; mov dword[esi + APIC_timer_div], 1011b; 1
; mov dword[esi + APIC_timer_init], 0xffffffff; max val
; push esi
; mov esi, 640 ; wait 0.64 sec
; call delay_ms
; pop esi
; mov eax, [esi + APIC_timer_cur]; read current tick couner
; xor eax, 0xffffffff ; eax = 0xffffffff - eax
; shr eax, 6 ; eax /= 64; APIC ticks per 0.01 sec
mov dword[esi + APIC_timer_div], 1011b; 1
mov dword[esi + APIC_timer_init], 0xffffffff; max val
push esi
mov esi, 640 ; wait 0.64 sec
call delay_ms
pop esi
mov eax, [esi + APIC_timer_cur]; read current tick couner
xor eax, 0xffffffff ; eax = 0xffffffff - eax
shr eax, 6 ; eax /= 64; APIC ticks per 0.01 sec
 
; Start (every 0.01 sec)
; mov dword[esi + APIC_LVT_timer], 0x30020; periodic int 0x20
; mov dword[esi + APIC_timer_init], eax
mov dword[esi + APIC_LVT_timer], 0x30020; periodic int 0x20
mov dword[esi + APIC_timer_init], eax
 
.done:
ret
446,38 → 437,7
pop ebp
ret
 
if 0
align 4
start_ap:
;eax= cpu id
 
; xchg bx, bx
 
test eax, eax ;do not start self
jz .exit
 
cmp eax, [cpu_count]
jae .exit
 
mov eax, [smpt+eax*4]
shl eax, 24
 
mov [esi+APIC_ICRH], eax
mov [esi+APIC_ICRL], dword (IPI_INIT+IPI_LEVEL_ASSERT)
 
mov ecx, 10000
@@:
loop @B
 
CMD_IPI_START equ (IPI_START+IPI_LEVEL_ASSERT)+((0x10000+__ap_start_16) shr 12)
 
mov [esi+APIC_ICRH], eax
mov [esi+APIC_ICRL], dword CMD_IPI_START
.exit:
ret
 
end if
 
 
 
 
/kernel/branches/Kolibri-acpi/core/dll.inc
34,93 → 34,7
jmp .wait
endp
 
align 4
proc pci_read32 stdcall, bus:dword, devfn:dword, reg:dword
push ebx
xor eax, eax
xor ebx, ebx
mov ah, byte [bus]
mov al, 6
mov bh, byte [devfn]
mov bl, byte [reg]
call pci_read_reg
pop ebx
ret
endp
 
align 4
proc pci_read16 stdcall, bus:dword, devfn:dword, reg:dword
push ebx
xor eax, eax
xor ebx, ebx
mov ah, byte [bus]
mov al, 5
mov bh, byte [devfn]
mov bl, byte [reg]
call pci_read_reg
pop ebx
ret
endp
 
align 4
proc pci_read8 stdcall, bus:dword, devfn:dword, reg:dword
push ebx
xor eax, eax
xor ebx, ebx
mov ah, byte [bus]
mov al, 4
mov bh, byte [devfn]
mov bl, byte [reg]
call pci_read_reg
pop ebx
ret
endp
 
align 4
proc pci_write8 stdcall, bus:dword, devfn:dword, reg:dword, val:dword
push ebx
xor eax, eax
xor ebx, ebx
mov ah, byte [bus]
mov al, 8
mov bh, byte [devfn]
mov bl, byte [reg]
mov ecx, [val]
call pci_write_reg
pop ebx
ret
endp
 
align 4
proc pci_write16 stdcall, bus:dword, devfn:dword, reg:dword, val:dword
push ebx
xor eax, eax
xor ebx, ebx
mov ah, byte [bus]
mov al, 9
mov bh, byte [devfn]
mov bl, byte [reg]
mov ecx, [val]
call pci_write_reg
pop ebx
ret
endp
 
align 4
proc pci_write32 stdcall, bus:dword, devfn:dword, reg:dword, val:dword
push ebx
xor eax, eax
xor ebx, ebx
mov ah, byte [bus]
mov al, 10
mov bh, byte [devfn]
mov bl, byte [reg]
mov ecx, [val]
call pci_write_reg
pop ebx
ret
endp
 
handle equ IOCTL.handle
io_code equ IOCTL.io_code
input equ IOCTL.input
509,6 → 423,136
ret
endp
 
; description
; allocate user memory and loads the specified file
;
; param
; file_name= path to file
;
; retval
; eax= file image in user memory
; ebx= size of file
;
; warging
; You mast call kernel_free() to delete each file
; loaded by the load_file() function
 
align 4
proc load_file_umode stdcall, file_name:dword
locals
attr dd ?
flags dd ?
cr_time dd ?
cr_date dd ?
acc_time dd ?
acc_date dd ?
mod_time dd ?
mod_date dd ?
file_size dd ?
 
km_file dd ?
um_file dd ?
endl
 
push esi
push edi
push ebx
 
 
lea eax, [attr]
stdcall get_fileinfo, [file_name], eax ;find file and get info
test eax, eax
jnz .err_1
 
mov eax, [file_size]
cmp eax, 1024*1024*16 ;to be enough for anybody (c)
ja .err_1
;it is very likely that the file is packed
stdcall kernel_alloc, [file_size] ;with kpack, so allocate memory from kernel heap
mov [km_file], eax
test eax, eax
jz .err_1
 
stdcall read_file, [file_name], eax, dword 0, [file_size]
cmp ebx, [file_size]
 
jne .err_2
 
mov eax, [km_file]
cmp dword [eax], 0x4B43504B ; check kpack signature
jne .raw_file
 
mov ebx, [eax+4] ;get real size of file
mov [file_size], ebx
stdcall user_alloc, ebx ;and allocate memory from user heap
mov [um_file], eax
test eax, eax
jz .err_2
 
pushad
mov ecx, unpack_mutex
call mutex_lock
 
stdcall unpack, [km_file], [um_file]
 
mov ecx, unpack_mutex
call mutex_unlock
popad
 
stdcall kernel_free, [km_file] ;we don't need packed file anymore
.exit:
mov eax, [um_file]
mov edx, [file_size]
 
pop ebx
pop edi
pop esi
ret
 
 
.raw_file: ; sometimes we load unpacked file
stdcall user_alloc, ebx ; allocate space from user heap
mov [um_file], eax
 
test eax, eax
jz .err_2
 
shr eax, 10 ; and remap pages.
 
mov ecx, [file_size]
add ecx, 4095
shr ecx, 12
 
mov esi, [km_file]
shr esi, 10
add esi, page_tabs
 
lea edi, [page_tabs+eax]
 
cld
@@:
lodsd
and eax, 0xFFFFF000
or eax, PG_USER
stosd
loop @B
 
stdcall free_kernel_space, [km_file] ; release allocated kernel space
jmp .exit ; physical pages still in use
 
.err_2:
stdcall kernel_free, [km_file]
.err_1:
xor eax, eax
xor edx, edx
 
pop ebx
pop edi
pop esi
ret
endp
 
 
uglobal
align 4
unpack_mutex MUTEX
515,37 → 559,31
endg
 
align 4
proc get_proc_ex stdcall, proc_name:dword, imports:dword
 
proc get_proc_ex stdcall uses ebx esi, proc_name:dword, imports:dword
mov ebx, [imports]
test ebx, ebx
jz .end
xor esi, esi
.look_up:
mov edx, [imports]
test edx, edx
jz .end
mov edx, [edx]
test edx, edx
jz .end
.next:
mov eax, [edx]
test eax, eax
jz .next_table
 
push edx
mov eax, [ebx+32]
mov eax, [OS_BASE+eax+esi*4]
add eax, OS_BASE
stdcall strncmp, eax, [proc_name], 256
pop edx
test eax, eax
jz .ok
 
add edx, 8
jmp .next
.next_table:
add [imports], 4
jmp .look_up
.ok:
mov eax, [edx+4]
ret
inc esi
cmp esi, [ebx+24]
jb .look_up
.end:
xor eax, eax
ret
.ok:
mov eax, [ebx+28]
mov eax, [OS_BASE+eax+esi*4]
add eax, OS_BASE
ret
endp
 
align 4
713,8 → 751,6
img_base dd ?
start dd ?
 
exports dd ? ;fake exports table
dd ?
file_name rb 13+16+4+1 ; '/sys/drivers/<up-to-16-chars>.obj'
endl
 
803,13 → 839,10
add ecx, [sym]
mov [strings], ecx
 
lea ebx, [exports]
mov dword [ebx], kernel_export
mov dword [ebx+4], 0
lea eax, [edx+20]
 
stdcall fix_coff_symbols, eax, [sym], [edx+COFF_HEADER.nSymbols], \
[strings], ebx
[strings], __exports
test eax, eax
jz .link_fail
 
911,8 → 944,6
img_base dd ?
endl
 
cli
 
; resolve file name
mov ebx, [file_name]
lea edi, [fullname+1]
923,6 → 954,8
 
; scan for required DLL in list of already loaded for this process,
; ignore timestamp
cli
 
mov esi, [CURRENT_TASK]
shl esi, 8
lea edi, [fullname]
946,6 → 979,7
mov eax, [ecx+DLLDESCR.exports]
sub eax, [ecx+DLLDESCR.defaultbase]
add eax, [esi+HDLL.base]
sti
ret
.next_in_process:
mov esi, [esi+HDLL.fd]
953,10 → 987,12
.not_in_process:
 
; scan in full list, compare timestamp
sti
lea eax, [fileinfo]
stdcall get_fileinfo, edi, eax
test eax, eax
jnz .fail
cli
mov esi, [dll_list.fd]
.scan_for_dlls:
cmp esi, dll_list
978,6 → 1014,7
 
; new DLL
.load_new:
sti
; load file
stdcall load_file, edi
test eax, eax
1005,13 → 1042,6
mov dword [esi+DLLDESCR.timestamp], eax
mov eax, dword [fileinfo+28]
mov dword [esi+DLLDESCR.timestamp+4], eax
; initialize DLLDESCR struct
and dword [esi+DLLDESCR.refcount], 0; no HDLLs yet; later it will be incremented
mov [esi+DLLDESCR.fd], dll_list
mov eax, [dll_list.bk]
mov [dll_list.bk], esi
mov [esi+DLLDESCR.bk], eax
mov [eax+DLLDESCR.fd], esi
 
; calculate size of loaded DLL
mov edx, [coff]
1181,6 → 1211,14
 
stdcall kernel_free, [coff]
 
cli
; initialize DLLDESCR struct
and dword [esi+DLLDESCR.refcount], 0; no HDLLs yet; later it will be incremented
mov [esi+DLLDESCR.fd], dll_list
mov eax, [dll_list.bk]
mov [dll_list.bk], esi
mov [esi+DLLDESCR.bk], eax
mov [eax+DLLDESCR.fd], esi
.dll_already_loaded:
inc [esi+DLLDESCR.refcount]
push esi
1253,6 → 1291,7
mov eax, [esi+DLLDESCR.exports]
sub eax, [esi+DLLDESCR.defaultbase]
add eax, [img_base]
sti
ret
.fail_and_free_data:
stdcall kernel_free, [esi+DLLDESCR.data]
1269,6 → 1308,7
.fail_and_dereference:
mov eax, 1 ; delete 1 reference
call dereference_dll
sti
xor eax, eax
ret
endp
/kernel/branches/Kolibri-acpi/core/exports.inc
1,6 → 1,6
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;; ;;
;; Copyright (C) KolibriOS team 2004-2011. All rights reserved. ;;
;; Copyright (C) KolibriOS team 2004-2012. All rights reserved. ;;
;; Distributed under terms of the GNU General Public License ;;
;; ;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
7,204 → 7,117
 
$Revision$
 
 
iglobal
szKernel db 'KERNEL', 0
szVersion db 'version',0
endg
 
szRegService db 'RegService',0
szGetService db 'GetService',0
szServiceHandler db 'ServiceHandler',0
szAttachIntHandler db 'AttachIntHandler',0
; szGetIntHandler db 'GetIntHandler', 0
szFpuSave db 'FpuSave',0
szFpuRestore db 'FpuRestore',0
szReservePortArea db 'ReservePortArea',0
szBoot_Log db 'Boot_Log',0
 
szMutexInit db 'MutexInit',0
szMutexLock db 'MutexLock',0
szMutexUnlock db 'MutexUnlock',0
 
szPciApi db 'PciApi', 0
szPciRead32 db 'PciRead32', 0
szPciRead16 db 'PciRead16', 0
szPciRead8 db 'PciRead8', 0
szPciWrite8 db 'PciWrite8',0
szPciWrite16 db 'PciWrite16',0
szPciWrite32 db 'PciWrite32',0
 
szAllocPage db 'AllocPage',0
szAllocPages db 'AllocPages',0
szFreePage db 'FreePage',0
szGetPgAddr db 'GetPgAddr',0
szMapPage db 'MapPage',0
szMapSpace db 'MapSpace',0
szMapIoMem db 'MapIoMem',0
szCommitPages db 'CommitPages',0
szReleasePages db 'ReleasePages',0
 
szAllocKernelSpace db 'AllocKernelSpace',0
szFreeKernelSpace db 'FreeKernelSpace',0
szKernelAlloc db 'KernelAlloc',0
szKernelFree db 'KernelFree',0
szUserAlloc db 'UserAlloc',0
szUserFree db 'UserFree',0
szKmalloc db 'Kmalloc',0
szKfree db 'Kfree',0
szCreateRingBuffer db 'CreateRingBuffer',0
 
szGetPid db 'GetPid',0
szCreateObject db 'CreateObject',0
szDestroyObject db 'DestroyObject',0
szCreateEvent db 'CreateEvent',0
szRaiseEvent db 'RaiseEvent',0
szWaitEvent db 'WaitEvent',0
szDestroyEvent db 'DestroyEvent',0
szClearEvent db 'ClearEvent',0
 
szLoadCursor db 'LoadCursor',0
 
szSysMsgBoardStr db 'SysMsgBoardStr', 0
szSysMsgBoard db 'SysMsgBoard', 0
szGetCurrentTask db 'GetCurrentTask',0
szLFBAddress db 'LFBAddress',0
szLoadFile db 'LoadFile',0
szSendEvent db 'SendEvent',0
szSetMouseData db 'SetMouseData',0
szSetKeyboardData db 'SetKeyboardData',0
szRegKeyboard db 'RegKeyboard',0
szDelKeyboard db 'DelKeyboard',0
szSleep db 'Sleep',0
szGetTimerTicks db 'GetTimerTicks',0
 
szGetDisplay db 'GetDisplay',0
szSetScreen db 'SetScreen',0
 
szStrncat db 'strncat',0
szStrncpy db 'strncpy',0
szstrncmp db 'strncmp',0
szStrnlen db 'strnlen',0
szStrchr db 'strchr',0
szStrrchr db 'strrchr',0
 
szDiskAdd db 'DiskAdd',0
szDiskDel db 'DiskDel',0
szDiskMediaChanged db 'DiskMediaChanged',0
 
szTimerHS db 'TimerHS',0
szCancelTimerHS db 'CancelTimerHS',0
 
szRegUSBDriver db 'RegUSBDriver',0
szUSBOpenPipe db 'USBOpenPipe',0
szUSBClosePipe db 'USBClosePipe',0
szUSBNormalTransferAsync db 'USBNormalTransferAsync',0
szUSBControlTransferAsync db 'USBControlTransferAsync',0
 
szNetRegDev db 'NetRegDev',0
szNetUnRegDev db 'NetUnRegDev',0
szNetPtrToNum db 'NetPtrToNum',0
szNetLinkChanged db 'NetLinkChanged',0
szEth_input db 'Eth_input',0
 
align 16
kernel_export:
dd szRegService , reg_service
dd szGetService , get_service
dd szServiceHandler , srv_handler
dd szAttachIntHandler, attach_int_handler
; dd szGetIntHandler , get_int_handler
dd szFpuSave , fpu_save
dd szFpuRestore , fpu_restore
dd szReservePortArea , r_f_port_area
dd szBoot_Log , boot_log
 
dd szMutexInit , mutex_init ;gcc fastcall
dd szMutexLock , mutex_lock ;gcc fastcall
dd szMutexUnlock , mutex_unlock ;gcc fastcall
 
dd szPciApi , pci_api_drv
dd szPciRead32 , pci_read32
dd szPciRead16 , pci_read16
dd szPciRead8 , pci_read8
dd szPciWrite8 , pci_write8
dd szPciWrite16 , pci_write16
dd szPciWrite32 , pci_write32
 
dd szAllocPage , alloc_page ;stdcall
dd szAllocPages , alloc_pages ;stdcall
dd szFreePage , free_page
dd szMapPage , map_page ;stdcall
dd szMapSpace , map_space
dd szMapIoMem , map_io_mem ;stdcall
dd szGetPgAddr , get_pg_addr
dd szCommitPages , commit_pages ;not implemented
dd szReleasePages , release_pages
 
dd szAllocKernelSpace, alloc_kernel_space ;stdcall
dd szFreeKernelSpace , free_kernel_space ;stdcall
dd szKernelAlloc , kernel_alloc ;stdcall
dd szKernelFree , kernel_free ;stdcall
dd szUserAlloc , user_alloc ;stdcall
dd szUserFree , user_free ;stdcall
dd szKmalloc , malloc
dd szKfree , free
dd szCreateRingBuffer, create_ring_buffer ;stdcall
 
dd szGetPid , get_pid
dd szCreateObject , create_kernel_object
dd szDestroyObject , destroy_kernel_object
dd szCreateEvent , create_event ;see EVENT.inc for specification
dd szRaiseEvent , raise_event ;see EVENT.inc for specification
dd szWaitEvent , wait_event ;see EVENT.inc for specification
dd szDestroyEvent , destroy_event ;see EVENT.inc for specification
dd szClearEvent , clear_event ;see EVENT.inc for specification
 
dd szLoadCursor , load_cursor ;stdcall
 
dd szSysMsgBoardStr , sys_msg_board_str
dd szSysMsgBoard , sys_msg_board
dd szGetCurrentTask , get_curr_task
dd szLoadFile , load_file ;retval eax, ebx
dd szSendEvent , send_event ;see EVENT.inc for specification
dd szSetMouseData , set_mouse_data ;stdcall
dd szSetKeyboardData , set_keyboard_data
dd szRegKeyboard , register_keyboard
dd szDelKeyboard , delete_keyboard
dd szSleep , delay_ms
dd szGetTimerTicks , get_timer_ticks
 
dd szGetDisplay , get_display
dd szSetScreen , set_screen
 
dd szStrncat , strncat
dd szStrncpy , strncpy
dd szstrncmp , strncmp
dd szStrnlen , strnlen
dd szStrchr , strchr
dd szStrrchr , strrchr
 
dd szDiskAdd , disk_add
dd szDiskDel , disk_del
dd szDiskMediaChanged, disk_media_changed
 
dd szTimerHS , timer_hs
dd szCancelTimerHS , cancel_timer_hs
 
dd szRegUSBDriver , reg_usb_driver
dd szUSBOpenPipe , usb_open_pipe
dd szUSBClosePipe , usb_close_pipe
dd szUSBNormalTransferAsync, usb_normal_transfer_async
dd szUSBControlTransferAsync, usb_control_async
 
dd szNetRegDev , NET_add_device
dd szNetUnRegDev , NET_remove_device
dd szNetPtrToNum , NET_ptr_to_num
dd szNetLinkChanged , NET_link_changed
dd szEth_input , ETH_input
 
exp_lfb:
dd szLFBAddress , 0
dd 0 ;terminator, must be zero
 
endg
align 4
__exports:
export 'KERNEL', \
alloc_kernel_space, 'AllocKernelSpace', \ ; stdcall
alloc_page, 'AllocPage', \ ; gcc ABI
alloc_pages, 'AllocPages', \ ; stdcall
commit_pages, 'CommitPages', \ ; eax, ebx, ecx
\
disk_add, 'DiskAdd', \ ;stdcall
disk_del, 'DiskDel', \
disk_media_changed, 'DiskMediaChanged', \ ;stdcall
\
create_event, 'CreateEvent', \ ; ecx, esi
destroy_event, 'DestroyEvent', \ ;
raise_event, 'RaiseEvent', \ ; eax, ebx, edx, esi
wait_event, 'WaitEvent', \ ; eax, ebx
wait_event_timeout, 'WaitEventTimeout', \ ; eax, ebx, ecx
get_event_ex, 'GetEvent', \ ; edi
clear_event, 'ClearEvent', \ ;see EVENT.inc for specification
send_event, 'SendEvent', \ ;see EVENT.inc for specification
\
create_kernel_object, 'CreateObject', \
create_ring_buffer, 'CreateRingBuffer', \ ; stdcall
destroy_kernel_object, 'DestroyObject', \
free_kernel_space, 'FreeKernelSpace', \ ; stdcall
free_page, 'FreePage', \ ; eax
kernel_alloc, 'KernelAlloc', \ ; stdcall
kernel_free, 'KernelFree', \ ; stdcall
malloc, 'Kmalloc', \
free, 'Kfree', \
map_io_mem, 'MapIoMem', \ ; stdcall
map_page, 'MapPage', \ ; stdcall
get_pg_addr, 'GetPgAddr', \ ; eax
map_space, 'MapSpace', \
release_pages, 'ReleasePages', \
\
mutex_init, 'MutexInit', \ ; gcc fastcall
mutex_lock, 'MutexLock', \ ; gcc fastcall
mutex_unlock, 'MutexUnlock', \ ; gcc fastcall
\
get_display, 'GetDisplay', \
set_screen, 'SetScreen', \
window._.get_rect, 'GetWindowRect', \ ; gcc fastcall
pci_api_drv, 'PciApi', \
pci_read8, 'PciRead8', \ ; stdcall
pci_read16, 'PciRead16', \ ; stdcall
pci_read32, 'PciRead32', \ ; stdcall
pci_write8, 'PciWrite8', \ ; stdcall
pci_write16, 'PciWrite16', \ ; stdcall
pci_write32, 'PciWrite32', \ ; stdcall
\
get_pid, 'GetPid', \
get_service, 'GetService', \ ;
reg_service, 'RegService', \ ; stdcall
attach_int_handler, 'AttachIntHandler', \ ; stdcall
user_alloc, 'UserAlloc', \ ; stdcall
user_alloc_at, 'UserAllocAt', \ ; stdcall
user_free, 'UserFree', \ ; stdcall
unmap_pages, 'UnmapPages', \ ; eax, ecx
sys_msg_board_str, 'SysMsgBoardStr', \
sys_msg_board, 'SysMsgBoard', \
get_timer_ticks, 'GetTimerTicks', \
get_stack_base, 'GetStackBase', \
delay_hs, 'Delay', \ ; ebx
set_mouse_data, 'SetMouseData', \ ;
set_keyboard_data, 'SetKeyboardData', \ ; gcc fastcall
register_keyboard, 'RegKeyboard', \
delete_keyboard, 'DelKeyboard', \
get_cpu_freq, 'GetCpuFreq', \
\
srv_handler, 'ServiceHandler', \
fpu_save, 'FpuSave', \
fpu_restore, 'FpuRestore', \
r_f_port_area, 'ReservePortArea', \
boot_log, 'Boot_Log', \
\
load_cursor, 'LoadCursor', \ ;stdcall
\
get_curr_task, 'GetCurrentTask', \
load_file, 'LoadFile', \ ;retval eax, ebx
delay_ms, 'Sleep', \
\
strncat, 'strncat', \
strncpy, 'strncpy', \
strncmp, 'strncmp', \
strnlen, 'strnlen', \
strchr, 'strchr', \
strrchr, 'strrchr', \
\
timer_hs, 'TimerHS', \
cancel_timer_hs, 'CancelTimerHS', \
\
reg_usb_driver, 'RegUSBDriver', \
usb_open_pipe, 'USBOpenPipe', \
usb_close_pipe, 'USBClosePipe', \
usb_normal_transfer_async, 'USBNormalTransferAsync', \
usb_control_async, 'USBControlTransferAsync', \
usb_get_param, 'USBGetParam', \
\
NET_add_device, 'NetRegDev', \
NET_remove_device, 'NetUnRegDev', \
NET_ptr_to_num, 'NetPtrToNum', \
NET_link_changed, 'NetLinkChanged', \
ETH_input, 'Eth_input', \
\
0, 'LFBAddress' ; must be the last one
load kernel_exports_count dword from __exports + 24
load kernel_exports_addresses dword from __exports + 28
exp_lfb = OS_BASE + kernel_exports_addresses + (kernel_exports_count - 1) * 4 - 4
/kernel/branches/Kolibri-acpi/core/heap.inc
890,6 → 890,7
 
mov ebx, [offset]
and ebx, not 4095 ; is it required ?
add ebx, [base]
 
.unmap:
mov eax, [edx] ; get page addres
897,7 → 898,7
jz @F
test eax, PG_SHARED ; page shared ?
jnz @F
mov [page_tabs+edx*4], dword 2
mov [edx], dword 2
; mark page as reserved
invlpg [ebx] ; when we start using
call free_page ; empty c-o-w page instead this ?
/kernel/branches/Kolibri-acpi/core/irq.inc
51,6 → 51,8
.irqh dd ?
endl
 
DEBUGF 1, "K : Attach Interrupt %d Handler %x\n", [irq], [handler]
 
and [.irqh], 0
 
push ebx
154,25 → 156,6
cmp [v86_irqhooks+ebp*8], 0
jnz v86_irq
 
cmp bp, 6
jnz @f
push ebp
call [fdc_irq_func]
pop ebp
@@:
 
cmp bp, 14
jnz @f
push ebp
call [irq14_func]
pop ebp
@@:
cmp bp, 15
jnz @f
push ebp
call [irq15_func]
pop ebp
@@:
bts [irq_active_set], ebp
 
lea esi, [irqh_tab+ebp*8] ; esi= list head
217,14 → 200,6
; Note: this still isn't 100% correct, because two IRQs can fire simultaneously,
; the better way would be to find the correct IRQ, but I don't know how to do
; this in that case.
; Also, [fdc_irq_func], [irq14_func], [irq15_func] could process interrupt
; but do not return whether they did it, so just ignore IRQs 6, 14, 15.
cmp ebp, 6
jz .fail
cmp ebp, 14
jz .fail
cmp ebp, 15
jz .fail
push ebp
xor ebp, ebp
.try_other_irqs:
232,8 → 207,14
jz .try_next_irq
cmp ebp, 1
jz .try_next_irq
cmp ebp, 6
jz .try_next_irq
cmp ebp, 12
jz .try_next_irq
cmp ebp, 14
jz .try_next_irq
cmp ebp, 15
jz .try_next_irq
lea esi, [irqh_tab+ebp*8]
mov ebx, esi
.try_next_handler:
/kernel/branches/Kolibri-acpi/core/memory.inc
358,7 → 358,7
 
cmp dword [LFBAddress], -1
jne @f
mov [BOOT_VAR+BOOT_MTRR], byte 2
mov [BOOT_VARS+BOOT_MTRR], byte 2
; max VGA=640*480*4=1228800 bytes
; + 32*640*4=81920 bytes for mouse pointer
stdcall alloc_pages, ((1228800+81920)/4096)
378,7 → 378,7
@@:
test [SCR_MODE], word 0100000000000000b
jnz @f
mov [BOOT_VAR+BOOT_MTRR], byte 2
mov [BOOT_VARS+BOOT_MTRR], byte 2
ret
@@:
call init_mtrr
1199,7 → 1199,7
cmp ebx, 11
jb .fail
 
cmp ebx, 25
cmp ebx, 27
ja .fail
 
jmp dword [f68call+ebx*4-11*4]
1310,6 → 1310,15
mov [esp+32], eax
ret
 
.27:
cmp ecx, OS_BASE
jae .fail
 
stdcall load_file_umode, ecx
mov [esp+24], edx
mov [esp+32], eax
ret
 
.fail:
xor eax, eax
mov [esp+32], eax
1335,6 → 1344,7
dd f68.24 ; set exception handler
dd f68.25 ; unmask exception
dd f68.26 ; user_unmap
dd f68.27 ; load_file_umode
 
 
align 4
1361,7 → 1371,7
align 4
proc init_mtrr
 
cmp [BOOT_VAR+BOOT_MTRR], byte 2
cmp [BOOT_VARS+BOOT_MTRR], byte 2
je .exit
 
bt [cpu_caps], CAPS_MTRR
1456,7 → 1466,7
mov ebx, [size]
dec ebx
mov eax, 0xFFFFFFFF
mov edx, 0x0000000F
mov edx, 0x00000000
sub eax, ebx
sbb edx, 0
or eax, 0x800
/kernel/branches/Kolibri-acpi/core/peload.inc
275,68 → 275,3
pop edi
pop ebp
ret 8
 
align 16
__exports:
export 'KERNEL', \
alloc_kernel_space, 'AllocKernelSpace', \ ; stdcall
alloc_page, 'AllocPage', \ ; gcc ABI
alloc_pages, 'AllocPages', \ ; stdcall
commit_pages, 'CommitPages', \ ; eax, ebx, ecx
\
disk_add, 'DiskAdd', \ ;stdcall
disk_media_changed, 'DiskMediaChanged', \ ;stdcall
\
create_event, 'CreateEvent', \ ; ecx, esi
destroy_event, 'DestroyEvent', \ ;
raise_event, 'RaiseEvent', \ ; eax, ebx, edx, esi
wait_event, 'WaitEvent', \ ; eax, ebx
wait_event_timeout, 'WaitEventTimeout', \ ; eax, ebx, ecx
get_event_ex, 'GetEvent', \ ; edi
\
create_kernel_object, 'CreateObject', \
create_ring_buffer, 'CreateRingBuffer', \ ; stdcall
destroy_kernel_object, 'DestroyObject', \
free_kernel_space, 'FreeKernelSpace', \ ; stdcall
free_page, 'FreePage', \ ; eax
kernel_alloc, 'KernelAlloc', \ ; stdcall
kernel_free, 'KernelFree', \ ; stdcall
malloc, 'Kmalloc', \
free, 'Kfree', \
map_io_mem, 'MapIoMem', \ ; stdcall
map_page, 'MapPage', \ ; stdcall
get_pg_addr, 'GetPgAddr', \ ; eax
\
mutex_init, 'MutexInit', \ ; gcc fastcall
mutex_lock, 'MutexLock', \ ; gcc fastcall
mutex_unlock, 'MutexUnlock', \ ; gcc fastcall
\
get_display, 'GetDisplay', \
set_screen, 'SetScreen', \
window._.get_rect, 'GetWindowRect', \ ; gcc fastcall
pci_api_drv, 'PciApi', \
pci_read8, 'PciRead8', \ ; stdcall
pci_read16, 'PciRead16', \ ; stdcall
pci_read32, 'PciRead32', \ ; stdcall
pci_write8, 'PciWrite8', \ ; stdcall
pci_write16, 'PciWrite16', \ ; stdcall
pci_write32, 'PciWrite32', \ ; stdcall
\
get_pid, 'GetPid', \
get_service, 'GetService', \ ;
reg_service, 'RegService', \ ; stdcall
attach_int_handler, 'AttachIntHandler', \ ; stdcall
user_alloc, 'UserAlloc', \ ; stdcall
user_free, 'UserFree', \ ; stdcall
unmap_pages, 'UnmapPages', \ ; eax, ecx
sys_msg_board_str, 'SysMsgBoardStr', \
get_timer_ticks, 'GetTimerTicks', \
get_stack_base, 'GetStackBase', \
delay_hs, 'Delay', \ ; ebx
set_mouse_data, 'SetMouseData', \ ;
set_keyboard_data, 'SetKeyboardData', \ ; gcc fastcall
timer_hs, 'TimerHs', \ ; stdcall
get_cpu_freq, 'GetCpuFreq'
 
 
 
/kernel/branches/Kolibri-acpi/core/sys32.inc
578,11 → 578,6
push esi ; remove hd1 & cd & flp reservation
shl esi, 5
mov esi, [esi+CURRENT_TASK+TASKDATA.pid]
cmp [hd1_status], esi
jnz @f
call free_hd_channel
and [hd1_status], 0
@@:
cmp [cd_status], esi
jnz @f
call free_cd_channel
/kernel/branches/Kolibri-acpi/core/syscall.inc
182,8 → 182,8
dd sys_apm ; 49-Advanced Power Management (APM)
dd syscall_set_window_shape ; 50-Window shape & scale
dd syscall_threads ; 51-Threads
dd undefined_syscall ; 52-Stack driver status
dd undefined_syscall ; 53-Socket interface
dd undefined_syscall ; 52- deprecated Stack driver status
dd undefined_syscall ; 53- deprecated Socket interface
dd undefined_syscall ; 54-reserved
dd sound_interface ; 55-Sound interface
dd undefined_syscall ; 56-reserved
/kernel/branches/Kolibri-acpi/core/taskman.inc
63,6 → 63,9
; [esp+4] = procedure DoRead, [esp+8] = filesize & [esp+12]... - arguments for it
 
locals
cmdline_size dd ? ; +0 ; cmdline -12
cmdline_adr dd ? ; +4 ; cmdline -8
cmdline_flag dd ? ; +8 ; cmdline -4
cmdline rd 64 ;256/4
filename rd 256 ;1024/4
flags dd ?
127,15 → 130,73
jmp .final
 
.namecopied:
xor eax, eax
mov [cmdline_flag], eax
mov [cmdline_adr], eax
mov [cmdline_size], eax
 
mov [cmdline], ebx
test ebx, ebx
jz @F
jz .no_copy
;--------------------------------------
pushad
pushfd
mov esi, ebx
mov ecx, 65536 ; 64 Kb max for ext.cmdline
cld
@@:
dec ecx
jz .end_string
 
lodsb
test al, al
jnz @b
 
.end_string:
mov eax, 65536 ; 64 Kb max for ext.cmdline
sub eax, ecx
mov [cmdline_size], eax
cmp eax, 255
ja @f
 
popfd
popad
jmp .old_copy
 
@@:
xor eax, eax
dec eax
mov [cmdline_flag], eax
popfd
popad
; get memory for the extended command line
stdcall kernel_alloc, [cmdline_size] ;eax
test eax, eax
jz .old_copy ; get memory failed
 
mov [cmdline_adr], eax
 
pushad
pushfd
mov esi, ebx
mov edi, eax
mov ecx, [cmdline_size]
cld
rep movsb
popfd
popad
jmp .no_copy
 
.old_copy:
; clear flag because old method with 256 bytes
xor eax, eax
mov [cmdline_flag], eax
;--------------------------------------
lea eax, [cmdline]
mov dword [eax+252], 0
.copy:
stdcall strncpy, eax, ebx, 255
@@:
.no_copy:
lea eax, [filename]
stdcall load_file, eax
 
1055,10 → 1116,34
cmp eax, [SLOT_BASE+APPDATA.mem_size+ebx*8]
ja @f
 
mov eax, [cmd_line]
 
cmp [edx], dword 0xffffffff ; extended destination tag
jne .no_ext_dest
 
mov edx, [edx+4] ; extended destination for cmdline
jmp .continue
 
.no_ext_dest:
mov [eax-12], dword 255
.continue:
mov byte [edx], 0 ;force empty string if no cmdline given
mov eax, [cmd_line]
 
test eax, eax
jz @f
;--------------------------------------
cmp [eax-4], dword 0xffffffff ; cmdline_flag
jne .old_copy
 
push eax
stdcall strncpy, edx, [eax-8], [eax-12]
pop eax
 
stdcall kernel_free, [eax-8]
jmp @f
 
.old_copy:
;--------------------------------------
stdcall strncpy, edx, eax, 256
@@:
mov edx, [params]
/kernel/branches/Kolibri-acpi/core/timers.inc
5,7 → 5,7
;; ;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 
$Revision: 2381 $
$Revision: 3598 $
 
; Simple implementation of timers. All timers are organized in a double-linked
; list, and the OS loop after every timer tick processes the list.