Changeset aecf79f in mainline


Ignore:
Timestamp:
2006-07-24T16:07:15Z (18 years ago)
Author:
Martin Decky <martin@…>
Branches:
lfn, master, serial, ticket/834-toolchain-update, topic/msim-upgrade, topic/simplify-dev-export
Children:
c59dd1a2
Parents:
7b0599b
Message:

xen memory initialization

Location:
kernel
Files:
2 added
13 edited

Legend:

Unmodified
Added
Removed
  • kernel/arch/xen32/Makefile.inc

    r7b0599b raecf79f  
    7777DEFS += -DCONFIG_PAGE_PT
    7878
    79 ## Compile with i8042 controller support
    80 #
    81 
    82 CONFIG_I8042 = y
    83 
    84 
    8579## Accepted configuration directives
    8680#
     
    126120        arch/$(ARCH)/src/mm/tlb.c \
    127121        arch/$(ARCH)/src/ddi/ddi.c \
    128         arch/$(ARCH)/src/drivers/i8254.c \
    129         arch/$(ARCH)/src/drivers/i8259.c \
    130         arch/$(ARCH)/src/drivers/ega.c \
    131         arch/$(ARCH)/src/drivers/vesa.c \
     122        arch/$(ARCH)/src/drivers/xconsole.c \
    132123        arch/$(ARCH)/src/boot/boot.S \
    133124        arch/$(ARCH)/src/fpu_context.c \
  • kernel/arch/xen32/_link.ld.in

    r7b0599b raecf79f  
    1515        .image PA2KA(BOOT_OFFSET): {
    1616                ktext_start = .;
     17                *(K_TEXT_START);
    1718                *(.text);
    1819                ktext_end = .;
  • kernel/arch/xen32/include/asm.h

    • Property mode changed from 120000 to 100644
    r7b0599b raecf79f  
    1 ../../ia32/include/asm.h
     1/*
     2 * Copyright (C) 2001-2004 Jakub Jermar
     3 * Copyright (C) 2005 Sergey Bondari
     4 * All rights reserved.
     5 *
     6 * Redistribution and use in source and binary forms, with or without
     7 * modification, are permitted provided that the following conditions
     8 * are met:
     9 *
     10 * - Redistributions of source code must retain the above copyright
     11 *   notice, this list of conditions and the following disclaimer.
     12 * - Redistributions in binary form must reproduce the above copyright
     13 *   notice, this list of conditions and the following disclaimer in the
     14 *   documentation and/or other materials provided with the distribution.
     15 * - The name of the author may not be used to endorse or promote products
     16 *   derived from this software without specific prior written permission.
     17 *
     18 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
     19 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
     20 * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
     21 * IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
     22 * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
     23 * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
     24 * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
     25 * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
     26 * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
     27 * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
     28 */
     29
     30/** @addtogroup xen32
     31 * @{
     32 */
     33/** @file
     34 */
     35
     36#ifndef __xen32_ASM_H__
     37#define __xen32_ASM_H__
     38
     39#include <arch/pm.h>
     40#include <arch/types.h>
     41#include <config.h>
     42
     43extern uint32_t interrupt_handler_size;
     44
     45extern void paging_on(void);
     46
     47extern void interrupt_handlers(void);
     48
     49extern void enable_l_apic_in_msr(void);
     50
     51
     52extern void asm_delay_loop(uint32_t t);
     53extern void asm_fake_loop(uint32_t t);
     54
     55
     56/** Halt CPU
     57 *
     58 * Halt the current CPU until interrupt event.
     59 */
     60static inline void cpu_halt(void) { __asm__("hlt\n"); };
     61static inline void cpu_sleep(void) { __asm__("hlt\n"); };
     62
     63#define GEN_READ_REG(reg) static inline unative_t read_ ##reg (void) \
     64    { \
     65        unative_t res; \
     66        __asm__ volatile ("movl %%" #reg ", %0" : "=r" (res) ); \
     67        return res; \
     68    }
     69
     70#define GEN_WRITE_REG(reg) static inline void write_ ##reg (unative_t regn) \
     71    { \
     72        __asm__ volatile ("movl %0, %%" #reg : : "r" (regn)); \
     73    }
     74
     75GEN_READ_REG(cr0);
     76GEN_READ_REG(cr2);
     77GEN_READ_REG(cr3);
     78GEN_WRITE_REG(cr3);
     79
     80GEN_READ_REG(dr0);
     81GEN_READ_REG(dr1);
     82GEN_READ_REG(dr2);
     83GEN_READ_REG(dr3);
     84GEN_READ_REG(dr6);
     85GEN_READ_REG(dr7);
     86
     87GEN_WRITE_REG(dr0);
     88GEN_WRITE_REG(dr1);
     89GEN_WRITE_REG(dr2);
     90GEN_WRITE_REG(dr3);
     91GEN_WRITE_REG(dr6);
     92GEN_WRITE_REG(dr7);
     93
     94/** Byte to port
     95 *
     96 * Output byte to port
     97 *
     98 * @param port Port to write to
     99 * @param val Value to write
     100 */
     101static inline void outb(uint16_t port, uint8_t val) { __asm__ volatile ("outb %b0, %w1\n" : : "a" (val), "d" (port) ); }
     102
     103/** Word to port
     104 *
     105 * Output word to port
     106 *
     107 * @param port Port to write to
     108 * @param val Value to write
     109 */
     110static inline void outw(uint16_t port, uint16_t val) { __asm__ volatile ("outw %w0, %w1\n" : : "a" (val), "d" (port) ); }
     111
     112/** Double word to port
     113 *
     114 * Output double word to port
     115 *
     116 * @param port Port to write to
     117 * @param val Value to write
     118 */
     119static inline void outl(uint16_t port, uint32_t val) { __asm__ volatile ("outl %l0, %w1\n" : : "a" (val), "d" (port) ); }
     120
     121/** Byte from port
     122 *
     123 * Get byte from port
     124 *
     125 * @param port Port to read from
     126 * @return Value read
     127 */
     128static inline uint8_t inb(uint16_t port) { uint8_t val; __asm__ volatile ("inb %w1, %b0 \n" : "=a" (val) : "d" (port) ); return val; }
     129
     130/** Word from port
     131 *
     132 * Get word from port
     133 *
     134 * @param port Port to read from
     135 * @return Value read
     136 */
     137static inline uint16_t inw(uint16_t port) { uint16_t val; __asm__ volatile ("inw %w1, %w0 \n" : "=a" (val) : "d" (port) ); return val; }
     138
     139/** Double word from port
     140 *
     141 * Get double word from port
     142 *
     143 * @param port Port to read from
     144 * @return Value read
     145 */
     146static inline uint32_t inl(uint16_t port) { uint32_t val; __asm__ volatile ("inl %w1, %l0 \n" : "=a" (val) : "d" (port) ); return val; }
     147
     148/** Enable interrupts.
     149 *
     150 * Enable interrupts and return previous
     151 * value of EFLAGS.
     152 *
     153 * @return Old interrupt priority level.
     154 */
     155static inline ipl_t interrupts_enable(void)
     156{
     157        ipl_t v;
     158        __asm__ volatile (
     159                "pushf\n\t"
     160                "popl %0\n\t"
     161                "sti\n"
     162                : "=r" (v)
     163        );
     164        return v;
     165}
     166
     167/** Disable interrupts.
     168 *
     169 * Disable interrupts and return previous
     170 * value of EFLAGS.
     171 *
     172 * @return Old interrupt priority level.
     173 */
     174static inline ipl_t interrupts_disable(void)
     175{
     176        ipl_t v;
     177        __asm__ volatile (
     178                "pushf\n\t"
     179                "popl %0\n\t"
     180                "cli\n"
     181                : "=r" (v)
     182        );
     183        return v;
     184}
     185
     186/** Restore interrupt priority level.
     187 *
     188 * Restore EFLAGS.
     189 *
     190 * @param ipl Saved interrupt priority level.
     191 */
     192static inline void interrupts_restore(ipl_t ipl)
     193{
     194        __asm__ volatile (
     195                "pushl %0\n\t"
     196                "popf\n"
     197                : : "r" (ipl)
     198        );
     199}
     200
     201/** Return interrupt priority level.
     202 *
     203 * @return EFLAFS.
     204 */
     205static inline ipl_t interrupts_read(void)
     206{
     207        ipl_t v;
     208        __asm__ volatile (
     209                "pushf\n\t"
     210                "popl %0\n"
     211                : "=r" (v)
     212        );
     213        return v;
     214}
     215
     216/** Return base address of current stack
     217 *
     218 * Return the base address of the current stack.
     219 * The stack is assumed to be STACK_SIZE bytes long.
     220 * The stack must start on page boundary.
     221 */
     222static inline uintptr_t get_stack_base(void)
     223{
     224        uintptr_t v;
     225       
     226        __asm__ volatile ("andl %%esp, %0\n" : "=r" (v) : "0" (~(STACK_SIZE-1)));
     227       
     228        return v;
     229}
     230
     231static inline uint64_t rdtsc(void)
     232{
     233        uint64_t v;
     234       
     235        __asm__ volatile("rdtsc\n" : "=A" (v));
     236       
     237        return v;
     238}
     239
     240/** Return current IP address */
     241static inline uintptr_t * get_ip()
     242{
     243        uintptr_t *ip;
     244
     245        __asm__ volatile (
     246                "mov %%eip, %0"
     247                : "=r" (ip)
     248                );
     249        return ip;
     250}
     251
     252/** Invalidate TLB Entry.
     253 *
     254 * @param addr Address on a page whose TLB entry is to be invalidated.
     255 */
     256static inline void invlpg(uintptr_t addr)
     257{
     258        __asm__ volatile ("invlpg %0\n" :: "m" (*(unative_t *)addr));
     259}
     260
     261/** Load GDTR register from memory.
     262 *
     263 * @param gdtr_reg Address of memory from where to load GDTR.
     264 */
     265static inline void gdtr_load(ptr_16_32_t *gdtr_reg)
     266{
     267        __asm__ volatile ("lgdtl %0\n" : : "m" (*gdtr_reg));
     268}
     269
     270/** Store GDTR register to memory.
     271 *
     272 * @param gdtr_reg Address of memory to where to load GDTR.
     273 */
     274static inline void gdtr_store(ptr_16_32_t *gdtr_reg)
     275{
     276        __asm__ volatile ("sgdtl %0\n" : : "m" (*gdtr_reg));
     277}
     278
     279/** Load IDTR register from memory.
     280 *
     281 * @param idtr_reg Address of memory from where to load IDTR.
     282 */
     283static inline void idtr_load(ptr_16_32_t *idtr_reg)
     284{
     285        __asm__ volatile ("lidtl %0\n" : : "m" (*idtr_reg));
     286}
     287
     288/** Load TR from descriptor table.
     289 *
     290 * @param sel Selector specifying descriptor of TSS segment.
     291 */
     292static inline void tr_load(uint16_t sel)
     293{
     294        __asm__ volatile ("ltr %0" : : "r" (sel));
     295}
     296
     297#endif
     298
     299/** @}
     300 */
  • kernel/arch/xen32/include/hypercall.h

    r7b0599b raecf79f  
    3131
    3232#include <arch/types.h>
     33#include <macros.h>
     34
     35
     36#define XEN_CONSOLE_IO  18
     37
     38
     39/*
     40 * Commands for XEN_CONSOLE_IO
     41 */
     42#define CONSOLE_IO_WRITE        0
     43#define CONSOLE_IO_READ         1
     44
    3345
    3446#define hypercall0(id)  \
     
    8395                        : "1" (p1),     \
    8496                          "2" (p2),     \
    85                           "3" (p3),     \
     97                          "3" (p3)      \
    8698                        : "memory"      \
    8799                );      \
     
    102114                          "2" (p2),     \
    103115                          "3" (p3),     \
    104                           "4" (p4),     \
     116                          "4" (p4)      \
    105117                        : "memory"      \
    106118                );      \
     
    110122#define hypercall5(id, p1, p2, p3, p4, p5)      \
    111123        ({      \
    112                 unative_t ret, __ign1, __ign2, __ign3, __ign4, __ing5;  \
     124                unative_t ret, __ign1, __ign2, __ign3, __ign4, __ign5;  \
    113125                asm volatile (  \
    114126                        "call hypercall_page + (" STRING(id) " * 32)\n" \
     
    123135                          "3" (p3),     \
    124136                          "4" (p4),     \
    125                           "5" (p5),     \
     137                          "5" (p5)      \
    126138                        : "memory"      \
    127139                );      \
     
    130142
    131143
    132 static inline int xen_console_io(int cmd, int count, char *str)
     144static inline int xen_console_io(const int cmd, const int count, const char *str)
    133145{
    134146        return hypercall3(XEN_CONSOLE_IO, cmd, count, str);
  • kernel/arch/xen32/include/pm.h

    • Property mode changed from 120000 to 100644
    r7b0599b raecf79f  
    1 ../../ia32/include/pm.h
     1/*
     2 * Copyright (C) 2001-2004 Jakub Jermar
     3 * All rights reserved.
     4 *
     5 * Redistribution and use in source and binary forms, with or without
     6 * modification, are permitted provided that the following conditions
     7 * are met:
     8 *
     9 * - Redistributions of source code must retain the above copyright
     10 *   notice, this list of conditions and the following disclaimer.
     11 * - Redistributions in binary form must reproduce the above copyright
     12 *   notice, this list of conditions and the following disclaimer in the
     13 *   documentation and/or other materials provided with the distribution.
     14 * - The name of the author may not be used to endorse or promote products
     15 *   derived from this software without specific prior written permission.
     16 *
     17 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
     18 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
     19 * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
     20 * IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
     21 * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
     22 * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
     23 * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
     24 * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
     25 * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
     26 * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
     27 */
     28
     29/** @addtogroup xen32
     30 * @{
     31 */
     32/** @file
     33 */
     34
     35#ifndef __PM_H__
     36#define __PM_H__
     37
     38#define IDT_ITEMS 64
     39#define GDT_ITEMS 7
     40
     41#define NULL_DES        0
     42#define KTEXT_DES       1
     43#define KDATA_DES       2
     44#define UTEXT_DES       3
     45#define UDATA_DES       4
     46#define TSS_DES         5
     47#define TLS_DES         6 /* Pointer to Thread-Local-Storage data */
     48
     49#define selector(des)   ((des) << 3)
     50
     51#define PL_KERNEL       1
     52#define PL_USER         3
     53
     54#define AR_PRESENT      (1<<7)
     55#define AR_DATA         (2<<3)
     56#define AR_CODE         (3<<3)
     57#define AR_WRITABLE     (1<<1)
     58#define AR_INTERRUPT    (0xe)
     59#define AR_TSS          (0x9)
     60
     61#define DPL_KERNEL      (PL_KERNEL<<5)
     62#define DPL_USER        (PL_USER<<5)
     63
     64#define TSS_BASIC_SIZE  104
     65#define TSS_IOMAP_SIZE  (16*1024+1)     /* 16K for bitmap + 1 terminating byte for convenience */
     66
     67#define IO_PORTS        (64*1024)
     68
     69#ifndef __ASM__
     70
     71#include <arch/types.h>
     72#include <typedefs.h>
     73#include <arch/context.h>
     74
     75struct ptr_16_32 {
     76        uint16_t limit;
     77        uint32_t base;
     78} __attribute__ ((packed));
     79typedef struct ptr_16_32 ptr_16_32_t;
     80
     81struct descriptor {
     82        unsigned limit_0_15: 16;
     83        unsigned base_0_15: 16;
     84        unsigned base_16_23: 8;
     85        unsigned access: 8;
     86        unsigned limit_16_19: 4;
     87        unsigned available: 1;
     88        unsigned unused: 1;
     89        unsigned special: 1;
     90        unsigned granularity : 1;
     91        unsigned base_24_31: 8;
     92} __attribute__ ((packed));
     93typedef struct descriptor  descriptor_t;
     94
     95struct idescriptor {
     96        unsigned offset_0_15: 16;
     97        unsigned selector: 16;
     98        unsigned unused: 8;
     99        unsigned access: 8;
     100        unsigned offset_16_31: 16;
     101} __attribute__ ((packed));
     102typedef struct idescriptor idescriptor_t;
     103
     104struct tss {
     105        uint16_t link;
     106        unsigned : 16;
     107        uint32_t esp0;
     108        uint16_t ss0;
     109        unsigned : 16;
     110        uint32_t esp1;
     111        uint16_t ss1;
     112        unsigned : 16;
     113        uint32_t esp2;
     114        uint16_t ss2;
     115        unsigned : 16;
     116        uint32_t cr3;
     117        uint32_t eip;
     118        uint32_t eflags;
     119        uint32_t eax;
     120        uint32_t ecx;
     121        uint32_t edx;
     122        uint32_t ebx;
     123        uint32_t esp;
     124        uint32_t ebp;
     125        uint32_t esi;
     126        uint32_t edi;
     127        uint16_t es;
     128        unsigned : 16;
     129        uint16_t cs;
     130        unsigned : 16;
     131        uint16_t ss;
     132        unsigned : 16;
     133        uint16_t ds;
     134        unsigned : 16;
     135        uint16_t fs;
     136        unsigned : 16;
     137        uint16_t gs;
     138        unsigned : 16;
     139        uint16_t ldtr;
     140        unsigned : 16;
     141        unsigned : 16;
     142        uint16_t iomap_base;
     143        uint8_t iomap[TSS_IOMAP_SIZE];
     144} __attribute__ ((packed));
     145typedef struct tss tss_t;
     146
     147extern ptr_16_32_t gdtr;
     148extern ptr_16_32_t bootstrap_gdtr;
     149extern ptr_16_32_t protected_ap_gdtr;
     150extern struct tss *tss_p;
     151
     152extern descriptor_t gdt[];
     153
     154extern void pm_init(void);
     155
     156extern void gdt_setbase(descriptor_t *d, uintptr_t base);
     157extern void gdt_setlimit(descriptor_t *d, uint32_t limit);
     158
     159extern void idt_init(void);
     160extern void idt_setoffset(idescriptor_t *d, uintptr_t offset);
     161
     162extern void tss_initialize(tss_t *t);
     163extern void set_tls_desc(uintptr_t tls);
     164
     165#endif /* __ASM__ */
     166
     167#endif
     168
     169/** @}
     170 */
  • kernel/arch/xen32/src/boot/boot.S

    r7b0599b raecf79f  
    3535        .ascii  "GUEST_OS=HelenOS,"
    3636        .ascii  "XEN_VER=xen-3.0,"
    37         .ascii  "HYPERCALL_PAGE=0x0002,"
     37        .ascii  "HYPERCALL_PAGE=0x0000,"
    3838        .ascii  "LOADER=generic,"
    3939        .ascii  "PT_MODE_WRITABLE"
     
    6161        hlt
    6262
     63.section K_TEXT_START, "aw", @progbits
    6364.global hypercall_page
    64 
    65 .org (0x0002 * PAGE_SIZE)
     65.org 0
    6666hypercall_page:
    6767        .space PAGE_SIZE
  • kernel/arch/xen32/src/interrupt.c

    • Property mode changed from 120000 to 100644
    r7b0599b raecf79f  
    1 ../../ia32/src/interrupt.c
     1/*
     2 * Copyright (C) 2006 Martin Decky
     3 * All rights reserved.
     4 *
     5 * Redistribution and use in source and binary forms, with or without
     6 * modification, are permitted provided that the following conditions
     7 * are met:
     8 *
     9 * - Redistributions of source code must retain the above copyright
     10 *   notice, this list of conditions and the following disclaimer.
     11 * - Redistributions in binary form must reproduce the above copyright
     12 *   notice, this list of conditions and the following disclaimer in the
     13 *   documentation and/or other materials provided with the distribution.
     14 * - The name of the author may not be used to endorse or promote products
     15 *   derived from this software without specific prior written permission.
     16 *
     17 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
     18 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
     19 * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
     20 * IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
     21 * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
     22 * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
     23 * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
     24 * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
     25 * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
     26 * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
     27 */
     28
     29/** @addtogroup xen32interrupt
     30 * @{
     31 */
     32/** @file
     33 */
     34
     35#include <arch/interrupt.h>
     36#include <syscall/syscall.h>
     37#include <print.h>
     38#include <debug.h>
     39#include <panic.h>
     40#include <func.h>
     41#include <cpu.h>
     42#include <arch/asm.h>
     43#include <mm/tlb.h>
     44#include <mm/as.h>
     45#include <arch.h>
     46#include <symtab.h>
     47#include <proc/thread.h>
     48#include <proc/task.h>
     49#include <synch/spinlock.h>
     50#include <arch/ddi/ddi.h>
     51#include <ipc/sysipc.h>
     52#include <interrupt.h>
     53
     54/*
     55 * Interrupt and exception dispatching.
     56 */
     57
     58void (* disable_irqs_function)(uint16_t irqmask) = NULL;
     59void (* enable_irqs_function)(uint16_t irqmask) = NULL;
     60void (* eoi_function)(void) = NULL;
     61
     62void PRINT_INFO_ERRCODE(istate_t *istate)
     63{
     64        char *symbol = get_symtab_entry(istate->eip);
     65
     66        if (!symbol)
     67                symbol = "";
     68
     69        if (CPU)
     70                printf("----------------EXCEPTION OCCURED (cpu%d)----------------\n", CPU->id);
     71        else
     72                printf("----------------EXCEPTION OCCURED----------------\n");
     73               
     74        printf("%%eip: %#x (%s)\n",istate->eip,symbol);
     75        printf("ERROR_WORD=%#x\n", istate->error_word);
     76        printf("%%cs=%#x,flags=%#x\n", istate->cs, istate->eflags);
     77        printf("%%eax=%#x, %%ecx=%#x, %%edx=%#x, %%esp=%#x\n",  istate->eax,istate->ecx,istate->edx,&istate->stack[0]);
     78#ifdef CONFIG_DEBUG_ALLREGS
     79        printf("%%esi=%#x, %%edi=%#x, %%ebp=%#x, %%ebx=%#x\n",  istate->esi,istate->edi,istate->ebp,istate->ebx);
     80#endif
     81        printf("stack: %#x, %#x, %#x, %#x\n", istate->stack[0], istate->stack[1], istate->stack[2], istate->stack[3]);
     82        printf("       %#x, %#x, %#x, %#x\n", istate->stack[4], istate->stack[5], istate->stack[6], istate->stack[7]);
     83}
     84
     85void null_interrupt(int n, istate_t *istate)
     86{
     87        fault_if_from_uspace(istate, "unserviced interrupt: %d", n);
     88
     89        PRINT_INFO_ERRCODE(istate);
     90        panic("unserviced interrupt: %d\n", n);
     91}
     92
     93/** General Protection Fault. */
     94void gp_fault(int n, istate_t *istate)
     95{
     96        if (TASK) {
     97                count_t ver;
     98               
     99                spinlock_lock(&TASK->lock);
     100                ver = TASK->arch.iomapver;
     101                spinlock_unlock(&TASK->lock);
     102       
     103                if (CPU->arch.iomapver_copy != ver) {
     104                        /*
     105                         * This fault can be caused by an early access
     106                         * to I/O port because of an out-dated
     107                         * I/O Permission bitmap installed on CPU.
     108                         * Install the fresh copy and restart
     109                         * the instruction.
     110                         */
     111                        io_perm_bitmap_install();
     112                        return;
     113                }
     114                fault_if_from_uspace(istate, "general protection fault");
     115        }
     116
     117        PRINT_INFO_ERRCODE(istate);
     118        panic("general protection fault\n");
     119}
     120
     121void ss_fault(int n, istate_t *istate)
     122{
     123        fault_if_from_uspace(istate, "stack fault");
     124
     125        PRINT_INFO_ERRCODE(istate);
     126        panic("stack fault\n");
     127}
     128
     129void simd_fp_exception(int n, istate_t *istate)
     130{
     131        uint32_t mxcsr;
     132        asm
     133        (
     134                "stmxcsr %0;\n"
     135                :"=m"(mxcsr)
     136        );
     137        fault_if_from_uspace(istate, "SIMD FP exception(19), MXCSR: %#zx",
     138                             (unative_t)mxcsr);
     139
     140        PRINT_INFO_ERRCODE(istate);
     141        printf("MXCSR: %#zx\n",(unative_t)(mxcsr));
     142        panic("SIMD FP exception(19)\n");
     143}
     144
     145void nm_fault(int n, istate_t *istate)
     146{
     147#ifdef CONFIG_FPU_LAZY     
     148        scheduler_fpu_lazy_request();
     149#else
     150        fault_if_from_uspace(istate, "fpu fault");
     151        panic("fpu fault");
     152#endif
     153}
     154
     155void syscall(int n, istate_t *istate)
     156{
     157        panic("Obsolete syscall handler.");
     158}
     159
     160void tlb_shootdown_ipi(int n, istate_t *istate)
     161{
     162        trap_virtual_eoi();
     163        tlb_shootdown_ipi_recv();
     164}
     165
     166void trap_virtual_enable_irqs(uint16_t irqmask)
     167{
     168        if (enable_irqs_function)
     169                enable_irqs_function(irqmask);
     170        else
     171                panic("no enable_irqs_function\n");
     172}
     173
     174void trap_virtual_disable_irqs(uint16_t irqmask)
     175{
     176        if (disable_irqs_function)
     177                disable_irqs_function(irqmask);
     178        else
     179                panic("no disable_irqs_function\n");
     180}
     181
     182void trap_virtual_eoi(void)
     183{
     184        if (eoi_function)
     185                eoi_function();
     186        else
     187                panic("no eoi_function\n");
     188
     189}
     190
     191static void ipc_int(int n, istate_t *istate)
     192{
     193        ipc_irq_send_notif(n-IVT_IRQBASE);
     194        trap_virtual_eoi();
     195}
     196
     197
     198/* Reregister irq to be IPC-ready */
     199void irq_ipc_bind_arch(unative_t irq)
     200{
     201        if (irq == IRQ_CLK)
     202                return;
     203        exc_register(IVT_IRQBASE+irq, "ipc_int", ipc_int);
     204        trap_virtual_enable_irqs(1 << irq);
     205}
     206
     207/** @}
     208 */
     209
  • kernel/arch/xen32/src/mm/frame.c

    r7b0599b raecf79f  
    5252void frame_arch_init(void)
    5353{
    54         static pfn_t minconf;
    55 
    5654        if (config.cpu_active == 1) {
    57                 minconf = 1;
    58 #ifdef CONFIG_SIMICS_FIX
    59                 minconf = max(minconf, ADDR2PFN(0x10000));
    60 #endif
    61 
    62                 /* Reserve frame 0 (BIOS data) */
    63                 frame_mark_unavailable(0, 1);
     55                pfn_t start = ADDR2PFN(ALIGN_UP(KA2PA(start_info.pt_base), PAGE_SIZE)) + start_info.nr_pt_frames;
     56                size_t size = start_info.nr_pages - start;
    6457               
    65 #ifdef CONFIG_SIMICS_FIX
    66                 /* Don't know why, but these addresses help */
    67                 frame_mark_unavailable(0xd000 >> FRAME_WIDTH,3);
    68 #endif
     58                zone_create(start, size, start, 0);
     59                last_frame = start + size;
    6960        }
    7061}
  • kernel/arch/xen32/src/mm/page.c

    r7b0599b raecf79f  
    7878}
    7979
    80 
    81 uintptr_t hw_map(uintptr_t physaddr, size_t size)
    82 {
    83         if (last_frame + ALIGN_UP(size, PAGE_SIZE) > KA2PA(KERNEL_ADDRESS_SPACE_END_ARCH))
    84                 panic("Unable to map physical memory %p (%d bytes)", physaddr, size)
    85        
    86         uintptr_t virtaddr = PA2KA(last_frame);
    87         pfn_t i;
    88         for (i = 0; i < ADDR2PFN(ALIGN_UP(size, PAGE_SIZE)); i++)
    89                 page_mapping_insert(AS_KERNEL, virtaddr + PFN2ADDR(i), physaddr + PFN2ADDR(i), PAGE_NOT_CACHEABLE);
    90        
    91         last_frame = ALIGN_UP(last_frame + size, FRAME_SIZE);
    92        
    93         return virtaddr;
    94 }
    95 
    9680void page_fault(int n, istate_t *istate)
    9781{
    98         uintptr_t page;
     82        uintptr_t page;
    9983        pf_access_t access;
    10084       
    101         page = read_cr2();
    102                
    103         if (istate->error_word & PFERR_CODE_RSVD)
     85        page = read_cr2();
     86       
     87        if (istate->error_word & PFERR_CODE_RSVD)
    10488                panic("Reserved bit set in page directory.\n");
    105 
     89       
    10690        if (istate->error_word & PFERR_CODE_RW)
    10791                access = PF_ACCESS_WRITE;
    10892        else
    10993                access = PF_ACCESS_READ;
    110 
    111         if (as_page_fault(page, access, istate) == AS_PF_FAULT) {
     94       
     95        if (as_page_fault(page, access, istate) == AS_PF_FAULT) {
    11296                fault_if_from_uspace(istate, "Page fault: %#x", page);
    113 
    114                 PRINT_INFO_ERRCODE(istate);
    115                 printf("page fault address: %#x\n", page);
    116                 panic("page fault\n");
    117         }
     97               
     98                PRINT_INFO_ERRCODE(istate);
     99                printf("page fault address: %#x\n", page);
     100                panic("page fault\n");
     101        }
    118102}
    119103
  • kernel/arch/xen32/src/pm.c

    r7b0599b raecf79f  
    7474        /* TLS descriptor */
    7575        { 0xffff, 0, 0, AR_PRESENT | AR_DATA | AR_WRITABLE | DPL_USER, 0xf, 0, 0, 1, 1, 0 },
    76         /* VESA Init descriptor */
    77 #ifdef CONFIG_FB
    78         { 0xffff, 0, VESA_INIT_SEGMENT>>12, AR_PRESENT | AR_CODE | DPL_KERNEL, 0xf, 0, 0, 0, 0, 0 }
    79 #endif 
    8076};
    8177
     
    153149static void clean_IOPL_NT_flags(void)
    154150{
    155         __asm__ volatile (
    156                 "pushfl\n"
    157                 "pop %%eax\n"
    158                 "and $0xffff8fff, %%eax\n"
    159                 "push %%eax\n"
    160                 "popfl\n"
    161                 : : : "eax"
    162         );
     151//      __asm__ volatile (
     152//              "pushfl\n"
     153//              "pop %%eax\n"
     154//              "and $0xffff8fff, %%eax\n"
     155//              "push %%eax\n"
     156//              "popfl\n"
     157//              : : : "eax"
     158//      );
    163159}
    164160
     
    166162static void clean_AM_flag(void)
    167163{
    168         __asm__ volatile (
    169                 "mov %%cr0, %%eax\n"
    170                 "and $0xfffbffff, %%eax\n"
    171                 "mov %%eax, %%cr0\n"
    172                 : : : "eax"
    173         );
     164//      __asm__ volatile (
     165//              "mov %%cr0, %%eax\n"
     166//              "and $0xfffbffff, %%eax\n"
     167//              "mov %%eax, %%cr0\n"
     168//              : : : "eax"
     169//      );
    174170}
    175171
     
    184180        idtr.limit = sizeof(idt);
    185181        idtr.base = (uintptr_t) idt;
    186         gdtr_load(&gdtr);
    187         idtr_load(&idtr);
     182//      gdtr_load(&gdtr);
     183//      idtr_load(&idtr);
    188184       
    189185        /*
     
    192188         */
    193189
    194         if (config.cpu_active == 1) {
    195                 idt_init();
    196                 /*
    197                  * NOTE: bootstrap CPU has statically allocated TSS, because
    198                  * the heap hasn't been initialized so far.
    199                  */
     190//      if (config.cpu_active == 1) {
     191//              idt_init();
     192//              /*
     193//               * NOTE: bootstrap CPU has statically allocated TSS, because
     194//               * the heap hasn't been initialized so far.
     195//               */
    200196                tss_p = &tss;
    201         }
    202         else {
    203                 tss_p = (tss_t *) malloc(sizeof(tss_t), FRAME_ATOMIC);
    204                 if (!tss_p)
    205                         panic("could not allocate TSS\n");
    206         }
    207 
    208         tss_initialize(tss_p);
     197//      }
     198//      else {
     199//              tss_p = (tss_t *) malloc(sizeof(tss_t), FRAME_ATOMIC);
     200//              if (!tss_p)
     201//                      panic("could not allocate TSS\n");
     202//      }
     203
     204//      tss_initialize(tss_p);
    209205       
    210206        gdt_p[TSS_DES].access = AR_PRESENT | AR_TSS | DPL_KERNEL;
     
    219215         * to its own TSS. We just need to load the TR register.
    220216         */
    221         tr_load(selector(TSS_DES));
     217//      tr_load(selector(TSS_DES));
    222218       
    223219        clean_IOPL_NT_flags();    /* Disable I/O on nonprivileged levels and clear NT flag. */
  • kernel/arch/xen32/src/smp/smp.c

    r7b0599b raecf79f  
    5454#include <print.h>
    5555#include <memstr.h>
    56 #include <arch/drivers/i8259.h>
    5756
    5857#ifdef CONFIG_SMP
     
    119118        outb(0x71,0xa);
    120119
    121         pic_disable_irqs(0xffff);
     120//      pic_disable_irqs(0xffff);
    122121        apic_init();
    123122
  • kernel/arch/xen32/src/xen32.c

    r7b0599b raecf79f  
    4040#include <arch/pm.h>
    4141
    42 #include <arch/drivers/ega.h>
    43 #include <arch/drivers/vesa.h>
    44 #include <genarch/i8042/i8042.h>
    45 #include <arch/drivers/i8254.h>
    46 #include <arch/drivers/i8259.h>
     42#include <arch/drivers/xconsole.h>
    4743
    4844#include <arch/context.h>
     
    6864void arch_pre_mm_init(void)
    6965{
    70 //      pm_init();
     66        pm_init();
    7167
    7268        if (config.cpu_active == 1) {
    7369//              bios_init();
    74 //              i8259_init();   /* PIC */
    75 //              i8254_init();   /* hard clock */
    7670               
    7771//              exc_register(VECTOR_SYSCALL, "syscall", (iroutine) syscall);
     
    8781{
    8882        if (config.cpu_active == 1) {
    89 
    90 #ifdef CONFIG_FB
    91                 if (vesa_present())
    92                         vesa_init();
    93                 else
    94 #endif
    95                         ega_init();     /* video */
    96                
    97                
     83                /* video */
     84                xen_console_init();
    9885                /* Enable debugger */
    9986                debugger_init();
     
    116103void arch_post_smp_init(void)
    117104{
    118         i8042_init();   /* keyboard controller */
    119105}
    120106
    121107void calibrate_delay_loop(void)
    122108{
    123         i8254_calibrate_delay_loop();
     109//      i8254_calibrate_delay_loop();
    124110        if (config.cpu_active == 1) {
    125111                /*
     
    127113                 * On SMP, i8254 is not used for time keeping and its interrupt pin remains masked.
    128114                 */
    129                 i8254_normal_operation();
     115//              i8254_normal_operation();
    130116        }
    131117}
     
    149135void arch_grab_console(void)
    150136{
    151         i8042_grab();
    152137}
     138
    153139/** Return console to userspace
    154140 *
     
    156142void arch_release_console(void)
    157143{
    158         i8042_release();
    159144}
    160145
  • kernel/kernel.config

    r7b0599b raecf79f  
    3838
    3939# Framebuffer support
    40 ! [(ARCH=mips32&MACHINE=lgxemul)|(ARCH=mips32&MACHINE=bgxemul)|(ARCH=ia32)|(ARCH=amd64)|(ARCH=xen32)] CONFIG_FB (y/n)
     40! [(ARCH=mips32&MACHINE=lgxemul)|(ARCH=mips32&MACHINE=bgxemul)|(ARCH=ia32)|(ARCH=amd64)] CONFIG_FB (y/n)
    4141
    4242# Framebuffer width
     
    5050@ "1600"
    5151@ "2048"
    52 ! [(ARCH=ia32|ARCH=amd64|ARCH=xen32)&CONFIG_FB=y] CONFIG_VESA_WIDTH (choice)
     52! [(ARCH=ia32|ARCH=amd64)&CONFIG_FB=y] CONFIG_VESA_WIDTH (choice)
    5353
    5454# Framebuffer height
     
    6363@ "1200"
    6464@ "1536"
    65 ! [(ARCH=ia32|ARCH=amd64|ARCH=xen32)&CONFIG_FB=y] CONFIG_VESA_HEIGHT (choice)
     65! [(ARCH=ia32|ARCH=amd64)&CONFIG_FB=y] CONFIG_VESA_HEIGHT (choice)
    6666
    6767# Framebuffer depth
     
    6969@ "16"
    7070@ "24"
    71 ! [(ARCH=ia32|ARCH=amd64|ARCH=xen32)&CONFIG_FB=y] CONFIG_VESA_BPP (choice)
     71! [(ARCH=ia32|ARCH=amd64)&CONFIG_FB=y] CONFIG_VESA_BPP (choice)
    7272
    7373# Support for SMP
     
    116116@ "synch/semaphore1" Semaphore test 1
    117117@ "synch/semaphore2" Sempahore test 2
    118 @ [ARCH=ia32|ARCH=amd64|ARCH=ia64|ARCH=xen32] "fpu/fpu1" Intel fpu test 1
    119 @ [ARCH=ia32|ARCH=amd64|ARCH=xen32] "fpu/sse1" Intel Sse test 1
     118@ [ARCH=ia32|ARCH=amd64|ARCH=ia64|ARCH=xen32] "fpu/fpu1" Intel FPU test 1
     119@ [ARCH=ia32|ARCH=amd64|ARCH=xen32] "fpu/sse1" Intel SSE test 1
    120120@ [ARCH=mips32&MACHINE!=msim&MACHINE!=simics] "fpu/mips1" MIPS FPU test 1
    121121@ "print/print1" Printf test 1
Note: See TracChangeset for help on using the changeset viewer.