multithreadingassemblyx86dosdining-philosopher

Is there a way to simulate multithreading in DOS, e.g., when solving the dining philosopher's problem?


The dining philosophers problem is a classic computer science textbook problem for demonstrating the use of multithreading. As Wikipedia says:

Five silent philosophers sit at a round table with bowls of spaghetti. Forks are placed between each pair of adjacent philosophers.

Each philosopher must alternately think and eat. However, a philosopher can only eat spaghetti when they have both left and right forks. Each fork can be held by only one philosopher and so a philosopher can use the fork only if it is not being used by another philosopher. After an individual philosopher finishes eating, they need to put down both forks so that the forks become available to others. A philosopher can only take the fork on their right or the one on their left as they become available and they cannot start eating before getting both forks.

Eating is not limited by the remaining amounts of spaghetti or stomach space; an infinite supply and an infinite demand are assumed.

The problem is how to design a discipline of behavior (a concurrent algorithm) such that no philosopher will starve; i.e., each can forever continue to alternate between eating and thinking, assuming that no philosopher can know when others may want to eat or think.

The problem was designed to illustrate the challenges of avoiding deadlock, a system state in which no progress is possible.

In summary, then, this is a classical problem in multithreading, demonstrating the need to avoid resource starvation using mutual exclusion principles.

I want to implement such a program in real-mode DOS, but DOS clearly lacks multithreading capabilities.

I am aware of third-party software such as RTKernel, but this seems like overkill for this situation.

Is there any solution to simulate multithreading so that I can program a simulation of the dining philosophers problem in DOS, using 16-bit x86 assembly language?


Solution

  • Multithreading is about creating the illusion that multiple execution paths in a program run simultaneously. On today's multi-core computers this doesn't have to be an illusion anymore if the number of threads stays within limits.

    A different road to multithreading

    In the preemptive multitasking model the running out of a timeslice triggers a thread switch. The switch is initiated from outside the running thread.
    In the multithreading module that I have written, the switch can not happen without the running thread's approval and collaboration. It is the running thread that decides where, but not when, a switch can take place. To this end the programmer has to insert calls to a function MaybeYieldThread at strategically chosen places in the thread. Loops are good places for this. If at the moment of such a call, the timeslice has not yet elapsed then the call will instantly return. If the timeslice has elapsed then the MaybeYieldThread momentarily acts like a true YieldThread and the switch happens.

    The major advantage of this approach is that it can avoid many of the race conditions for which you would normally be using synchronization objects like mutexes, semaphores, or critical sections. You insert your call MaybeYieldThread instruction(s) where it is thread-safe and that's it!

    The main characteristics

    The multithreading capabilities are encoded in a single source file mtModule.INC that you include in your application anywhere you like.

    The api description

    The api that I propose is a small one, but I believe it delivers all the multithreading capability a DOS program could need... At some moment I had implemented features like thread handles, thread priorities, and inter thread communication. In retrospect and bearing in mind the saying "Less is More", I am glad that I removed all of these.

    It all starts with a call to BeginSessionThread. You define the borders of the session memory where all of the thread's stacks will be placed, you define the timeslice to be used, and you point to the first thread that immediately receives control if no errors were encountered.

    Among the things that the first thread will do is creating additional threads using CreateThread. What you provide is the code address of the other thread and the amount of memory you wish to use for its stack.

    Once threads are up and running, they can use YieldThread to give up control in favor of the next thread, use MaybeYieldThread to give up control if, and only if, the timeslice that they are running in has elapsed, and use SleepThread to give up control and remove themselves from being scheduled until the requested duration is over.

    If a thread has outlived its purpose, a call (or jmp) to ExitThread or a mere ret instruction (from a balanced stack of course!) removes the thread permanently from the scheduler and returns the memory that its stack occupied, to the pool of free session memory.

    When no more multithreading is needed, a call (or jmp) to EndSessionThread will return control to the instruction directly below from where the session was started (the call BeginSessionThread instruction). It is possible to pass an exitcode.
    Alternatively, exiting from the last active thread will also end the session, but in this case the exitcode will be zero.

    In order to suspend the multithreading session, you can call StopSessionThread. It will reset the timer frequency to the standard 18.2 Hz and freeze all pending SleepTimes. To resume the multithreading session, all it takes is a call to ContSessionThread. Suspending the session is one way to temporarily pause the program without disturbing the SleepTimes. And if you want to EXEC a child program or even launch a nested multithreading session, suspending the current session is mandatory for success.

    The api quick reference

    BeginSessionThread
     Input
      BX timeslice in milliseconds [1,55]
      CX requested stacksize for first thread
      DX near address of first thread
      SI para address begin session memory
      DI para address end session memory
      -- everything else is user defined parameter
     Output
      CF=0 Session has ended, AX is SessionExitcode
      CF=1 'Insufficient memory'
           'Invalid stacksize'
           'Invalid timeslice'
     --------------------------------------
    CreateThread
     Input
      CX requested stacksize for thread
      DX near address of thread
      -- everything else is user defined parameter
     Output
      CF=0 OK
      CF=1 'Invalid stacksize'
           'Out of memory'
     --------------------------------------
    SleepThread
     Input
      CX is requested duration in milliseconds
     Output
      none
     --------------------------------------
    MaybeYieldThread
     Input
      none
     Output
      none
     --------------------------------------
    YieldThread
     Input
      none
     Output
      none
     --------------------------------------
    ExitThread
     Input
      none
     Output
      none
     --------------------------------------
    EndSessionThread
     Input
      CX is SessionExitcode
     Output
      none
     --------------------------------------
    StopSessionThread
     Input
      none
     Output
      none
     --------------------------------------
    ContSessionThread
     Input
      none
     Output
      none
     --------------------------------------
    

    Some points of interest

    It is mandatory that a thread doesn't change the SS segment register and that it leaves about 80 bytes on the stack for use by the mtModule.INC.
    For optimal 'preemptiveness', you should not use MaybeYieldThread too sparsely. On the other hand for efficiency reasons, you should perhaps not be using MaybeYieldThread in a tight loop.

    ; mtModule.INC Multithreading in DOS (c) 2020 Sep Roland
    ; ------------------------------------------------------
    ; assemble with FASM, compatible with CMD and DOSBox
    
    ; Functions:
    ;  BeginSessionThread(BX,CX,DX,SI,DI,..) -> AX CF
    ;  CreateThread(CX,DX,..) -> CF
    ;  SleepThread(CX)
    ;  MaybeYieldThread()
    ;  YieldThread()
    ;  ExitThread()
    ;  EndSessionThread(CX)
    ;  StopSessionThread()
    ;  ContSessionThread()
    
    ; Session header:
    ;  +0  wSessionHighMem
    ;  +2  wSessionNumberOfThreads
    ;  +4 dwSessionParentStackptr
    ;  +8  wSessionTickVarStep
    ; +10  wSessionMicroTimeslice
    ; +12  wSessionTickVar
    
    ; Thread header:
    ;  +0  wThreadLowMem
    ;  +2  wThreadStacksize
    ;  +4  wThreadStatus: DEAD/FREE (-1), AWAKE (0), ASLEEP (1+)
    ;  +6  wThreadStackptr
    ; --------------------------------------
    ; IN (bx=0,cx,dx,ss:si,fs) OUT (ax,CF) MOD (cx,si,di,bp,ds,es)
    mtAlloc:cmp     cx, 4096                ; Max 64KB stack
            ja      .NOK
            cmp     cx, 8                   ; Min 128 bytes stack
            jb      .NOK
    ; Find a free alloc that is big enough
            mov     ax, fs
            inc     ax                      ; Skipping session header
    .a:     mov     ds, ax
            cmp     [bx+4], bx              ; ThreadStatus
            jge     .b                      ; Is occupied
            mov     bp, [bx+2]              ; ThreadStacksize (size of free alloc)
            sub     bp, cx
            jae     .OK
    .b:     add     ax, [bx+2]              ; ThreadStacksize
            cmp     ax, [fs:bx]             ; SessionHighMem
            jb      .a
    .NOK:   stc
            ret
    .OK:    je      .c                      ; Tight fit, no split up
    ; Init header of a free alloc
            add     ax, cx
            mov     ds, ax
            mov     [bx], fs                ; ThreadLowMem
            mov     [bx+2], bp              ; ThreadStacksize
            mov     word [bx+4], -1         ; ThreadStatus = FREE
            sub     ax, cx
            mov     ds, ax
    ; Init thread header
    .c:     mov     [bx], fs                ; ThreadLowMem
            mov     [bx+2], cx              ; ThreadStacksize
            mov     [bx+4], bx              ; ThreadStatus = AWAKE
            imul    di, cx, 16              ; -> DI is total stacksize in bytes
            sub     di, (32+8+4)+2+2        ; Initial items that go on this stack
            mov     [bx+6], di              ; ThreadStackptr
    ; Init thread stack
            mov     es, ax
            mov     cx, (32+8+4)/2          ; GPRs, SRegs, EFlags
            cld
            rep movs word [di], [ss:si]
            mov     [di], dx                ; ThreadAddress
            mov     word [di+2], ExitThread
            inc     word [fs:bx+2]          ; SessionNumberOfThreads
            clc
            ret
    ; --------------------------------------
    ; IN (bx,cx,dx,si,di,..) OUT (ax,CF)
    ; BX timeslice in milliseconds [1,55] (55 uses standard 54.925494 msec)
    ; CX requested stacksize for first thread, DX near address of first thread
    ; SI para address begin session memory, DI para address end session memory
    ;
    ; CF=0  Session has ended, AX is SessionExitcode
    ; CF=1  'Insufficient memory' or 'Invalid stacksize' or 'Invalid timeslice'
    BeginSessionThread:
            pushfd                          ; '..' Every register is considered
            push    ds es fs gs             ; parameter on the first invocation
            pushad                          ; of the thread
    ; Test parameters
            mov     bp, di                  ; SessionHighMem
            sub     bp, si                  ; ThreadLowMem
            jbe     mtFail
            dec     bp
            jz      mtFail
            dec     bx                      ; Timeslice in msec
            cmp     bx, 55
            jnb     mtFail
            inc     bx
    ; Turn MilliTimeslice BX into TickVarStep AX and MicroTimeslice CX
            mov     ax, 65535               ; Standard step is 'chain always'
            mov     cx, 54925               ; Standard slice is 54925.494 microsec
            cmp     bx, 55
            je      .a
            push    dx                      ; (1)
            mov     ax, 1193180 Mod 65536   ; TickVarStep = (1193180 * BX) / 1000
            mul     bx                      ; BX = [1,54]
            imul    cx, bx, 1193180/65536
            add     dx, cx
            mov     cx, 1000
            div     cx                      ; -> AX = {1193, 2386, ..., 64431}
            imul    cx, bx                  ; -> CX = {1000, 2000, ..., 54000}
            pop     dx                      ; (1)
    ; Init session header
    .a:     xor     bx, bx                  ; CONST
            mov     ds, si                  ; -> DS = Session header
            mov     [bx], di                ; SessionHighMem
            mov     [bx+2], bx              ; SessionNumberOfThreads = 0
            mov     [bx+4], sp              ; SessionParentStackptr
            mov     [bx+6], ss
            mov     [bx+8], ax              ; SessionTickVarStep
            mov     [bx+10], cx             ; SessionMicroTimeslice
            ;;mov     [bx+12], bx           ; SessionTickVar = 0
    ; Init header of a free alloc
            mov     [bx+16], ds             ; ThreadLowMem
            mov     [bx+18], bp             ; ThreadStacksize, all of the session
            mov     word [bx+20], -1        ; ThreadStatus = FREE          memory
    ; Create first thread
            mov     fs, si                  ; ThreadLowMem -> FS = Session header
            mov     si, sp                  ; -> SS:SI = Initial registers
            mov     cx, [ss:si+24]          ; pushad.CX
            call    mtAlloc                 ; -> AX CF (CX SI DI BP DS ES)
            jc      mtFail
            mov     [cs:mtTick+5], fs       ; ThreadLowMem
            mov     [cs:mtChain+3], cs      ; Patch far pointer
            call    mtSwap                  ; Hook vector 08h/1Ch
            jmp     mtCont
    ; --------------------------------------
    ; IN (ss:sp)
    mtFail: popad                           ; Return with all registers preserved
            pop     gs fs es ds             ; to caller
            popfd
            stc
            ret
    ; --------------------------------------
    ; IN (cx,dx,..) OUT (CF)
    ; CX requested stacksize for thread, DX near address of thread
    ;
    ; CF=0  OK
    ; CF=1  'Invalid stacksize' or 'Out of memory'
    CreateThread:
            pushfd                          ; '..' Every register is considered
            push    ds es fs gs             ; parameter on the first invocation
            pushad                          ; of the thread
            xor     bx, bx                  ; CONST
            mov     fs, [ss:bx]             ; ThreadLowMem -> FS = Session header
            mov     si, sp                  ; -> SS:SI = Initial registers
    ; Coalescing free blocks
            mov     ax, fs
            inc     ax
    .a:     mov     ds, ax                  ; -> DS = Thread header
            mov     bp, [bx+2]              ; ThreadStacksize
            cmp     [bx+4], bx              ; ThreadStatus
            jge     .c                      ; Is occupied
            mov     es, ax
    .b:     add     ax, bp                  ; BP is size of a free alloc
            cmp     ax, [fs:bx]             ; SessionHighMem
            jnb     .d
            mov     ds, ax
            mov     bp, [bx+2]              ; ThreadStacksize
            cmp     [bx+4], bx              ; ThreadStatus
            jge     .c
            add     [es:bx+2], bp           ; ThreadStacksize, BP is size of
            jmp     .b                      ;    the free alloc that follows
    .c:     add     ax, bp                  ; BP is size of an actual thread stack
            cmp     ax, [fs:bx]             ; SessionHighMem
            jb      .a
    .d:     call    mtAlloc                 ; -> AX CF (CX SI DI BP DS ES)
            jc      mtFail
    ; ---   ---   ---   ---   ---   ---   --
    ; IN (ss:sp)
    mtFine: popad                           ; Return with all registers preserved
            pop     gs fs es ds             ; to caller
            popfd
            clc
            ret
    ; --------------------------------------
    ; IN (cx) OUT ()
    ; CX is requested duration in msec
    SleepThread:
            pushf
            pusha
            push    ds
            xor     bx, bx                  ; CONST
            mov     ds, [ss:bx]             ; ThreadLowMem -> DS = Session header
            mov     ax, 1000                ; TICKS = (CX * 1000) / MicroTimeslice
            mul     cx
            mov     cx, [bx+10]             ; SessionMicroTimeslice
            shr     cx, 1                   ; Rounding to nearest
            adc     ax, cx
            adc     dx, bx
            div     word [bx+10]            ; SessionMicroTimeslice
            mov     [ss:bx+4], ax           ; ThreadStatus = TICKS
            pop     ds
            popa
            popf
            jmp     YieldThread
    ; --------------------------------------
    mtTick: push    ds                      ; 1. Decrement all sleep counters
            pusha
            xor     bx, bx                  ; CONST
            mov     ax, 0                   ; SMC Start of session memory
            mov     ds, ax                  ; ThreadLowMem -> DS = Session header
            mov     cx, [bx+8]              ; SessionTickVarStep
            stc
            adc     [bx+12], cx             ; SessionTickVar
            pushf                           ; (1)
            mov     dx, [bx]                ; SessionHighMem
            inc     ax
    .a:     mov     ds, ax                  ; -> DS = Thread header
            mov     cx, [bx+4]              ; ThreadStatus
            dec     cx
            js      .b                      ; AX was [-1,0], ergo not ASLEEP
            mov     [bx+4], cx              ; ThreadStatus
    .b:     add     ax, [bx+2]              ; ThreadStacksize -> End current stack
            cmp     ax, dx
            jb      .a
            mov     byte [cs:$+23], 90h     ; 2. Turn 'MaybeYield' into 'Yield'
            popf                            ; (1)
            popa
            pop     ds
            jc      mtChain
            push    ax
            mov     al, 20h
            out     20h, al
            pop     ax
            iret
    mtChain:jmp far 0:mtTick                ; 3. Chain to original vector 08h/1Ch
    ; --------------------------------------
    ; IN () OUT ()
    MaybeYieldThread:
            ret                             ; SMC {90h=nop,C3h=ret}
    ; ---   ---   ---   ---   ---   ---   --
    ; IN () OUT ()
    YieldThread:
            mov     byte [cs:$-1], 0C3h     ; Back to 'MaybeYield'
            pushfd                          ; Save context current thread
            push    ds es fs gs
            pushad
            xor     bx, bx                  ; CONST
            mov     ax, ss                  ; Begin current stack
            mov     ds, ax                  ; -> DS = Thread header
            mov     [bx+6], sp              ; ThreadStackptr
            mov     fs, [bx]                ; ThreadLowMem -> FS = Session header
            sti                             ; Guard against every thread ASLEEP!
    .a:     add     ax, [bx+2]              ; ThreadStacksize -> End current stack
            cmp     ax, [fs:bx]             ; SessionHighMem
            jb      .b
            mov     ax, fs                  ; Session header
            inc     ax                      ; Stack lowest thread
    .b:     mov     ds, ax
            cmp     [bx+4], bx              ; ThreadStatus
            jne     .a                      ; Is DEAD/FREE (-1) or ASLEEP (1+)
    ; ---   ---   ---   ---   ---   ---   --
    ; IN (ax,bx=0)
    mtCont: mov     ss, ax
            mov     sp, [ss:bx+6]           ; ThreadStackptr
            popad                           ; Restore context new current thread
            pop     gs fs es ds
            popfd
            ret
    ; --------------------------------------
    ; IN () OUT ()
    ExitThread:
            xor     bx, bx                  ; CONST
            dec     word [ss:bx+4]          ; ThreadStatus = DEAD/FREE
            mov     ds, [ss:bx]             ; ThreadLowMem -> DS = Session header
            dec     word [bx+2]             ; SessionNumberOfThreads
            jnz     YieldThread             ; Not exiting from the sole thread
            xor     cx, cx                  ; SessionExitcode
    ; ---   ---   ---   ---   ---   ---   --
    ; IN (cx) OUT (ax,CF=0)
    EndSessionThread:
            call    mtSwap                  ; Unhook vector 08h/1Ch
            xor     bx, bx                  ; CONST
            mov     ds, [ss:bx]             ; ThreadLowMem -> DS = Session header
            lss     sp, [bx+4]              ; SessionParentStackptr
            mov     [esp+28], cx            ; pushad.AX, SessionExitcode
            jmp     mtFine
    ; --------------------------------------
    ; IN () OUT ()
    StopSessionThread:
    ContSessionThread:
            push    ax
            mov     ax, [ss:0000h]          ; ThreadLowMem -> AX = Session header
            mov     [cs:mtTick+5], ax       ; ThreadLowMem (In case there's been a
            pop     ax                      ;                       nested session)
    ; ---   ---   ---   ---   ---   ---   --
    ; IN () OUT ()
    mtSwap: push    ds
            pushad
            xor     bx, bx                  ; CONST
            mov     ds, bx                  ; -> DS = IVT
            mov     ax, [046Ch]             ; BIOS.Timer
    .Wait:  cmp     ax, [046Ch]
            je      .Wait
            cli
            mov     ds, [cs:mtTick+5]       ; ThreadLowMem -> DS = Session header
            mov     [bx+12], bx             ; SessionTickVar = 0
            mov     dx, [bx+8]              ; SessionTickVarStep
            mov     ds, bx                  ; -> DS = IVT
            mov     bl, 1Ch*4               ; BH=0
            inc     dx                      ; SessionTickVarStep
            jz      .Swap
            dec     dx
            mov     bl, 08h*4               ; BH=0
            mov     ax, cs
            cmp     [cs:mtChain+3], ax
            je      .Hook
    .Unhook:xor     dx, dx
    .Hook:  mov     al, 34h
            out     43h, al
            mov     al, dl
            out     40h, al
            mov     al, dh
            out     40h, al
    .Swap:  mov     eax, [bx]
            xchg    [cs:mtChain+1], eax
            mov     [bx], eax               ; Hook/Unhook vector 08h/1Ch
            sti
            popad
            pop     ds
            ret
    ; --------------------------------------
    

    An example application

    Next demo program uses every function available in the above api. Its sole purpose is to demonstrate how to use the api functions, nothing more.
    It's easy to experiment with different timeslices because you can specify the length of the timeslice (expressed in milliseconds) on the commandline.
    The program runs fine in true real address mode and under emulation (Windows CMD and DOSBox).

    Different types of multithreading

    ; mtVersus.ASM Multithreading in DOS (c) 2020 Sep Roland
    ; ------------------------------------------------------
    ; assemble with FASM, compatible with CMD and DOSBox
    DefaultTimeslice=55                     ; [1,55]
    
            ORG     256
    
            mov     sp, $
            cld
    
    ; Was timeslice specified on commandline ?
            xor     cx, cx                  ; RequestedTimeslice
            mov     si, 0081h               ; Commandline
    Skip:   lodsb
            cmp     al, " "
            je      Skip
            cmp     al, 9
            je      Skip
    Digit:  sub     al, "0"
            jb      Other
            cmp     al, 9
            ja      Other
            cbw
            imul    cx, 10                  ; Reasonably ignoring overflow
            add     cx, ax
            lodsb
            jmp     Digit
    Other:  mov     bx, DefaultTimeslice
            cmp     cx, 1
            jb      Setup
            cmp     cx, 55
            ja      Setup
            mov     bx, cx
    Setup:  mov     di, [0002h]             ; PSP.NXTGRAF -> end of session memory
            lea     si, [di-128]            ; 2KB session memory (11 threads)
            mov     dx, Main
            mov     cx, 8                   ; 128 bytes stack
    
            mov     bp, MsgCO
            call    BeginSessionThread      ; -> AX CF
            jc      Exit
            mov     bp, MsgPE
            call    BeginSessionThread      ; -> AX CF
            ;;;jc      Exit
    
    Exit:   mov     ax, 4C00h               ; DOS.Terminate
            int     21h
    ; --------------------------------------
    ; IN (bp)                               ; BP=ModeOfOperation
    Main:   mov     dx, bp                  ; Displaying title
            mov     ah, 09h                 ; DOS.PrintString
            int     21h
    
            mov     di, EOF                 ; Preparing output string
            mov     cx, 79
            mov     al, " "
            rep stosb
            mov     word [di], 240Dh        ; CR and '$'
    
            mov     di, EOF+6               ; Creating 10 counting threads
            mov     dx, Count
            mov     cx, 8                   ; 128 bytes stack
    .a:     mov     byte [di], "0"
            call    CreateThread            ; -> CF
            jc      EndSessionThread        ; CX=8
            add     di, 8
            cmp     di, EOF+79
            jb      .a
    
            mov     byte [Flag], 0
            mov     dx, 10                  ; Sleep while counters run (10 sec)
    .b:     mov     cx, 1000
            call    SleepThread
            mov     ah, 01h                 ; BIOS.TestKey
            int     16h                     ; -> AX ZF
            jz      .c
            mov     ah, 00h                 ; BIOS.GetKey
            int     16h                     ; -> AX
            call    StopSessionThread
            mov     ah, 00h                 ; BIOS.GetKey
            int     16h                     ; -> AX
            call    ContSessionThread
    .c:     dec     dx
            jnz     .b
    
            not     byte [Flag]             ; Forces all other threads to exit
            call    YieldThread
    
    ; Exiting from the sole thread == EndSessionThread
            mov     dl, 10
            mov     ah, 02h                 ; DOS.PrintChar
            int     21h
            ret                             ; == ExitThread
    ; --------------------------------------
    ; IN (di,bp)                            ; DI=Counter, BP=ModeOfOperation
    Count:  mov     si, di                  ; Position of the ones in our counter
    .a:     mov     al, [si]
            inc     al
            cmp     al, "9"
            jbe     .b
            mov     byte [si], "0"
            dec     si
            cmp     byte [si], " "
            jne     .a
            mov     al, "1"
    .b:     mov     [si], al
            mov     dx, EOF
            mov     ah, 09h                 ; DOS.PrintString
            int     21h
            cmp     bp, MsgPE
            je      .PE
    .CO:    call    YieldThread
            cmp     byte [Flag], 0
            je      Count
            jmp     ExitThread
    .PE:    call    MaybeYieldThread
            cmp     byte [Flag], 0
            je      Count
            ret                             ; == ExitThread
    ; --------------------------------------
    MsgCO:  db      13, 10, '10 seconds of cooperative multithreading '
            db      'using YieldThread():', 13, 10, '$'
    MsgPE:  db      13, 10, '10 seconds of preemptive multithreading '
            db      'using MaybeYieldThread():', 13, 10, '$'
    Flag:   db      0
    ; --------------------------------------
            INCLUDE 'mtModule.INC'
    ; --------------------------------------
    EOF:
    ; --------------------------------------