Ignore:
Timestamp:
Sep 2, 2000, 11:08:23 PM (25 years ago)
Author:
bird
Message:

Merged in the Grace branch. New Win32k!

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/win32k/ldr/mytkExecPgm.asm

    r2872 r4164  
    1 ; $Id: mytkExecPgm.asm,v 1.10 2000-02-23 16:53:04 bird Exp $
     1; $Id: mytkExecPgm.asm,v 1.11 2000-09-02 21:08:10 bird Exp $
    22;
    33; mytkExecPgm - tkExecPgm overload
     
    1010
    1111;
     12;   Defined Constants And Macros
     13;
     14CCHFILENAME     EQU 261                 ; The size of the filename buffer
     15CCHARGUMENTS    EQU 1536                ; The size of the argument buffer
     16CCHMAXPATH      EQU CCHFILENAME - 1     ; Max path length
     17
     18;
    1219;   Include files
    1320;
    1421    include devsegdf.inc
    1522
    16 ;
    17 ;   Imported Functions
     23
     24;
     25;   Imported Functions and variables.
    1826;
    1927    extrn  _g_tkExecPgm:PROC
    20     extrn  AcquireBuffer:PROC
    21     extrn  ReleaseBuffer:PROC
    22     extrn  QueryBufferSegmentOffset:PROC
    2328
    2429    ; Scans strings until empy-string is reached.
     
    4550    extrn  _f_FuBuff:PROC
    4651
     52
     53    ; 32-bit memcpy. (see OS2KTK.h)
     54    extrn _TKFuBuff@16:PROC
     55
     56    ;
     57    ; LDR semaphore
     58    ;
     59    extrn pLdrSem:DWORD
     60    extrn _LDRClearSem@0:PROC
     61    extrn _KSEMRequestMutex@8:PROC
     62    extrn _KSEMQueryMutex@8:PROC
     63
     64    ;
     65    ; Loader State
     66    ;
     67    extrn ulLDRState:DWORD
     68
     69    ;
     70    ; Pointer to current executable module.
     71    ;
     72    extrn pExeModule:DWORD
     73
     74    ;
     75    ; DevHlp32
     76    ;
     77    extrn D32Hlp_VirtToLin:PROC
     78
     79    ;
     80    ; TKSSBase (32-bit)
     81    ;
     82    extrn pulTKSSBase32:DWORD
     83
    4784;
    4885;   Exported symbols
    4986;
    5087    public mytkExecPgm
    51 
     88    public tkExecPgmCopyEnv
     89
     90    public fTkExecPgm
     91    public achTkExecPgmFilename
     92    public achTkExecPgmArguments
     93
     94
     95
     96;
     97; Global data
     98;
     99
     100; Filename and arguments buffers + environment pointer
     101; from the tkExecPgm call.
     102;
     103; This data is only valid at isLdrStateExecPgm time
     104; (and you'll have to be behind the loader semaphore of course!)
     105DATA16 SEGMENT
     106fTkExecPgm              db 0            ; 0 - achTkExecPgmFilename and achTkExecPgmArguments is INVALID
     107                                        ; 1 - achTkExecPgmFilename and achTkExecPgmArguments is VALID.
     108achTkExecPgmFilename    db CCHFILENAME dup (0)  ; The filename  passed in to tkExecPgm if (fTkExec is TRUE)
     109achTkExecPgmArguments   db CCHARGUMENTS dup (0) ; The arguments passed in to tkExecPgm if (fTkExec is TRUE)
     110fpachTkExecPgmEnv       dd 0            ; Far pointer to environment passed in to tkExecPgm.
     111                                        ; Valid at isLdrStateExecPgm time.
     112                                        ; NOTE! User data, don't touch it directly!
     113DATA16 ENDS
    52114
    53115
    54116CODE32 SEGMENT
    55 
    56117;;
    57 ;
     118; New implementation.
    58119; @returns   same as tkExecPgm: eax, edx and carry flag
    59120; @param     ax     Exec flag
     
    65126;            may modify later if this is a UNIX shellscript or
    66127;            a PE-file started by pe.exe.
    67 ; @status
     128; @status    completely implemented.
    68129; @author    knut st. osmundsen (knut.stange.osmundsen@pmsc.no)
    69 ; @remark
    70 ;
    71 ;   The buffer we are using is a C struct as follows.
    72 ;   struct Buffer
    73 ;   {
    74 ;       char szFilename[261];  /* offset 0   */
    75 ;       char achArg[1536-261]; /* offset 261 */
    76 ;   };
     130;
    77131;
    78132mytkExecPgm PROC FAR
    79 pBuffer     = dword ptr -04h
    80 SegBuffer   = -08h
    81 OffBuffer   = -0Ch
    82 cchFilename = dword ptr -10h
    83 cchArgs     = dword ptr -14h
    84 ;usExecFlag  = -18h
    85 ;SegFilename = -1ch
    86 ;OffFilename = -1eh
    87 ;SegEnv      = -20h
    88 ;OffEnv      = -22h
    89 ;SegArg      = -24h
    90 ;OffArg      = -26h
    91 
    92     ASSUME CS:CODE32, DS:NOTHING, SS:NOTHING
    93 ;    int     3
    94     push    ebp
    95     mov     ebp, esp
    96     lea     esp, [ebp + cchArgs]
    97 
    98     push    eax
    99     push    ecx
    100     push    ds
    101     push    es
    102     push    edi
    103 
    104     ; parameter validations
    105     mov     ax, ds                      ; pointer to filename
    106     cmp     ax, 4
    107     jb      mytkExecPgm_CalltkExecPgm_X1
    108 
    109     ;
    110     ; filename length
    111     ;
    112     mov     ax, ds
    113     mov     es, ax
    114     pushad
    115     push    es
    116     push    ds
    117     mov     bx, ds
    118     mov     di, dx                      ; es:di is now filename address (ds:dx).
    119     push    cs                          ; Problem calling far into the calltab segement.
    120     call    near ptr FLAT:_f_FuStrLen
    121     movzx   ecx, cx
    122     mov     [ebp+cchFilename], ecx
    123     pop     ds
    124     pop     es
    125     popad
    126     jc      mytkExecPgm_CalltkExecPgm_X1; If the FuStrLen call failed we bail out!
    127 
    128     ;
    129     ; if filename length is more that CCHMAXPATH then we don't do anything!.
    130     ;
    131     cmp     [ebp+cchFilename], 260
    132     jae     mytkExecPgm_CalltkExecPgm_X1; length >= 260
    133 
    134     ;
    135     ; args length
    136     ; Note: the arguments are a series of ASCIIZs ended by an empty string (ie. '\0').
    137     ;
    138     pop     edi
    139     push    edi
    140     xor     ecx, ecx
    141     cmp     di, 4                       ; The argument might me a invalid pointer...
    142     jb      mytkExecPgm_CalltkExecPgm_1
    143 
    144     pushad
    145     push    es
    146     push    ds
    147     mov     bx, di                      ;
    148     mov     di, si                      ; bx:di -> arguments
    149     push    cs                          ; Problem calling far into the calltab segement.
    150     call    near ptr FLAT:_f_FuStrLenZ
    151     movzx   ecx, cx
    152     mov     [ebp+cchArgs], ecx
    153     pop     ds
    154     pop     es
    155     popad
    156     jc      mytkExecPgm_CalltkExecPgm_X1
    157 
    158 mytkExecPgm_CalltkExecPgm_1:
    159     mov     ecx, [ebp+cchArgs]
    160     add     ecx, [ebp+cchFilename]      ; filename
    161     add     ecx, 3 + 260                ;  260 = new argument from a scrip file or something.
    162                                         ;    3 = two '\0's and a space after added argument.
    163     cmp     ecx, 1536                   ; 1536 = Buffersize.  FIXME! Define this!!!
    164     jae     mytkExecPgm_CalltkExecPgm_X1; jmp if argument + file + new file > buffer size
    165 
    166     ;
    167     ; Aquire a buffer
    168     ;
    169     call    AcquireBuffer
    170     or      eax, eax
    171     jz      mytkExecPgm_CalltkExecPgm_X1; Failed to get buffer.
    172     mov     [ebp+pBuffer], eax
    173 
    174     ;
    175     ; Get Segment and offset for the buffer
    176     ;
    177     call    QueryBufferSegmentOffset
    178     mov     cx, es
    179     mov     [ebp+OffBuffer], ax
    180     mov     [ebp+SegBuffer], es
    181     test    eax, 000570000h
    182     jnz     mytkExecPgm_CalltkExecPgm_X2
    183 
    184     ;
    185     ; Copy filename to pBuffer.
    186     ;
    187     pushad
    188     push    es
    189     push    ds
    190     mov     di, ax                      ; es:di  pBuffer
    191     mov     si, dx
    192     mov     bx, ds                      ; bx:si  Filename pointer (input ds:dx)
    193     mov     ecx, [ebp+cchFilename]
    194     push    cs                          ; Problem calling far into the calltab segement.
    195     call    near ptr FLAT:_f_FuBuff
    196     pop     ds
    197     pop     es
    198     popad
    199     jc      mytkExecPgm_CalltkExecPgm_X2
    200 
    201     ;
    202     ; Copy Args to pBuffer + 261
    203     ;
    204     ; stack: edi, es, ds, ecx, eax
    205     pop     edi
    206     push    edi
    207     add     eax, 261                    ; we'll use eax in the branch
    208     cmp     di, 4
    209     jb      mytkExecPgm_CalltkExecPgm_2
    210     pushad
    211     push    es
    212     push    ds
    213     mov     ecx, [ebp+cchArgs]
    214     mov     bx, di                      ; ds:si -> arguments
    215     mov     di, ax                      ; es:di -> buffer + 261
    216     push    cs                          ; Problem calling far into the calltab segement.
    217     call    near ptr FLAT:_f_FuBuff
    218     pop     ds
    219     pop     es
    220     popad
    221     jc      mytkExecPgm_CalltkExecPgm_X2
    222     jmp     mytkExecPgm_CalltkExecPgm_3
    223 
    224 mytkExecPgm_CalltkExecPgm_2:
    225     mov     word ptr es:[eax], 0        ; Terminate the empty string!
    226 
    227     ;
    228     ; Restore variables pushed on the stack
    229     ;
    230     ; stack: edi, es, ds, ecx, eax
    231 mytkExecPgm_CalltkExecPgm_3:
    232     pop     edi
    233     pop     es
    234     pop     ds
    235     pop     ecx
    236     pop     eax
    237 
    238     ;
    239     ; Set new input parameters (call _g_tkExecPgm)
    240     ;
    241     ; ds:dx is to become SegBuffer:OffBuffer
    242     ; di:si is to become SegBuffer:OffBuffer+261
    243     ;
    244     ; The some of the old values are stored on the stack (for the time being)
    245     push    ds
    246     push    edi
    247     push    esi
    248 
    249     mov     di, [ebp+SegBuffer]
    250     mov     ds, di
    251     mov     si, [ebp+OffBuffer]
    252     mov     dx, si                      ; ds:dx  SegBuffer:OffBuffer
    253     add     si, 261                     ; di:si  SegBuffer:OffBuffer+261
    254 
    255     ;
    256     ; Call _g_tkExecPgm
    257     ;
    258     push    cs                          ; Problem calling far into the calltab segement.
    259     call    near ptr FLAT:_g_tkExecPgm
    260     pushfd
    261 
    262     ;
    263     ; Release buffer
    264     ;
    265     push    eax
    266     mov     eax, [ebp + pBuffer]
    267     call    ReleaseBuffer
    268     mov     [ebp + pBuffer], 0
    269     pop     eax
    270 
    271     ;
    272     ; Return
    273     ;
    274     popfd
    275     pop     esi
    276     pop     edi
    277     pop     ds
    278     leave
    279     retf
    280 
    281 mytkExecPgm_CalltkExecPgm_X2:
    282     ;
    283     ; Release buffer
    284     ;
    285     mov     eax, [ebp + pBuffer]
    286     call    ReleaseBuffer
    287     mov     [ebp + pBuffer], 0
    288 
    289 mytkExecPgm_CalltkExecPgm_X1:
    290     pop     edi
    291     pop     es
    292     pop     ds
    293     pop     ecx
    294     pop     eax
    295 
    296 mytkExecPgm_CalltkExecPgm:
    297     push    cs
    298     call    near ptr FLAT:_g_tkExecPgm
    299     leave
    300     retf
    301 mytkExecPgm ENDP
    302 
    303 
    304 
    305 CODE32 ENDS
    306 
    307 if 0 ; alternate implementation.
    308 mytkExecPgm PROC FAR
    309 pBuffer     = dword ptr -04h
    310 SegBuffer   = -08h
    311 OffBuffer   = -0Ch
    312 cchFilename = -10h
    313 cchArgs     = -14h
    314 usExecFlag  = -18h
    315 SegFilename = -1ch
    316 OffFilename = -1eh
    317 SegEnv      = -20h
    318 OffEnv      = -22h
    319 SegArg      = -24h
    320 OffArg      = -26h
     133cchFilename = -4h
     134cchArgs     = -08h
     135usExecFlag  = -0ch
     136SegFilename = -10h
     137OffFilename = -12h
     138SegEnv      = -14h
     139OffEnv      = -16h
     140SegArg      = -18h
     141OffArg      = -1ah
    321142
    322143    ASSUME CS:CODE32, DS:NOTHING, SS:NOTHING
     
    325146    lea     esp, [ebp + OffArg]
    326147
    327     ; save input parameters
     148    ;
     149    ; Save input parameters
     150    ;
    328151    mov     [ebp + usExecFlag], ax
    329152    mov     ax, es
     
    332155    mov     [ebp + SegArg], di
    333156    mov     [ebp + OffArg], si
    334     mov     ax, ds
    335     mov     [ebp + SegFilename], ax
     157    mov     bx, ds
     158    mov     [ebp + SegFilename], bx
    336159    mov     [ebp + OffFilename], dx
    337160
    338     ; parameter validations
    339     cmp     ax, 4                       ; pointer to filename
    340     jb      mytkExecPgm_CalltkExecPgm_X1
    341 
    342     ;
    343     ; filename length
    344     ;
    345     mov     bx, ax
     161    ;
     162    ; Parameter validations - if any of these fail we'll just pass on to
     163    ; the real tkExecPgm without setting up any buffers stuff.
     164    ; 1) validate the file pointer.
     165    ; 2) validate the file name length < 260
     166    ; 3) validate that the arguments aren't larger than the buffer.
     167    ;
     168
     169    ; Validate filename pointer
     170    ;
     171    cmp     bx, 4                       ; pointer to filename
     172    jb      tkepgm_backout
     173
     174    ; Validate filename length
     175    ;
    346176    mov     di, dx                      ; bx:di is now filename address
    347177    push    cs                          ; Problem calling far into the calltab segement.
    348178    call    near ptr FLAT:_f_FuStrLen
    349     jc      mytkExecPgm_CalltkExecPgm_X1; If the FuStrLen call failed we bail out!
    350 
    351     ;
     179    jc      tkepgm_backout              ; If the FuStrLen call failed we bail out!
     180
    352181    ; if filename length is more that CCHMAXPATH then we don't do anything!.
    353     ;
    354     cmp     cx, 260
    355     jae     mytkExecPgm_CalltkExecPgm_X1; length >= 260
    356     mov     [ebp+cchFilename], cx
     182    cmp     cx, CCHMAXPATH
     183    jae     tkepgm_backout              ; length >= CCHMAXPATH
     184    mov     [ebp + cchFilename], cx
    357185
    358186    ;
     
    360188    ; Note: the arguments are a series of ASCIIZs ended by an empty string (ie. '\0').
    361189    ;
    362     mov     bx, [ebp+SegArg]
     190    xor     cx, cx                      ; Set length to zero.
     191    mov     bx, [ebp + SegArg]
    363192    cmp     bx, 4                       ; The argument might me an NULL pointer
    364     xor     cx, cx
    365     jb      mytkExecPgm_CalltkExecPgm_1
    366 
    367     mov     di, [ebp+OffArg]            ; bx:di -> arguments
     193    jb      tkepgm1
     194
     195    mov     di, [ebp + OffArg]          ; bx:di -> arguments
    368196    push    cs                          ; Problem calling far into the calltab segement.
    369197    call    near ptr FLAT:_f_FuStrLenZ
    370     mov     [ebp+cchArgs], cx
    371     jc      mytkExecPgm_CalltkExecPgm_X1
    372 
    373 mytkExecPgm_CalltkExecPgm_1:
    374     add     cx, [ebp+cchFilename]       ; filename length
    375     add     cx, 3 + 260                 ;  260 = new argument from a scrip file or something.
     198    jc      tkepgm_backout
     199
     200tkepgm1:
     201    mov     [ebp + cchArgs], cx
     202    add     cx, [ebp + cchFilename]     ; filename length
     203    add     cx, 3 + 260                 ;  260 = additional arguments from a script file or something.
    376204                                        ;    3 = two '\0's and a space after added argument.
    377     cmp     ecx, 1536                   ; 1536 = Buffersize.  FIXME! Define this!!!
    378     jae     mytkExecPgm_CalltkExecPgm_X1; jmp if argument + file + new file > buffer size
    379 
    380     ;
    381     ; Aquire a buffer
    382     ;
    383     call    AcquireBuffer
    384     mov     [ebp+pBuffer], eax
    385     or      eax, eax
    386     jz      mytkExecPgm_CalltkExecPgm_X1; Failed to get buffer.
    387 
    388     ;
    389     ; Get Segment and offset for the buffer
    390     ;
    391     call    QueryBufferSegmentOffset
    392     mov     cx, es
    393     mov     [ebp+OffBuffer], ax
    394     mov     [ebp+SegBuffer], es
    395     test    eax, 000570000h
    396     jnz     mytkExecPgm_CalltkExecPgm_X2
    397 
    398     ;
    399     ; Copy filename to pBuffer.
    400     ;
    401     mov     di, ax                      ; es:di  pBuffer
    402     mov     si, dx
    403     mov     bx, ds                      ; bx:si  Filename pointer (input ds:dx)
    404     mov     cx, [ebp+cchFilename]       ; cx = length of area to copy
     205    cmp     cx, CCHARGUMENTS            ; argument Buffersize.
     206    jae     tkepgm_backout              ; jmp if argument + file + additional arguments >= buffer size
     207
     208
     209    ;
     210    ; Aquire the OS/2 loader semaphore
     211    ;   Since parameters looks good, we're ready for getting the loader semaphore.
     212    ;   We use the loader semaphore to serialize access to the win32k.sys loader
     213    ;   subsystem.
     214    ;   Before we can get the loader semaphore, we'll need to set ds and es to
     215    ;   flat R0 context.
     216    ;   The loader semaphore is later requested by the original tkExecPgm so
     217    ;   this shouldn't break anything.
     218    ;
     219    mov     ax, seg FLAT:DATA32
     220    mov     ds, ax
     221    mov     es, ax
     222    ASSUME  DS:FLAT, ES:FLAT
     223
     224    mov     eax, pLdrSem                ; Get pointer to the loader semaphore.
     225    or      eax, eax                    ; Check if null. (paranoia)
     226    jz      tkepgm_backout              ; Fail if null.
     227
     228    push    0ffffffffh                  ; Wait indefinitely.
     229    push    eax                         ; Push LdrSem address (which is the handle).
     230    call    near ptr FLAT:_KSEMRequestMutex@8
     231    or      eax, eax                    ; Check if failed.
     232    jnz     tkepgm_backout              ; Backout on failure.
     233
     234
     235    ;
     236    ; From here on we won't backout to the tkepgm_backout lable but
     237    ; the tkepgm_backout2 lable. (This will restore the parameters
     238    ; and jump in at the call to tkExecPgm behind the Loader Sem.)
     239    ;
     240
     241
     242    ;
     243    ; Set global data:
     244    ;   Zeros pointer to exemodule to NULL (a bit paranoia).
     245    ;   Mark global data valid.
     246    ;   Store Environment pointer.
     247    ;   Set loader state.
     248    ;
     249    mov     pExeModule, 0               ; Sets the exemodule pointer to NULL.
     250    mov     fTkExecPgm, 1               ; Optimistic, mark the global data valid.
     251    mov     eax, [ebp + OffEnv]         ; Environment FAR pointer.
     252    mov     fpachTkExecPgmEnv, eax      ; Store the Environment pointer. This will
     253                                        ; later permit us to get the passed in
     254                                        ; environment in for ex. ldrOpenPath.
     255    mov     ulLDRState, 1               ; Set the loader state to LDRSTATE_TKEXECPGM!
     256    ASSUME  DS:NOTHING, ES:NOTHING
     257
     258
     259    ;
     260    ; Copy filename to achBuffer.
     261    ;
     262    mov     di, seg achTkExecPgmFilename
     263    mov     es, di
     264    mov     edi, offset achTkExecPgmFilename
     265                                        ; es:(e)di -> &achTkExecPgmFilename[0]
     266    mov     si, [ebp + OffFilename]
     267    mov     bx, [ebp + SegFilename]     ; bx:si  Filename pointer (input ds:dx)
     268    ASSUME DS:NOTHING
     269    mov     cx, [ebp + cchFilename]     ; cx = length of area to copy
    405270    push    cs                          ; Problem calling far into the calltab segement.
    406271    call    near ptr FLAT:_f_FuBuff
    407     jc      mytkExecPgm_CalltkExecPgm_X2
    408 
    409     ;
    410     ; Copy Args to pBuffer + 261
    411     ;
    412     mov     si, [ebp+SegArg]
    413     cmp     si, 4
    414     jb      mytkExecPgm_CalltkExecPgm_2
    415     mov     ds, si
    416     mov     si, [ebp+OffArg]            ; ds:si -> arguments
    417     mov     di, [ebp+SegBuffer]
     272    jc      tkepgm_backout2             ; In case of error back (quite unlikely).
     273
     274
     275    ;
     276    ; Copy Args to achTkExecPgmArguments
     277    ;
     278    mov     di, seg achTkExecPgmArguments
    418279    mov     es, di
    419     mov     di, [ebp+OffBuffer]
    420     add     di, 261                     ; es:di -> buffer + 261
    421     mov     cx, [ebp+cchArgs]           ; cx = length of area to copy
     280    mov     edi, offset achTkExecPgmArguments
     281                                        ; es:(e)di -> &achTkExecPgmArguments[0]
     282    mov     word ptr es:[edi], 0        ; Terminate the argument string in case
     283                                        ; there aren't any arguments.('\0\0')
     284                                        ; (We're just about to find that out.)
     285    mov     bx, [ebp + SegArg]
     286    cmp     bx, 4                       ; Is the argument pointer a null-pointer?
     287    jb      tkepgm_setup_parms          ; Skip copy if null pointer.
     288                                        ; Argument string is '\0\0'.
     289    mov     si, [ebp + OffArg]          ; bx:si -> arguments
     290    mov     cx, [ebp + cchArgs]         ; cx = length of area to copy
    422291    push    cs                          ; Problem calling far into the calltab segement.
    423292    call    near ptr FLAT:_f_FuBuff
    424     jc      mytkExecPgm_CalltkExecPgm_X2
    425     jmp     mytkExecPgm_CalltkExecPgm_3
    426 
    427 mytkExecPgm_CalltkExecPgm_2:
    428     mov     word ptr es:[eax], 0        ; Terminate the empty string!
    429 
    430     ;
    431     ; Set new input parameters (call _g_tkExecPgm)
    432     ;
    433     ; ds:dx is to become SegBuffer:OffBuffer
    434     ; di:si is to become SegBuffer:OffBuffer+261
    435     ;
    436 mytkExecPgm_CalltkExecPgm_3:
    437     mov     di, [ebp+SegBuffer]
    438     mov     ds, di
    439     mov     si, [ebp+OffBuffer]
    440     mov     dx, si                      ; ds:dx  SegBuffer:OffBuffer
    441     add     si, 261                     ; di:si  SegBuffer:OffBuffer+261
    442     mov     bx, [ebp+SegEnv]
     293    jc      tkepgm_backout2             ; In case of error back (quite unlikely).
     294
     295
     296    ;
     297    ; Setup new input parameters (call _g_tkExecPgm)
     298    ;
     299    ; ds:dx is to become &achTkExecPgmFilename[0]
     300    ; di:si is to become &achTkExecPgmArguments[0]
     301    ;
     302tkepgm_setup_parms:
     303    mov     ax, [ebp + usExecFlag]
     304    mov     di, seg achTkExecPgmArguments
     305    mov     esi, offset achTkExecPgmArguments ; di:si  &achTkExecPgmArguments[0]
     306    mov     ds, di                            ; Assumes same segment (which of course is true).
     307    mov     edx, offset achTkExecPgmFilename  ; ds:dx  &achTkExecPgmFilename[0]
     308    mov     bx, [ebp + SegEnv]
    443309    mov     es, bx
    444     mov     bx, [ebp+SegEnv]
     310    mov     bx, [ebp + OffEnv]                ; es:bx  Environment
     311
    445312
    446313    ;
    447314    ; Call _g_tkExecPgm
    448315    ;
     316tkepgm_callbehind:
    449317    push    cs                          ; Problem calling far into the calltab segement.
    450318    call    near ptr FLAT:_g_tkExecPgm
    451     pushfd
    452 
    453     ;
    454     ; Release buffer
    455     ;
    456     push    eax
    457     mov     eax, [ebp + pBuffer]
    458     call    ReleaseBuffer
    459     mov     [ebp + pBuffer], 0
    460     pop     eax
    461 
    462     ;
    463     ; Return
    464     ;
    465     push    [ebp + SegFilename]
     319    pushfd                              ; preserve flags
     320    push    eax                         ; preserve result.
     321    push    ecx                         ; preserve ecx just in case
     322    push    edx                         ; preserve edx just in case
     323    mov     ax, seg FLAT:DATA32
     324    mov     ds, ax
     325    mov     es, ax
     326    ASSUME  ds:FLAT, es:FLAT            ; both ds and es are now FLAT
     327
     328
     329    ;
     330    ; Clear loader semaphore?
     331    ; and clear loader state, current exe module and tkExecPgm global data flag.
     332    ;
     333    push    0                           ; Usage count variable.
     334    mov     eax, pulTKSSBase32          ; Get TKSSBase
     335    mov     eax, [eax]
     336    add     eax, esp                    ; Added TKSSBase to the usage count pointer
     337    push    eax                         ; Push address of usage count pointer.
     338    push    pLdrSem                     ; Push pointer to loader semaphore ( = handle).
     339    call    near ptr FLAT:_KSEMQueryMutex@8
     340    or      eax, eax                    ; Check return code. (1 = our / free; 0 = not our but take)
     341    pop     eax                         ; Pops usage count.
     342    je      tkepgm_callbehindret        ; jmp if not taken by us (rc=FALSE).
     343    or      eax, eax                    ; Check usage count.
     344    jz      tkepgm_callbehindret        ; jmp if 0 (=free).
     345    mov     ulLDRState, 0               ; Clears loaderstate. (LDRSTATE_UNKNOWN)
     346    mov     pExeModule, 0               ; Sets the exemodule pointer to NULL.
     347    mov     fTkExecPgm, 0               ; Marks global data invalid.
     348    call    near ptr FLAT:_LDRClearSem@0
     349
     350    ;
     351    ; Restore ds and es (probably unecessary but...) and Return
     352    ;
     353tkepgm_callbehindret:
     354    push    dword ptr [ebp + SegFilename]
    466355    pop     ds
    467     push    [ebp + SegEnv]
     356    push    dword ptr [ebp + SegEnv]
    468357    pop     es
    469     popfd
     358    pop     edx                         ; restore edx
     359    pop     ecx                         ; restore ecx
     360    pop     eax                         ; restore result.
     361    popfd                               ; restore flags
    470362    leave
    471363    retf
    472364
    473 mytkExecPgm_CalltkExecPgm_X2:
    474     ;
    475     ; Release buffer
    476     ;
    477     mov     eax, [ebp + pBuffer]
    478     call    ReleaseBuffer
    479     mov     [ebp + pBuffer], 0
    480 
    481 mytkExecPgm_CalltkExecPgm_X1:
    482     pop     ds
     365
     366;
     367; This is a backout were tkExecPgm probably will backout and we're
     368; allready behind the loader semaphore.
     369;
     370tkepgm_backout2:
     371    ;
     372    ; Set Flat context and invalidate buffer.
     373    ;
     374    mov     ax, seg FLAT:DATA32
     375    mov     ds, ax
     376    ASSUME ds:FLAT
     377    mov     fTkExecPgm, 0               ; Marks global data invalid.
     378
     379    ;
     380    ; Restore parameters. and call the original tkExecPgm
     381    ;
     382    mov     ax, [ebp + usExecFlag]
     383    mov     dx, [ebp + SegFilename]
     384    mov     ds, dx
     385    mov     dx, [ebp + OffFilename]
     386    mov     bx, [ebp + SegEnv]
     387    mov     es, bx
     388    mov     bx, [ebp + OffEnv]
     389    mov     di, [ebp + SegArg]
     390    mov     si, [ebp + OffArg]
     391    jmp     tkepgm_callbehind
     392
     393
     394;
     395; This is a backout were tkExecPgm too is exspected to back out.
     396;
     397tkepgm_backout:
     398    ;
     399    ; Restore parameters. and call the original tkExecPgm
     400    ;
     401    mov     ax, [ebp + usExecFlag]
     402    mov     dx, [ebp + SegFilename]
     403    mov     ds, dx
     404    mov     dx, [ebp + OffFilename]
     405    mov     bx, [ebp + SegEnv]
     406    mov     es, bx
     407    mov     bx, [ebp + OffEnv]
     408    mov     di, [ebp + SegArg]
     409    mov     si, [ebp + OffArg]
    483410
    484411mytkExecPgm_CalltkExecPgm:
    485     push    cs
     412    push    cs                          ; Problem calling far into the calltab segement.
    486413    call    near ptr FLAT:_g_tkExecPgm
    487414    leave
     
    489416mytkExecPgm ENDP
    490417
     418
     419
     420;;
     421; Function which copies the environment data passed into tkExecPgm
     422; to a given buffer.
     423; @cproto    ULONG _Optlink tkExecPgmCopyEnv(char *pachBuffer, unsigned cchBuffer);
     424; @returns   OS/2 return code - NO_ERROR on success.
     425;            0 on error or no data.
     426; @param     pachBuffer     Pointer to buffer which the environment data is
     427;                           to be copied to.
     428;                           (eax)
     429; @param     cchBuffer      Size of the buffer.
     430;                           (edx)
     431; @uses      eax, edx, ecx
     432; @sketch
     433; @status
     434; @author    knut st. osmundsen (knut.stange.osmundsen@pmsc.no)
     435; @remark
     436tkExecPgmCopyEnv PROC NEAR
     437cchEnv  = -04h
     438    ASSUME ds:FLAT, es:FLAT, ss:NOTHING
     439    push    ebp
     440    mov     ebp, esp
     441    lea     esp, [ebp + cchEnv]
     442
     443    push    ebx
     444    mov     ebx, eax                    ; ebx now holds the buffer pointer.
     445
     446    ;
     447    ; Call tkExecPgmEnvLength to get length and check that pointer is valid.
     448    ;
     449    push    edx
     450    call    tkExecPgmEnvLength
     451    pop     ecx                         ; ecx now holds the buffer length.
     452
     453    cmp     eax, 0
     454    ja      tkepce_ok1
     455    mov     eax, 232                    ; ERROR_NO_DATA
     456    jmp     tkepce_ret                  ; Fail if no data or any other error.
     457
     458tkepce_ok1:
     459    cmp     eax, ecx                    ; (ecx is the buffer size.)
     460    jbe     tkepce_ok2                  ; Fail if buffer too small.
     461    mov     eax, 111                    ; ERROR_BUFFER_OVERFLOW
     462    jmp     tkepce_ret
     463
     464tkepce_ok2:
     465    mov     [ebp + cchEnv], eax         ; Save environment length.
     466
     467
     468    ;
     469    ; Thunk the environment 16-bit far pointer to 32-bit.
     470    ;
     471    mov     eax, fpachTkExecPgmEnv
     472    call    D32Hlp_VirtToLin
     473    or      eax, eax                    ; check if thunking were successful.
     474    jnz     tkepce_ok3                  ; Jump if success.
     475    mov     eax, edx                    ; A special feature for D32Hlp_VirtToLin is that edx
     476                                        ; have the error code in case on failure.
     477    jmp tkepce_ret
     478
     479tkepce_ok3:
     480    ;
     481    ; Copy the environment data.
     482    ;
     483    push    3                           ; Fatal if error.
     484    push    dword ptr [ebp + cchEnv]    ; Number of bytes to copy
     485    push    eax                         ; Source buffer pointer. (user)
     486    push    ebx                         ; Target buffer pointer.
     487    call    near ptr FLAT:_TKFuBuff@16
     488
     489tkepce_ret:
     490    pop     ebx
     491    leave
     492    ret
     493tkExecPgmCopyEnv ENDP
     494
     495
     496
     497;;
     498; This function gets the length of the tkExecPgm environment data.
     499; @cproto    ULONG _Optlink tkExecPgmEnvLength(void);
     500; @returns   Environment data length in bytes.
     501; @uses      eax, edx, ecx
     502; @sketch
     503; @status
     504; @author    knut st. osmundsen (knut.stange.osmundsen@pmsc.no)
     505; @remark
     506tkExecPgmEnvLength PROC NEAR
     507    ASSUME ds:FLAT, es:FLAT, ss:NOTHING
     508    push    ebp
     509    mov     ebp, esp
     510
     511    ;
     512    ; Push register which needs to be presered.
     513    ;
     514    push    es
     515    push    ds
     516    push    esi
     517    push    edi
     518    push    ebx
     519
     520
     521    ;
     522    ; Check that the data is valid.
     523    ;
     524    cmp     ulLDRState, 1               ; LDRSTATE_TKEXECPGM
     525    jnz     tkepel_err_ret
     526
     527
     528    ;
     529    ; Check if the environment pointer is NULL.
     530    ;
     531    mov     ebx, fpachTkExecPgmEnv
     532    ror     ebx, 16
     533    cmp     bx, 4
     534    jb      tkepel_err_ret
     535
     536
     537tkepel1:
     538    ;
     539    ; Get the environment length
     540    ;
     541    mov     edi, ebx
     542    ror     edi, 16                     ; bx:di -> [fpachTkExecPgmEnv]
     543    xor     ecx, ecx
     544    push    cs                          ; Problem calling far into the calltab segement.
     545    call    near ptr FLAT:_f_FuStrLenZ
     546    jc      tkepel_err_ret
     547    movzx   eax, cx
     548    jmp     tkepel_ret
     549
     550
     551; Failure
     552tkepel_err_ret:
     553    xor     eax, eax
     554
     555
     556; Return
     557tkepel_ret:
     558    pop     ebx                         ; restore registers
     559    pop     edi
     560    pop     esi
     561    pop     ds
     562    pop     es
     563    leave
     564    ret
     565tkExecPgmEnvLength ENDP
     566
     567
     568
     569
     570
    491571CODE32 ENDS
    492 endif
    493572
    494573
Note: See TracChangeset for help on using the changeset viewer.