]> rtime.felk.cvut.cz Git - l4.git/blob - kernel/fiasco/src/kern/ia32/64/shortcut.S
update
[l4.git] / kernel / fiasco / src / kern / ia32 / 64 / shortcut.S
1
2 #include "config_gdt.h"
3 #include "config_tcbsize.h"
4 #include "globalconfig.h"
5 #include "idt_init.h"
6 #include <low_level.h>
7 #include "shortcut.h"
8 #include "tcboffset.h"
9 #include "regdefs.h"
10 #include "asm.h"
11
12 #define L4_IPC_RECANCELED               0x40
13 #define L4_IPC_RETIMEOUT                0x20
14
15 #define PDIR_IDX(virt)                  (((virt) >> 22) & 0x3ff)
16
17 /* stack layout
18         SS
19         ESP
20         EFL
21         CS
22         EIP
23         
24         %rax    
25         %rbp
26         %rbx
27         %rdi
28         %rsi
29         %rdx
30         %rcx
31         %r8
32         %r9
33         %r10
34         %r11
35         %r12
36         %r13
37         %r14
38         %r15
39 */
40
41         
42 // XXXX: let save the user r8-r14 or use them as
43 // additional IPC registers (would be the best solution)
44 // then we can save and restore them lazily (only
45 // if we need will block. If we dont block,
46 // we can leave them in place.
47                 
48 #define OFS__THREAD__SS   (THREAD_BLOCK_SIZE - 1*8)
49 #define OFS__THREAD__ESP  (THREAD_BLOCK_SIZE - 2*8)
50 #define OFS__THREAD__EFL  (THREAD_BLOCK_SIZE - 3*8)
51 #define OFS__THREAD__CS   (THREAD_BLOCK_SIZE - 4*8)
52 #define OFS__THREAD__EIP  (THREAD_BLOCK_SIZE - 5*8)
53
54 // In the SYSENTER path all kernel memory accesses go through stack
55 // segment ss. This way we do not need to RESET_KERNEL_SEGMENTS in
56 // SMAS. The RESET_KERNEL_SEGMENTS function is executed if the shortcut
57 // fails or we switch to another thread which is not in shortcut.
58
59         //
60         // ready_enqueue
61         //
62         // Here we don't check if the context which is to be enqueued is
63         // not current() and has the same priority as current(). In this
64         // case, Context::ready_enqueue() enqueues current() first. We
65         // don't do this here but the location this macro is called from
66         // has to check this.
67         //
68         // precondition  : ecx = thread->sched()
69         //                 rax = thread->sched()->prio() (upper 32bits 0)
70         // scratches     : ecx, edx
71         .macro  READY_ENQUEUE thread, label
72         // if (prio > prio_highest)
73         //   prio_highest = prio
74         cmp     CONTEXT_PRIO_HIGHEST, %eax
75         jbe     1f
76         mov     %eax, CONTEXT_PRIO_HIGHEST
77
78 1:      mov    CONTEXT_PRIO_NEXT (, %rax, 8), %rdx
79         // if (!prio_next[prio])
80         or      %rdx, %rdx
81         jnz     2f
82         // prio_next[prio] = this;
83         mov    \thread, CONTEXT_PRIO_NEXT (, %rax, 8)
84         // ready_next = this;
85         mov     \thread, OFS__THREAD__READY_NEXT (\thread)
86         // ready_prev = this;
87         mov     \thread, OFS__THREAD__READY_PREV (\thread)
88         jmp     \label
89 2:      // ecx = prio_next[prio]->ready_prev
90         mov    OFS__THREAD__READY_PREV (%rdx), %rcx
91         // ready_next = prio_next[prio]
92         mov    %rdx, OFS__THREAD__READY_NEXT (\thread)
93         // ready_prev = prio_next[prio]->ready_prev
94         mov    %rcx, OFS__THREAD__READY_PREV (\thread)
95         // prio_next[prio]->ready_prev = this
96         mov     \thread, OFS__THREAD__READY_PREV (%rdx)
97         // ready_prev->ready_next = this
98         mov     \thread, OFS__THREAD__READY_NEXT (%rcx)
99         .endm
100
101
102 # define KIP_SWITCH_TIME   0xA8
103 # define KIP_CONSUMED_TIME 0xB8
104
105         //
106         // bookkeeping for the time a thread consumed
107         //
108         // precondition  : ebx = THIS
109         //                 esi = DEST
110         // scratches     : eax, ecx, edx, ebp
111         .macro  CONSUME_TIME
112         .endm
113
114
115 #ifdef CONFIG_ASSEMBLER_IPC_SHORTCUT
116
117 // only dummys
118
119         .globl  entry_sys_ipc
120 entry_sys_ipc:
121         push    %rax
122         SAVE_STATE
123         ESP_TO_TCB_AT %rbx
124         RESET_THREAD_CANCEL_AT %rbx
125
126 #define THIS_rbx %rbx
127
128         call    ipc_short_cut_wrapper
129 in_slow_ipc1:
130         RESTORE_STATE
131         pop     %rax
132         iretq
133         .globl  in_slow_ipc1
134
135 i30_ret_switch:
136         .globl  i30_ret_switch
137
138
139 #ifndef CONFIG_PF_UX
140
141 // IPC entry point for sysenter. 
142
143         .align  16
144         .globl  entry_sys_fast_ipc
145         .globl  entry_syscall
146 entry_sys_fast_ipc:
147 entry_syscall:
148         mov     %rsp,%r15               /* save user rsp */
149         mov     syscall_rsp0,%rsp       /* get address of kernel stack */
150         pop     %rsp                    /* set kernel stack */
151
152 /* we dont need the segment stuff */
153 //      push    $(GDT_DATA_USER | SEL_PL_U)     /* fake user ss */
154         sub     $8, %rsp
155         push    %r15                            /* save user rsp */
156         push    %r11                            /* save user rflags */
157         
158 //      push    $(GDT_CODE_USER | SEL_PL_U)     /* fake user cs */
159         sub     $8, %rsp
160         push    %rcx                            /* save user rip */
161
162         SAVE_STATE_SYSEXIT
163         ESP_TO_TCB_AT %rbx
164 #define THIS_rbx %rbx
165         RESET_THREAD_CANCEL_AT %rbx
166
167
168         // test if long send or no send at all
169         test    $~0, %rax
170         jnz     se_shortcut_failed
171
172         // test if destination is L4_INVALID_ID
173
174         // because the default op-size is 32 bit
175         // i will use the 32bit regs if possible
176         // to save the 64bit op-prefix
177         // operations on the 32bit registers
178         // will zero out the upper 32bits.
179         
180         cmp     $~0, %esi
181         je      se_shortcut_failed
182
183         // test if destination is L4_NIL_ID
184         test    %esi, %esi
185         jz      se_shortcut_failed
186
187         // test if destination has ``next_period'' bit set
188         movabsq $0x0020000000000000, %rcx
189         test    %rcx, %rsi
190         jnz     se_shortcut_failed
191
192 //      int3
193
194 // at this point we need only the lower 32bits of the dest id
195 // the higher bits will masked out later
196
197 // the ver0 field (the lower 10bits) of the ID spawns 1024 bytes,
198 // so multiply it by 4
199         shl     $2, %esi
200         and     $TCB_ADDRESS_MASK, %rsi
201
202 // this works, because the kernel lies in the top of the
203 // virt. address space, where all higher bits are 1
204         or      $VAL__MEM_LAYOUT__TCBS, %rsi    // dst = dst_id.lookup
205 #define DEST_rsi %rsi
206
207 //      int3
208
209 #define RECV_DESC_rbp           %rbp
210 #define RECV_DESC_rbp_low       %ebp
211
212         // test if have receive operation
213         cmp     $~0, RECV_DESC_rbp
214 /*      je      se_test_tcb_mapped              // no */
215         // first version will handle only send+rcv
216         je      se_shortcut_failed      
217
218         // test if short receive
219         cmp     $1, RECV_DESC_rbp
220         ja      se_shortcut_failed              // more than 2 dwords
221
222         // rdi contains the timeout
223         // test if simple timeout
224         testl   $0x0f, %edi                     // rcv_to==inf => exp = 0
225         jz      1f                              // rcv_to==inf => o.k.
226         testl   $0xff000000, %edi
227         jnz     se_shortcut_failed              // (rcv_to!=inf) && (rcv_to!=0)
228
229 1:      // test if open wait and (irq attached or sender queued)
230         // ebp is 0 (receive) or 1 (open wait) here
231         test    RECV_DESC_rbp_low, RECV_DESC_rbp_low
232         jz      se_test_tcb_mapped              // closed wait
233
234         mov     OFS__THREAD__SENDER_FIRST (THIS_rbx), %rax
235         test    %rax, %rax
236         jnz     se_shortcut_failed
237         or      OFS__THREAD__IRQ (THIS_rbx), %rax
238         jnz     se_shortcut_failed
239         jmp     se_test_tcb_mapped
240
241 //      int3
242         .align  8
243 se_shortcut_failed:
244         // shortcut failed, execute normal ipc C++ pass
245         CNT_SHORTCUT_FAILED
246         call    sys_ipc_wrapper
247 in_slow_ipc2:
248         DO_SYSEXIT
249
250
251         .align  16
252 se_test_tcb_mapped:
253
254         lea     OFS__THREAD__STATE (DEST_rsi), %rcx // addr of dst tcb state
255
256         // Here we could raise a pagefault. The pagefault handler notices
257         // that by looking at the pagefault address. In that case the pager
258         // sets the carry flag and returns immediatly.
259         andl    $~0, %ss:(%rcx)         // can raise pagefault
260         jc      se_shortcut_failed_1            // tcb is not paged
261
262         testl   $(Thread_delayed_deadline | Thread_delayed_ipc), (%rcx)
263         jnz     se_shortcut_failed_1
264
265         // we assume the thread state will fit in the first 32bit
266         mov     (%rcx), %eax
267
268         and     $(Thread_receiving | Thread_send_in_progress | \
269                 Thread_ipc_in_progress), %eax
270
271         mov     OFS__THREAD__PARTNER (DEST_rsi), %rdx
272         
273         // dst->thread_lock()->test()
274         cmp     $0, \
275                 OFS__THREAD__THREAD_LOCK__SWITCH_LOCK__LOCK_OWNER (DEST_rsi)
276         jne     se_shortcut_failed_1            // dst is locked
277
278         lea     CAST__Thread_TO_Sender (THIS_rbx), %rcx // (Sender*)this
279
280         //    (ipc_state == (Thread_receiving | Thread_ipc_in_progress)
281         cmpb    $(Thread_ipc_in_progress | Thread_receiving), %al
282         jne     se_shortcut_failed_1
283
284         // see Receiver::sender_ok
285         mov    OFS__THREAD__SENDER_FIRST (DEST_rsi), %rax
286
287         // if DEST_esi->partner() == 0, openwait
288         test    %rdx, %rdx
289         jne     1f
290
291         // sender_queue empty?
292         test    %rax, %rax
293         jnz     1f
294         jmp     se_sender_ok
295
296 1:      // if DEST_esi->partner() == this, wait for me
297         cmp     %rcx, %rdx
298         jne     se_shortcut_failed_1
299
300         jmp     se_sender_ok
301 se_shortcut_failed_1:
302         jmp     se_shortcut_failed
303
304         .align  16
305
306 se_sender_ok:
307         CNT_SHORTCUT_SUCCESS
308
309         // clear, we need it later
310         xor     %eax, %eax
311
312         // wake up receiver
313         andl    $~(Thread_ipc_receiving_mask | \
314                    Thread_ipc_in_progress), OFS__THREAD__STATE (DEST_rsi)
315         orb     $Thread_ready, OFS__THREAD__STATE (DEST_rsi)
316
317         // %eax=0 => default: no receive part => status ok
318
319         // prepare a receive if we have one
320         cmp     $~0, RECV_DESC_rbp
321         je      se_do_switch_exec               // no receive part
322         // we should jump, because we have ruled out receiving before
323
324 //      int3
325
326 #define REGS_rsp        %rsp
327         // set_rcv_regs (regs)
328         mov     REGS_rsp, OFS__THREAD__RCV_REGS (THIS_rbx)
329
330         orb     $(Thread_receiving | Thread_ipc_in_progress),\
331                  OFS__THREAD__STATE (THIS_rbx)
332
333         // default: open wait
334         xor     %ecx, %ecx
335
336         test    RECV_DESC_rbp_low, RECV_DESC_rbp_low    // open wait?
337         jnz     1f                                      // openwait cmp yes
338
339         // set dst's partner
340         lea     CAST__Thread_TO_Sender (DEST_rsi), %rcx // (Sender*)dst
341
342 1:      mov     %rcx, OFS__THREAD__PARTNER (THIS_rbx)
343
344         // timeout = 0
345         movb    $L4_IPC_RETIMEOUT, %al
346         testl   $0x0f, %edi                     // rcv_to==inf => exp = 0
347         jne     se_do_switch_exec               // timeout==inf? no
348
349         // timeout = infinite ==> need wakeup
350         movb    $L4_IPC_RECANCELED, %al
351         andb    $~Thread_ready, OFS__THREAD__STATE (THIS_rbx)
352
353         .align  16
354 se_do_switch_exec:
355
356         mov     %rax, REG_RAX (REGS_rsp)        // store ipc result
357
358         CNT_CONTEXT_SWITCH
359
360         mov     OFS__THREAD__STATE (THIS_rbx), %eax
361         test    $Thread_fpu_owner, %eax
362         jz      1f
363         // set ts
364         mov     %cr0, %rdx
365         or      $CR0_TS, %rdx
366         mov     %rdx, %cr0   
367         jmp     2f
368
369 1:      testl   $Thread_fpu_owner, OFS__THREAD__STATE (DEST_rsi)
370         jz      2f
371         // clear ts
372         clts       
373
374 2:      // %eax=thread_state (THIS_ebx)
375         xor     %edx, %edx
376
377         // if (state() & Thread_ready && ! in_ready_list())
378         //   ready_enqueue()
379         cmp     %rdx, OFS__THREAD__READY_NEXT (THIS_rbx)
380         jne     se_no_enqueue
381         testb   $Thread_ready, %al
382         jnz     se_enqueue_this
383
384         .align  8
385 se_no_enqueue:
386         // not for performance kernels!
387         CONSUME_TIME            // scratches eax, ecx, edx, ebp
388
389         // push restart address onto old stack
390
391 //      mov     $se_ret_switch, %rax
392         lea     se_ret_switch(%rip), %rax
393         pushq   %rax
394
395         mov     REGS_rsp, OFS__THREAD__KERNEL_SP (THIS_rbx)
396 #undef REGS_rsp
397 #define DEST_KERNEL_SP_rbp %rbp
398         mov     OFS__THREAD__KERNEL_SP (DEST_rsi), DEST_KERNEL_SP_rbp
399
400         // switch esp0 on TSS
401         mov     CPUS_BASE + OFS__CPU__TSS, %rax
402         leaq    THREAD_BLOCK_SIZE (DEST_rsi), %rcx
403
404         mov     %rcx, 4 (%rax)  // x86_tss.esp0
405
406         // we dont clear the IPC window of the destination thread
407         // reason: ipc already finished and the destination thread
408         // will setup an new one before entering long IPC again
409
410 //      int3
411         // pdir = space_context - kmem::mem_phys (needed later)
412         movq    OFS__THREAD__SPACE (DEST_rsi), %rax
413         leaq    OFS__SPACE__MEM_SPACE (%rax), %rax
414         sub     PHYSMEM_OFFS, %rax
415
416         mov     PAGE_DIR_ADDR, %rcx             // get_pdir()
417         cmp     %rax, %rcx                      // get_pdir == pdir
418         jne     se_flush_pdir                   // no => flush
419
420 se_addr_space_switched: 
421
422         lea     se_ret_switch(%rip), %rax
423         cmp     %rax, (DEST_KERNEL_SP_rbp)
424         jne     se_slow_switch
425
426         RESET_THREAD_IPC_MASK_AT DEST_rsi
427
428         // Setup return registers. We have to add 8 to each %rsp,%rbp reference
429         // since there is the return address pushed on the stack.
430         
431         mov     OFS__THREAD__EIP (DEST_rsi), %rcx
432         /* make RIP canonical, workaround for intel IA32e flaw */
433         shl     $16, %rcx
434         sar     $16, %rcx
435         mov     OFS__THREAD__ESP (DEST_rsi), %r15
436         mov     OFS__THREAD__EFL (DEST_rsi), %r11       
437         mov     OFS__THREAD__ID  (THIS_rbx), %rsi
438
439         mov     8+REG_RDX (%rsp), %rdx
440         mov     8+REG_RBX (%rsp), %rbx
441         mov     $RETURN_DOPE, %eax      
442
443         mov     8+REG_R14 (%rbp), %r14
444         mov     8+REG_R13 (%rbp), %r13
445         mov     8+REG_R12 (%rbp), %r12
446         mov     8+REG_R10 (%rbp), %r10
447         mov     8+REG_R9 (%rbp), %r9
448         mov     8+REG_R8 (%rbp), %r8
449         
450         mov     %r15, %rsp
451         sysretq
452         
453 se_flush_pdir:
454         CNT_ADDR_SPACE_SWITCH
455         mov     %rax, PAGE_DIR_ADDR                     // set pdir, flush TLBs
456         jmp     se_addr_space_switched
457
458 se_enqueue_this:
459         // ecx = sched(), eax = sched()->prio()
460         mov     OFS__THREAD__SCHED (THIS_rbx), %rcx
461
462         xor     %eax, %eax
463         movl    OFS__SCHED_CONTEXT__PRIO (%rcx), %eax
464         READY_ENQUEUE THIS_rbx, se_no_enqueue // scratches ecx, edx
465         jmp     se_no_enqueue
466
467         .align  16
468 se_ret_switch:
469         // shortcut success
470         ESP_TO_TCB_AT %rbx
471         RESET_THREAD_IPC_MASK_AT %rbx
472         DO_SYSEXIT
473
474
475         // The destination thread is not in a shortcut IPC so we cannot
476         // throw it directly into user space since it may held a thread
477         // lock or does not return via sysexit (int-entered IPC or
478         // ex_regs manipulation)
479         .align  16
480 se_slow_switch:
481         mov     OFS__THREAD__RCV_REGS (DEST_rsi), %rax
482         mov     8+REG_RDX (%rsp), %rdx
483         mov     8+REG_RBX (%rsp), %rcx
484         mov     %rdx, REG_RDX (%rax)            // dst_regs->edx = dw1
485         mov     %rcx, REG_RBX (%rax)            // dst_regs->ebx = dw2
486         mov     OFS__THREAD__ID (THIS_rbx), %rdx
487         movq    $RETURN_DOPE, REG_RAX (%rax)
488         mov     %rdx, REG_RSI (%rax)            // dst_regs->esi = id.low
489         mov     %rbp, %rsp                      // load new stack pointer
490         pop     %rax
491         jmp     *%rax
492
493         .globl  in_slow_ipc2
494         .globl  se_ret_switch
495
496 #endif // CONFIG_PF_UX
497
498         .globl  in_slow_ipc1
499         .globl  i30_ret_switch
500
501 #endif // CONFIG_ASSEMBLER_IPC_SHORTCUT
502
503         // fast return from Dirq::hit
504         .align  16
505         .globl  fast_ret_from_irq
506 fast_ret_from_irq:
507         RESTORE_STATE
508         popq    %rax
509         andq    $0x7f, 8(%rsp)                  // if entered using syscall
510         orq     $EFLAGS_IF, 16(%rsp)            // if entered using syscall
511         iretq
512