Changeset 3542


Ignore:
Timestamp:
Mar 21, 2019, 7:17:58 PM (6 years ago)
Author:
Andreas Schnellbacher
Message:
  • Improved and harmonized error message output.
  • Harmonized code.
  • Minor changes.
Location:
trunk/src/netlabs/bin
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • TabularUnified trunk/src/netlabs/bin/assocs.erx

    r3541 r3542  
    252252   rest = UserSubKeys
    253253   DO FOREVER
    254       PARSE VAR rest SubKey'00'x rest
     254      PARSE VAR rest SubKey'00'''rest
    255255      IF SubKey = '' THEN
    256256         LEAVE
     
    308308         /* Get first path segment */
    309309         PARSE VAR SubKey SubKey'\'.
     310         PARSE VAR SubKey SubKey '=' .
    310311
    311312         /* Check item for integer > 0 as group id */
  • TabularUnified trunk/src/netlabs/bin/colors.erx

    r3541 r3542  
    356356   rest = UserSubKeys
    357357   DO FOREVER
    358       PARSE VAR rest SubKey'00'x rest
     358      PARSE VAR rest SubKey'00'x''rest
    359359      IF SubKey = '' THEN
    360360         LEAVE
     
    412412         /* Get first path segment */
    413413         PARSE VAR SubKey SubKey'\'.
     414         PARSE VAR SubKey SubKey '=' .
    414415
    415416         /* Check item for integer > 0 as group id */
     
    957958         Stem.0 = 0
    958959         DO FOREVER
    959             PARSE VAR rest SubKey'00'x rest
     960            PARSE VAR rest SubKey'00'x''rest
    960961            IF SubKey = '' THEN
    961962               LEAVE
  • TabularUnified trunk/src/netlabs/bin/newsamewindow.erx

    r2991 r3542  
    4242****************************************************************************/
    4343
     44IF ADDRESS() <> 'EPM' THEN
     45   '@ECHO OFF'
     46
    4447/* ----------------- Standard ERX initialization follows ----------------- */
    4548SIGNAL ON HALT NAME Halt
     
    5659Redirection = '>NUL 2>&1'
    5760PARSE SOURCE . . ThisFile
    58 GlobalVars = 'env TRUE FALSE Redirection ERROR. ThisFile'
     61GlobalVars = 'env TRUE FALSE Redirection ERROR. ThisFile ThisName'
    5962GlobalVars = GlobalVars 'ErrorQueueName ErrorMessage'
    6063
    61 /* some OS/2 Error codes */
     64/* Some OS/2 error codes */
    6265ERROR.NO_ERROR           =   0
    6366ERROR.INVALID_FUNCTION   =   1
     
    8083ErrorMessage   = ''
    8184
     85PARSE SOURCE . . ThisFile
     86lp = LASTPOS( '\', ThisFile)
     87ThisDir = LEFT( ThisFile, lp - 1)
     88ThisName = SUBSTR( ThisFile, lp + 1)
     89
    8290CALL RxFuncAdd 'SysLoadFuncs', 'RexxUtil', 'SysLoadFuncs'
    8391CALL SysLoadFuncs
    8492/* ----------------- Standard ERX initialization ends -------------------- */
     93
     94/* Extend the environment, if not already */
     95next = VALUE( 'NEPMD_NAME',, env)
     96IF next = '' THEN
     97   'CALL' ThisDir'\..\..\netlabs\bin\EPMENV'
    8598
    8699/* ------------- Configuration ---------------- */
     
    98111/* -------------------------------------------- */
    99112
    100 GlobalVars = GlobalVars 'Ini. Key. Title.'
     113GlobalVars = GlobalVars 'Ini. Key. Obj. fInit Title.'
    101114
    102115CALL RxFuncAdd 'WPToolsLoadFuncs', 'WPTOOLS', 'WPToolsLoadFuncs'
     
    104117
    105118DO 1
     119   fInit = 0
    106120
    107121   PARSE ARG Args
     
    119133      rc = ERROR.INVALID_PARAMETER
    120134      ErrorMessage = 'Error: No action specified. Parameter' ||,
    121          ' for NEWSAMEWINDOW.ERX is missing.'
     135         ' for 'TRANSLATE( ThisName)' is missing.'
    122136      LEAVE
    123137   END
     
    127141   Obj.0 = 0
    128142
    129    /* Get user sub keys from RegContainer */
    130    UserSubKeys = ''
    131    next = SysIni( Ini._Filename, Ini._RegContainer, Key._MainPath)
    132    next = STRIP( next, 'T', '00'x)
    133    IF \(next = '' | next = 'ERROR:') THEN
    134       UserSubKeys = next
    135 
    136    /* Add user objects to Obj. */
    137    rest = UserSubKeys
    138    DO FOREVER
    139       PARSE VAR rest SubKey'00'x''rest
    140       IF SubKey = '' THEN
    141          LEAVE
    142 
    143       /* Check items for integer > 0 */
    144       IF VERIFY( SubKey, '0123456789') <> 0 THEN
    145          ITERATE
    146       IF SubKey = 0 THEN
    147          ITERATE
    148 
    149       /* Query key */
    150       next = SysIni( Ini._Filename, Ini._RegKeys, Key._MainPath'\'SubKey)
    151       next = STRIP( next, 'T', '00'x)
    152       IF \(next = '' | next = 'ERROR:') THEN
    153       DO
    154          /* Add next to Obj. */
    155          n = Obj.0 + 1
    156          Obj.n = next
    157          Obj.0 = n
    158       END
    159    END
    160 
    161    IF Obj.0 = 0 THEN
    162    DO
    163       /* Get all default keys */
    164       DefaultKey.  = ''
    165       DefaultKey.0 = ''
    166       next = SysIni( Ini._Filename, Ini._RegDefaults, 'ALL:', 'DefaultKey.')
    167       SearchKey = Key._MainPath'\'
    168       SearchLen = LENGTH( SearchKey)
    169       DO k = 1 TO DefaultKey.0
    170          /* Find keys that start with SearchKey */
    171          IF LEFT( DefaultKey.k, SearchLen) = SearchKey THEN
    172          DO
    173             /* Get reamaining key string */
    174             SubKey = SUBSTR( DefaultKey.k, SearchLen + 1)
    175             /* Get first path segment */
    176             PARSE VAR SubKey SubKey'\'.
    177 
    178             /* Check items for integer > 0 */
    179             IF VERIFY( SubKey, '0123456789') <> 0 THEN
    180                ITERATE
    181             IF SubKey = 0 THEN
    182                ITERATE
    183 
    184             /* Query key */
    185             next = SysIni( Ini._Filename, Ini._RegDefaults, DefaultKey.k)
    186             next = STRIP( next, 'T', '00'x)
    187             IF \(next = '' | next = 'ERROR:') THEN
    188             DO
    189                /* Add next to Obj. */
    190                n = Obj.0 + 1
    191                Obj.n = next
    192                Obj.0 = n
    193             END
    194          END
    195       END
    196    END
     143   /* Get all user keys */
     144   CALL GetUserObjects
     145
     146   /* Get all default keys */
     147   /* This fills also the DefaultKey. array */
     148   CALL GetDefaultObjects
    197149
    198150   /* Get special object */
     
    202154   DO
    203155      /* No user key exists in RegKeys, query RegDefaults */
    204       next = SysIni( Ini._Filename, Ini._RegDefaults, Key._MainPath'\'Key._Special)
    205       next = STRIP( next, 'T', '00'x)
     156      IF fInit THEN
     157         next = FindTextIniVal( 'DefaultKey.', Key._MainPath'\'Key._Special)
     158      ELSE
     159      DO
     160         next = SysIni( Ini._Filename, Ini._RegDefaults, Key._MainPath'\'Key._Special)
     161         next = STRIP( next, 'T', '00'x)
     162      END
    206163      IF (next = '' | next = 'ERROR:') THEN
    207164      DO
     
    214171
    215172   /* Query current setting from first object */
    216    Obj = Obj.1
    217    rcx = WPToolsQueryObject( Obj, 'Class', 'Title', 'Setup', 'Location')
     173   Object = Obj.1
     174   rcx = WPToolsQueryObject( Object, 'Class', 'Title', 'Setup', 'Location')
    218175   IF (rcx = 1) THEN
    219176      fOldR =CheckR( Setup)
     
    221178   DO
    222179      rc = ERROR.FILE_NOT_FOUND
    223       ErrorMessage = 'Error: Setup string couldn''t be queried from 'Obj'.'
     180      ErrorMessage = 'Error: Setup string couldn''t be queried from 'Object'.'
    224181      LEAVE
    225182   END
     
    257214END
    258215
    259 CALL SayErrorMessage
     216/* ErrorMessage */
     217DO 1
     218   IF ErrorMessage = '' THEN
     219      LEAVE
     220   /* Prepend 'Error 'rc ... if ErrorMessage doesn't contain the word 'Error' */
     221   IF POS( 'ERROR', TRANSLATE( ErrorMessage)) = 0 THEN
     222      ErrorMessage = 'Error 'rc' running 'ThisFile': 'ErrorMessage
     223   CALL SayErrorMessage
     224END
    260225EXIT( rc)
     226
     227/* ----------------------------------------------------------------------- */
     228GetUserObjects: PROCEDURE EXPOSE (GlobalVars)
     229
     230   rc = ERROR.NO_ERROR
     231
     232   /* Get user sub keys from RegContainer */
     233   UserSubKeys = ''
     234   next = SysIni( Ini._Filename, Ini._RegContainer, Key._MainPath)
     235   next = STRIP( next, 'T', '00'x)
     236   IF next <> '' & next <> 'ERROR:' THEN
     237      UserSubKeys = next
     238
     239   /* Add user objects to Obj. */
     240   rest = UserSubKeys
     241   DO FOREVER
     242      PARSE VAR rest SubKey'00'x''rest
     243      IF SubKey = '' THEN
     244         LEAVE
     245
     246      /* Check item for integer > 0 as group id */
     247      IF VERIFY( SubKey, '0123456789') <> 0 THEN
     248         ITERATE
     249      IF SubKey = 0 THEN
     250         ITERATE
     251
     252      /* Query key */
     253      next = SysIni( Ini._Filename, Ini._RegKeys, Key._MainPath'\'SubKey)
     254      next = STRIP( next, 'T', '00'x)
     255      IF next <> '' & next <> 'ERROR:' THEN
     256      DO
     257         /* Add next to Obj. */
     258         n = Obj.0 + 1
     259         Obj.n = next
     260         Obj.0 = n
     261      END
     262   END
     263
     264   RETURN( rc)
     265
     266/* ----------------------------------------------------------------------- */
     267GetDefaultObjects: PROCEDURE EXPOSE (GlobalVars)
     268
     269   rc = ERROR.NO_ERROR
     270
     271   /* Get all default keys */
     272   DefaultKey.  = ''
     273   DefaultKey.0 = 0
     274
     275   next = SysIni( Ini._Filename, Ini._RegDefaults, 'ALL:', 'DefaultKey.')
     276   IF next = 'ERROR:' THEN
     277       fInit = 1
     278
     279   IF fInit THEN
     280      next = TextIniToStem( File._DefaultsCfg, 'ALL:', 'ALL:', 'DefaultKey.')
     281
     282   SearchKey = Key._MainPath'\'
     283   SearchLen = LENGTH( SearchKey)
     284   DO k = 1 TO DefaultKey.0
     285      /* Find keys that start with SearchKey */
     286      IF LEFT( DefaultKey.k, SearchLen) = SearchKey THEN
     287      DO
     288         /* Get reamaining key string */
     289         SubKey = SUBSTR( DefaultKey.k, SearchLen + 1)
     290         /* Get first path segment */
     291         PARSE VAR SubKey SubKey'\'.
     292         PARSE VAR SubKey SubKey '=' .
     293
     294         /* Check item for integer > 0 as group id */
     295         IF VERIFY( SubKey, '0123456789') <> 0 THEN
     296            ITERATE
     297         IF SubKey = 0 THEN
     298            ITERATE
     299
     300         /* Query key */
     301         IF fInit THEN
     302         DO
     303            PARSE VAR DefaultKey.k . '=' next
     304            next = STRIP( next)
     305         END
     306         ELSE
     307         DO
     308            next = SysIni( Ini._Filename, Ini._RegDefaults, DefaultKey.k)
     309            next = STRIP( next, 'T', '00'x)
     310         END
     311         IF next <> '' & next <> 'ERROR:' THEN
     312         DO
     313            /* Add next to Obj. */
     314            n = Obj.0 + 1
     315            Obj.n = next
     316            Obj.0 = n
     317         END
     318      END
     319   END
     320
     321   RETURN( rc)
    261322
    262323/* ----------------------------------------------------------------------- */
     
    326387   RETURN( rcx)
    327388
     389/* ----------------------------------------------------------------------- */
     390/* Syntax:                                                                 */
     391/*    rc = TextIniToStem( File, ApplicationList, Key, Stem)                */
     392/* Adds key = value lines of a text ini file to a specified stem var. The  */
     393/* search can be reduced to a list of ini applications or to a key. If no  */
     394/* Application list is specified, 'ALL:' applications are listed. If no    */
     395/* key is specified, 'ALL:' keys are listed. The number of items is        */
     396/* written to Stem''0.                                                     */
     397/* Different from SysIni for OS/2 ini files, TextIniToStem always lists    */
     398/* entire lines. Theerefore, in most cases, that list has to be parsed     */
     399/* to key and value pairs.                                                 */
     400/* Example:                                                                */
     401/*    rcx = TextIniToStem( 'defaults.cfg', 'ALL:', 'ALL:', 'DefaultKey.')  */
     402/*    DO n = 1 TO DefaultKey.0                                             */
     403/*       SAY DefaultKey.n                                                  */
     404/*    END                                                                  */
     405/* This is used here for DEFAULTS.CFG parsing */
     406TextIniToStem:
     407/*
     408Adding the value of StemVar to the expose list is not possible. Therefore
     409this function must be global.
     410*/
     411   rc = ERROR.NO_ERROR
     412   PARSE ARG File, ApplicationList, Key, StemVar
     413
     414   Entry = ''
     415   IF ApplicationList  = '' THEN
     416      ApplicationList  = 'ALL:'
     417   Application = ''
     418   IF Key = '' THEN
     419      Key = 'ALL:'
     420
     421   IF RIGHT( StemVar, 1) <> '.' THEN
     422      StemVar = StemVar'.'
     423   CALL VALUE StemVar, ''
     424   CALL VALUE StemVar''0, 0
     425
     426   next = STREAM( File, 'C', 'OPEN READ')
     427   DO WHILE CHARS( File) > 0
     428      line = LINEIN( File)
     429      SELECT
     430         WHEN LEFT( line, 1) = ';' THEN
     431            NOP
     432         WHEN STRIP( line) = '' THEN
     433            NOP
     434         WHEN LEFT( line, 1) = '[' THEN
     435         DO
     436            p2 = POS( ']', line)
     437            IF p2 > 0 THEN
     438            DO
     439               nextApplication = SUBSTR( line, 2, p2 - 2)
     440               IF WORDPOS( nextApplication, ApplicationList) > 0 | ApplicationList = 'ALL:' THEN
     441                  Application = nextApplication
     442               ELSE
     443                  Application = ''  /* nextApplication is other, reset Application */
     444            END
     445         END
     446      OTHERWISE
     447         PARSE VALUE line WITH nextKey '=' nextEntry
     448         /* it must be a 'Key = Entry' line */
     449         nextKey   = STRIP( nextKey)
     450         nextEntry = STRIP( nextEntry)
     451         IF ApplicationList <> 'ALL:' & Application = '' THEN
     452            ITERATE
     453         IF nextKey = '' THEN
     454            ITERATE
     455         IF Key = 'ALL:' | nextKey = Key THEN
     456         DO
     457            s = VALUE( StemVar''0) + 1
     458            CALL VALUE StemVar''0, s
     459            CALL VALUE StemVar''s, nextKey'='nextEntry
     460         END
     461      END
     462   END
     463   rc = STREAM( File, 'C', 'CLOSE')
     464
     465   RETURN( rc)
     466
     467/* ----------------------------------------------------------------------- */
     468/* Requires a previous call to TextIniToStem. Returns Val for a specified  */
     469/* Key.                                                                    */
     470FindTextIniVal: PROCEDURE EXPOSE (GlobalVars)
     471   Val = ''
     472   PARSE ARG StemVar, Key
     473   IF RIGHT( StemVar, 1) <> '.' THEN
     474      StemVar = StemVar'.'
     475
     476   DO s = 1 TO VALUE( StemVar''0)
     477      ThisLine = VALUE( StemVar''s)
     478      PARSE VALUE ThisLine WITH ThisKey '=' ThisVal
     479      ThisKey = STRIP( ThisKey)
     480      ThisVal = STRIP( ThisVal)
     481      IF ThisKey = Key THEN
     482      DO
     483         Val = ThisVal
     484         LEAVE
     485      END
     486   END
     487   RETURN( Val)
     488
    328489/* --------------------- Standard ERX macros follow ---------------------- */
    329490
     
    342503
    343504/* ----------------------------------------------------------------------- */
     505/* For PmPrintf output, use CALL SayDegug '...' When being called from an  */
     506/* environment outside of EPM, the message text is processed by a SAY      */
     507/* statement instead. */
     508SayDebug: PROCEDURE EXPOSE (GlobalVars)
     509   PARSE ARG Message
     510
     511   SELECT
     512      WHEN ADDRESS() = 'EPM' THEN
     513         'dprintf' Message
     514   OTHERWISE
     515      SAY Message
     516   END
     517
     518   RETURN( '')
     519
     520/* ----------------------------------------------------------------------- */
    344521SayErrorMessage: PROCEDURE EXPOSE (GlobalVars)
    345522
     
    358535      WHEN ADDRESS() = 'EPM' THEN
    359536      DO
    360          /*'sayerror' ErrorMessage*/
    361          ThisFileName = SUBSTR( ThisFile, LASTPOS( '\', ThisFile) + 1)
    362          rcx = RxMessageBox( ErrorMessage, TRANSLATE( ThisFileName),,
     537         'sayerror' ErrorMessage
     538         rcx = RxMessageBox( ErrorMessage, TRANSLATE( ThisName),,
    363539            'OK', 'ERROR')
    364540      END
  • TabularUnified trunk/src/netlabs/bin/omitopenbox.erx

    r2991 r3542  
    3636****************************************************************************/
    3737
     38IF ADDRESS() <> 'EPM' THEN
     39   '@ECHO OFF'
     40
    3841/* ----------------- Standard ERX initialization follows ----------------- */
    3942SIGNAL ON HALT NAME Halt
     
    5053Redirection = '>NUL 2>&1'
    5154PARSE SOURCE . . ThisFile
    52 GlobalVars = 'env TRUE FALSE Redirection ERROR. ThisFile'
     55GlobalVars = 'env TRUE FALSE Redirection ERROR. ThisFile ThisName'
    5356GlobalVars = GlobalVars 'ErrorQueueName ErrorMessage'
    5457
    55 /* some OS/2 Error codes */
     58/* Some OS/2 error codes */
    5659ERROR.NO_ERROR           =   0
    5760ERROR.INVALID_FUNCTION   =   1
     
    7477ErrorMessage   = ''
    7578
     79PARSE SOURCE . . ThisFile
     80lp = LASTPOS( '\', ThisFile)
     81ThisDir = LEFT( ThisFile, lp - 1)
     82ThisName = SUBSTR( ThisFile, lp + 1)
     83
    7684CALL RxFuncAdd 'SysLoadFuncs', 'RexxUtil', 'SysLoadFuncs'
    7785CALL SysLoadFuncs
    7886/* ----------------- Standard ERX initialization ends -------------------- */
     87
     88/* Extend the environment, if not already */
     89next = VALUE( 'NEPMD_NAME',, env)
     90IF next = '' THEN
     91   'CALL' ThisDir'\..\..\netlabs\bin\EPMENV'
    7992
    8093/* ------------- Configuration ---------------- */
     
    87100/* -------------------------------------------- */
    88101
    89 GlobalVars = GlobalVars 'Ini. Key.'
     102GlobalVars = GlobalVars 'Ini. Key. Obj. fInit'
    90103
    91104CALL RxFuncAdd 'WPToolsLoadFuncs', 'WPTOOLS', 'WPToolsLoadFuncs'
     
    93106
    94107DO 1
     108   fInit = 0
    95109
    96110   PARSE ARG Args
     
    108122      rc = ERROR.INVALID_PARAMETER
    109123      ErrorMessage = 'Error: No action specified. Parameter' ||,
    110          ' for OMITOPENBOX.ERX is missing.'
     124         ' for 'TRANSLATE( ThisName)' is missing.'
    111125      LEAVE
    112126   END
     
    116130   Obj.0 = 0
    117131
    118    /* Get user sub keys from RegContainer */
    119    UserSubKeys = ''
    120    next = SysIni( Ini._Filename, Ini._RegContainer, Key._MainPath)
    121    next = STRIP( next, 'T', '00'x)
    122    IF \(next = '' | next = 'ERROR:') THEN
    123       UserSubKeys = next
    124 
    125    /* Add user objects to Obj. */
    126    rest = UserSubKeys
    127    DO FOREVER
    128       PARSE VAR rest SubKey'00'x''rest
    129       IF SubKey = '' THEN
    130          LEAVE
    131 
    132       /* Check items for integer > 0 */
    133       IF VERIFY( SubKey, '0123456789') <> 0 THEN
    134          ITERATE
    135       IF SubKey = 0 THEN
    136          ITERATE
    137 
    138       /* Query key */
    139       next = SysIni( Ini._Filename, Ini._RegKeys, Key._MainPath'\'SubKey)
    140       next = STRIP( next, 'T', '00'x)
    141       IF \(next = '' | next = 'ERROR:') THEN
    142       DO
    143          /* Add next to Obj. */
    144          n = Obj.0 + 1
    145          Obj.n = next
    146          Obj.0 = n
    147       END
    148    END
    149 
    150    IF Obj.0 = 0 THEN
    151    DO
    152       /* Get all default keys */
    153       DefaultKey.  = ''
    154       DefaultKey.0 = ''
    155       next = SysIni( Ini._Filename, Ini._RegDefaults, 'ALL:', 'DefaultKey.')
    156       SearchKey = Key._MainPath'\'
    157       SearchLen = LENGTH( SearchKey)
    158       DO k = 1 TO DefaultKey.0
    159          /* Find keys that start with SearchKey */
    160          IF LEFT( DefaultKey.k, SearchLen) = SearchKey THEN
    161          DO
    162             /* Get reamaining key string */
    163             SubKey = SUBSTR( DefaultKey.k, SearchLen + 1)
    164             /* Get first path segment */
    165             PARSE VAR SubKey SubKey'\'.
    166 
    167             /* Check items for integer > 0 */
    168             IF VERIFY( SubKey, '0123456789') <> 0 THEN
    169                ITERATE
    170             IF SubKey = 0 THEN
    171                ITERATE
    172 
    173             /* Query key */
    174             next = SysIni( Ini._Filename, Ini._RegDefaults, DefaultKey.k)
    175             next = STRIP( next, 'T', '00'x)
    176             IF \(next = '' | next = 'ERROR:') THEN
    177             DO
    178                /* Add next to Obj. */
    179                n = Obj.0 + 1
    180                Obj.n = next
    181                Obj.0 = n
    182             END
    183          END
    184       END
    185    END
     132   /* Get all user keys */
     133   CALL GetUserObjects
     134
     135   /* Get all default keys */
     136   /* This fills also the DefaultKey. array */
     137   CALL GetDefaultObjects
    186138
    187139   /* Query current setting from first object */
    188    Obj = Obj.1
    189    rcx = WPToolsQueryObject( Obj, 'Class', 'Title', 'Setup', 'Location')
     140   Object = Obj.1
     141   rcx = WPToolsQueryObject( Object, 'Class', 'Title', 'Setup', 'Location')
    190142   IF (rcx = 1) THEN
    191143      fOldO = CheckO( Setup)
    192144   ELSE
    193145   DO
    194       ErrorMessage = 'Error: Setup string couldn''t be queried from 'Obj'.'
     146      ErrorMessage = 'Error: Setup string couldn''t be queried from 'Object'.'
    195147      rc = ERROR.FILE_NOT_FOUND
    196148      LEAVE
     
    225177END
    226178
    227 CALL SayErrorMessage
     179/* ErrorMessage */
     180DO 1
     181   IF ErrorMessage = '' THEN
     182      LEAVE
     183   /* Prepend 'Error 'rc ... if ErrorMessage doesn't contain the word 'Error' */
     184   IF POS( 'ERROR', TRANSLATE( ErrorMessage)) = 0 THEN
     185      ErrorMessage = 'Error 'rc' running 'ThisFile': 'ErrorMessage
     186   CALL SayErrorMessage
     187END
    228188EXIT( rc)
     189
     190/* ----------------------------------------------------------------------- */
     191GetUserObjects: PROCEDURE EXPOSE (GlobalVars)
     192
     193   rc = ERROR.NO_ERROR
     194
     195   /* Get user sub keys from RegContainer */
     196   UserSubKeys = ''
     197   next = SysIni( Ini._Filename, Ini._RegContainer, Key._MainPath)
     198   next = STRIP( next, 'T', '00'x)
     199   IF next <> '' & next <> 'ERROR:' THEN
     200      UserSubKeys = next
     201
     202   /* Add user objects to Obj. */
     203   rest = UserSubKeys
     204   DO FOREVER
     205      PARSE VAR rest SubKey'00'x''rest
     206      IF SubKey = '' THEN
     207         LEAVE
     208
     209      /* Check item for integer > 0 as group id */
     210      IF VERIFY( SubKey, '0123456789') <> 0 THEN
     211         ITERATE
     212      IF SubKey = 0 THEN
     213         ITERATE
     214
     215      /* Query key */
     216      next = SysIni( Ini._Filename, Ini._RegKeys, Key._MainPath'\'SubKey)
     217      next = STRIP( next, 'T', '00'x)
     218      IF next <> '' & next <> 'ERROR:' THEN
     219      DO
     220         /* Add next to Obj. */
     221         n = Obj.0 + 1
     222         Obj.n = next
     223         Obj.0 = n
     224      END
     225   END
     226
     227   RETURN( rc)
     228
     229/* ----------------------------------------------------------------------- */
     230GetDefaultObjects: PROCEDURE EXPOSE (GlobalVars)
     231
     232   rc = ERROR.NO_ERROR
     233
     234   /* Get all default keys */
     235   DefaultKey.  = ''
     236   DefaultKey.0 = 0
     237
     238   next = SysIni( Ini._Filename, Ini._RegDefaults, 'ALL:', 'DefaultKey.')
     239   IF next = 'ERROR:' THEN
     240       fInit = 1
     241
     242   IF fInit THEN
     243      next = TextIniToStem( File._DefaultsCfg, 'ALL:', 'ALL:', 'DefaultKey.')
     244
     245   SearchKey = Key._MainPath'\'
     246   SearchLen = LENGTH( SearchKey)
     247   DO k = 1 TO DefaultKey.0
     248      /* Find keys that start with SearchKey */
     249      IF LEFT( DefaultKey.k, SearchLen) = SearchKey THEN
     250      DO
     251         /* Get reamaining key string */
     252         SubKey = SUBSTR( DefaultKey.k, SearchLen + 1)
     253         /* Get first path segment */
     254         PARSE VAR SubKey SubKey'\'.
     255         PARSE VAR SubKey SubKey '=' .
     256
     257         /* Check item for integer > 0 as group id */
     258         IF VERIFY( SubKey, '0123456789') <> 0 THEN
     259            ITERATE
     260         IF SubKey = 0 THEN
     261            ITERATE
     262
     263         /* Query key */
     264         IF fInit THEN
     265         DO
     266            PARSE VAR DefaultKey.k . '=' next
     267            next = STRIP( next)
     268         END
     269         ELSE
     270         DO
     271            next = SysIni( Ini._Filename, Ini._RegDefaults, DefaultKey.k)
     272            next = STRIP( next, 'T', '00'x)
     273         END
     274         IF next <> '' & next <> 'ERROR:' THEN
     275         DO
     276            /* Add next to Obj. */
     277            n = Obj.0 + 1
     278            Obj.n = next
     279            Obj.0 = n
     280         END
     281      END
     282   END
     283
     284   RETURN( rc)
    229285
    230286/* ----------------------------------------------------------------------- */
     
    273329   RETURN( rcx)
    274330
     331/* ----------------------------------------------------------------------- */
     332/* Syntax:                                                                 */
     333/*    rc = TextIniToStem( File, ApplicationList, Key, Stem)                */
     334/* Adds key = value lines of a text ini file to a specified stem var. The  */
     335/* search can be reduced to a list of ini applications or to a key. If no  */
     336/* Application list is specified, 'ALL:' applications are listed. If no    */
     337/* key is specified, 'ALL:' keys are listed. The number of items is        */
     338/* written to Stem''0.                                                     */
     339/* Different from SysIni for OS/2 ini files, TextIniToStem always lists    */
     340/* entire lines. Theerefore, in most cases, that list has to be parsed     */
     341/* to key and value pairs.                                                 */
     342/* Example:                                                                */
     343/*    rcx = TextIniToStem( 'defaults.cfg', 'ALL:', 'ALL:', 'DefaultKey.')  */
     344/*    DO n = 1 TO DefaultKey.0                                             */
     345/*       SAY DefaultKey.n                                                  */
     346/*    END                                                                  */
     347/* This is used here for DEFAULTS.CFG parsing */
     348TextIniToStem:
     349/*
     350Adding the value of StemVar to the expose list is not possible. Therefore
     351this function must be global.
     352*/
     353   rc = ERROR.NO_ERROR
     354   PARSE ARG File, ApplicationList, Key, StemVar
     355
     356   Entry = ''
     357   IF ApplicationList  = '' THEN
     358      ApplicationList  = 'ALL:'
     359   Application = ''
     360   IF Key = '' THEN
     361      Key = 'ALL:'
     362
     363   IF RIGHT( StemVar, 1) <> '.' THEN
     364      StemVar = StemVar'.'
     365   CALL VALUE StemVar, ''
     366   CALL VALUE StemVar''0, 0
     367
     368   next = STREAM( File, 'C', 'OPEN READ')
     369   DO WHILE CHARS( File) > 0
     370      line = LINEIN( File)
     371      SELECT
     372         WHEN LEFT( line, 1) = ';' THEN
     373            NOP
     374         WHEN STRIP( line) = '' THEN
     375            NOP
     376         WHEN LEFT( line, 1) = '[' THEN
     377         DO
     378            p2 = POS( ']', line)
     379            IF p2 > 0 THEN
     380            DO
     381               nextApplication = SUBSTR( line, 2, p2 - 2)
     382               IF WORDPOS( nextApplication, ApplicationList) > 0 | ApplicationList = 'ALL:' THEN
     383                  Application = nextApplication
     384               ELSE
     385                  Application = ''  /* nextApplication is other, reset Application */
     386            END
     387         END
     388      OTHERWISE
     389         PARSE VALUE line WITH nextKey '=' nextEntry
     390         /* it must be a 'Key = Entry' line */
     391         nextKey   = STRIP( nextKey)
     392         nextEntry = STRIP( nextEntry)
     393         IF ApplicationList <> 'ALL:' & Application = '' THEN
     394            ITERATE
     395         IF nextKey = '' THEN
     396            ITERATE
     397         IF Key = 'ALL:' | nextKey = Key THEN
     398         DO
     399            s = VALUE( StemVar''0) + 1
     400            CALL VALUE StemVar''0, s
     401            CALL VALUE StemVar''s, nextKey'='nextEntry
     402         END
     403      END
     404   END
     405   rc = STREAM( File, 'C', 'CLOSE')
     406
     407   RETURN( rc)
     408
     409/* ----------------------------------------------------------------------- */
     410/* Requires a previous call to TextIniToStem. Returns Val for a specified  */
     411/* Key.                                                                    */
     412FindTextIniVal: PROCEDURE EXPOSE (GlobalVars)
     413   Val = ''
     414   PARSE ARG StemVar, Key
     415   IF RIGHT( StemVar, 1) <> '.' THEN
     416      StemVar = StemVar'.'
     417
     418   DO s = 1 TO VALUE( StemVar''0)
     419      ThisLine = VALUE( StemVar''s)
     420      PARSE VALUE ThisLine WITH ThisKey '=' ThisVal
     421      ThisKey = STRIP( ThisKey)
     422      ThisVal = STRIP( ThisVal)
     423      IF ThisKey = Key THEN
     424      DO
     425         Val = ThisVal
     426         LEAVE
     427      END
     428   END
     429   RETURN( Val)
     430
    275431/* --------------------- Standard ERX macros follow ---------------------- */
    276432
     
    282438      WHEN ADDRESS() = 'EPM' THEN
    283439         'sayerror' Message
     440   OTHERWISE
     441      SAY Message
     442   END
     443
     444   RETURN( '')
     445
     446/* ----------------------------------------------------------------------- */
     447/* For PmPrintf output, use CALL SayDegug '...' When being called from an  */
     448/* environment outside of EPM, the message text is processed by a SAY      */
     449/* statement instead. */
     450SayDebug: PROCEDURE EXPOSE (GlobalVars)
     451   PARSE ARG Message
     452
     453   SELECT
     454      WHEN ADDRESS() = 'EPM' THEN
     455         'dprintf' Message
    284456   OTHERWISE
    285457      SAY Message
     
    305477      WHEN ADDRESS() = 'EPM' THEN
    306478      DO
    307          /*'sayerror' ErrorMessage*/
    308          ThisFileName = SUBSTR( ThisFile, LASTPOS( '\', ThisFile) + 1)
    309          rcx = RxMessageBox( ErrorMessage, TRANSLATE( ThisFileName),,
     479         'sayerror' ErrorMessage
     480         rcx = RxMessageBox( ErrorMessage, TRANSLATE( ThisName),,
    310481            'OK', 'ERROR')
    311482      END
  • TabularUnified trunk/src/netlabs/bin/startupdir.erx

    r3111 r3542  
    2929****************************************************************************/
    3030
     31IF ADDRESS() <> 'EPM' THEN
     32   '@ECHO OFF'
     33
    3134/* ----------------- Standard ERX initialization follows ----------------- */
    3235SIGNAL ON HALT NAME Halt
     
    4346Redirection = '>NUL 2>&1'
    4447PARSE SOURCE . . ThisFile
    45 GlobalVars = 'env TRUE FALSE Redirection ERROR. ThisFile'
     48GlobalVars = 'env TRUE FALSE Redirection ERROR. ThisFile ThisName'
    4649GlobalVars = GlobalVars 'ErrorQueueName ErrorMessage'
    4750
    48 /* some OS/2 Error codes */
     51/* Some OS/2 error codes */
    4952ERROR.NO_ERROR           =   0
    5053ERROR.INVALID_FUNCTION   =   1
     
    6770ErrorMessage   = ''
    6871
     72PARSE SOURCE . . ThisFile
     73lp = LASTPOS( '\', ThisFile)
     74ThisDir = LEFT( ThisFile, lp - 1)
     75ThisName = SUBSTR( ThisFile, lp + 1)
     76
    6977CALL RxFuncAdd 'SysLoadFuncs', 'RexxUtil', 'SysLoadFuncs'
    7078CALL SysLoadFuncs
    7179/* ----------------- Standard ERX initialization ends -------------------- */
     80
     81/* Extend the environment, if not already */
     82next = VALUE( 'NEPMD_NAME',, env)
     83IF next = '' THEN
     84   'CALL' ThisDir'\..\..\netlabs\bin\EPMENV'
    7285
    7386/* ------------- Configuration ---------------- */
     
    8093/* -------------------------------------------- */
    8194
    82 GlobalVars = GlobalVars 'Ini. Key.'
     95GlobalVars = GlobalVars 'Ini. Key. Obj. fInit'
    8396
    8497CALL RxFuncAdd 'WPToolsLoadFuncs', 'WPTOOLS', 'WPToolsLoadFuncs'
     
    8699
    87100DO 1
     101   fInit = 0
    88102
    89103   PARSE ARG NewDir
     
    96110         rc = ERROR.INVALID_PARAMETER
    97111         ErrorMessage = 'Error: No action or directory specified.' ||,
    98             ' Parameter for STARTUPDIR.ERX is missing.'
     112            ' Parameter for 'TRANSLATE( ThisName)' is missing.'
    99113         LEAVE
    100114      END
     
    107121   Obj.0 = 0
    108122
    109    /* Get user sub keys from RegContainer */
    110    UserSubKeys = ''
    111    next = SysIni( Ini._Filename, Ini._RegContainer, Key._MainPath)
    112    next = STRIP( next, 'T', '00'x)
    113    IF \(next = '' | next = 'ERROR:') THEN
    114       UserSubKeys = next
    115 
    116    /* Add user objects to Obj. */
    117    rest = UserSubKeys
    118    DO FOREVER
    119       PARSE VAR rest SubKey'00'x''rest
    120       IF SubKey = '' THEN
    121          LEAVE
    122 
    123       /* Check items for integer > 0 */
    124       IF VERIFY( SubKey, '0123456789') <> 0 THEN
    125          ITERATE
    126       IF SubKey = 0 THEN
    127          ITERATE
    128 
    129       /* Query key */
    130       next = SysIni( Ini._Filename, Ini._RegKeys, Key._MainPath'\'SubKey)
    131       next = STRIP( next, 'T', '00'x)
    132       IF \(next = '' | next = 'ERROR:') THEN
    133       DO
    134          /* Add next to Obj. */
    135          n = Obj.0 + 1
    136          Obj.n = next
    137          Obj.0 = n
    138       END
    139    END
    140 
    141    IF Obj.0 = 0 THEN
    142    DO
    143       /* Get all default keys */
    144       DefaultKey.  = ''
    145       DefaultKey.0 = ''
    146       next = SysIni( Ini._Filename, Ini._RegDefaults, 'ALL:', 'DefaultKey.')
    147       SearchKey = Key._MainPath'\'
    148       SearchLen = LENGTH( SearchKey)
    149       DO k = 1 TO DefaultKey.0
    150          /* Find keys that start with SearchKey */
    151          IF LEFT( DefaultKey.k, SearchLen) = SearchKey THEN
    152          DO
    153             /* Get reamaining key string */
    154             SubKey = SUBSTR( DefaultKey.k, SearchLen + 1)
    155             /* Get first path segment */
    156             PARSE VAR SubKey SubKey'\'.
    157 
    158             /* Check items for integer > 0 */
    159             IF VERIFY( SubKey, '0123456789') <> 0 THEN
    160                ITERATE
    161             IF SubKey = 0 THEN
    162                ITERATE
    163 
    164             /* Query key */
    165             next = SysIni( Ini._Filename, Ini._RegDefaults, DefaultKey.k)
    166             next = STRIP( next, 'T', '00'x)
    167             IF \(next = '' | next = 'ERROR:') THEN
    168             DO
    169                /* Add next to Obj. */
    170                n = Obj.0 + 1
    171                Obj.n = next
    172                Obj.0 = n
    173             END
    174          END
    175       END
    176    END
     123   /* Get all user keys */
     124   CALL GetUserObjects
     125
     126   /* Get all default keys */
     127   /* This fills also the DefaultKey. array */
     128   CALL GetDefaultObjects
    177129
    178130   /* Query current setting from first object */
    179    Obj = Obj.1
    180    rcx = WPToolsQueryObject( Obj, 'Class', 'Title', 'Setup', 'Location')
     131   Object = Obj.1
     132   rcx = WPToolsQueryObject( Object, 'Class', 'Title', 'Setup', 'Location')
    181133   IF (rcx = 1) THEN
    182134      OldDir = GetStartupDir( Setup)
     
    184136   DO
    185137      rc = ERROR.FILE_NOT_FOUND
    186       ErrorMessage = 'Error: Setup string couldn''t be queried from 'Obj'.'
     138      ErrorMessage = 'Error: Setup string couldn''t be queried from 'Object'.'
    187139      LEAVE
    188140   END
     
    206158END
    207159
    208 CALL SayErrorMessage
     160/* ErrorMessage */
     161DO 1
     162   IF ErrorMessage = '' THEN
     163      LEAVE
     164   /* Prepend 'Error 'rc ... if ErrorMessage doesn't contain the word 'Error' */
     165   IF POS( 'ERROR', TRANSLATE( ErrorMessage)) = 0 THEN
     166      ErrorMessage = 'Error 'rc' running 'ThisFile': 'ErrorMessage
     167   CALL SayErrorMessage
     168END
    209169EXIT( rc)
     170
     171/* ----------------------------------------------------------------------- */
     172GetUserObjects: PROCEDURE EXPOSE (GlobalVars)
     173
     174   rc = ERROR.NO_ERROR
     175
     176   /* Get user sub keys from RegContainer */
     177   UserSubKeys = ''
     178   next = SysIni( Ini._Filename, Ini._RegContainer, Key._MainPath)
     179   next = STRIP( next, 'T', '00'x)
     180   IF next <> '' & next <> 'ERROR:' THEN
     181      UserSubKeys = next
     182
     183   /* Add user objects to Obj. */
     184   rest = UserSubKeys
     185   DO FOREVER
     186      PARSE VAR rest SubKey'00'x''rest
     187      IF SubKey = '' THEN
     188         LEAVE
     189
     190      /* Check item for integer > 0 as group id */
     191      IF VERIFY( SubKey, '0123456789') <> 0 THEN
     192         ITERATE
     193      IF SubKey = 0 THEN
     194         ITERATE
     195
     196      /* Query key */
     197      next = SysIni( Ini._Filename, Ini._RegKeys, Key._MainPath'\'SubKey)
     198      next = STRIP( next, 'T', '00'x)
     199      IF next <> '' & next <> 'ERROR:' THEN
     200      DO
     201         /* Add next to Obj. */
     202         n = Obj.0 + 1
     203         Obj.n = next
     204         Obj.0 = n
     205      END
     206   END
     207
     208   RETURN( rc)
     209
     210/* ----------------------------------------------------------------------- */
     211GetDefaultObjects: PROCEDURE EXPOSE (GlobalVars)
     212
     213   rc = ERROR.NO_ERROR
     214
     215   /* Get all default keys */
     216   DefaultKey.  = ''
     217   DefaultKey.0 = 0
     218
     219   next = SysIni( Ini._Filename, Ini._RegDefaults, 'ALL:', 'DefaultKey.')
     220   IF next = 'ERROR:' THEN
     221       fInit = 1
     222
     223   IF fInit THEN
     224      next = TextIniToStem( File._DefaultsCfg, 'ALL:', 'ALL:', 'DefaultKey.')
     225
     226   SearchKey = Key._MainPath'\'
     227   SearchLen = LENGTH( SearchKey)
     228   DO k = 1 TO DefaultKey.0
     229      /* Find keys that start with SearchKey */
     230      IF LEFT( DefaultKey.k, SearchLen) = SearchKey THEN
     231      DO
     232         /* Get reamaining key string */
     233         SubKey = SUBSTR( DefaultKey.k, SearchLen + 1)
     234         /* Get first path segment */
     235         PARSE VAR SubKey SubKey'\'.
     236         PARSE VAR SubKey SubKey '=' .
     237
     238         /* Check item for integer > 0 as group id */
     239         IF VERIFY( SubKey, '0123456789') <> 0 THEN
     240            ITERATE
     241         IF SubKey = 0 THEN
     242            ITERATE
     243
     244         /* Query key */
     245         IF fInit THEN
     246         DO
     247            PARSE VAR DefaultKey.k . '=' next
     248            next = STRIP( next)
     249         END
     250         ELSE
     251         DO
     252            next = SysIni( Ini._Filename, Ini._RegDefaults, DefaultKey.k)
     253            next = STRIP( next, 'T', '00'x)
     254         END
     255         IF next <> '' & next <> 'ERROR:' THEN
     256         DO
     257            /* Add next to Obj. */
     258            n = Obj.0 + 1
     259            Obj.n = next
     260            Obj.0 = n
     261         END
     262      END
     263   END
     264
     265   RETURN( rc)
    210266
    211267/* ----------------------------------------------------------------------- */
     
    247303
    248304/* ----------------------------------------------------------------------- */
     305/* For PmPrintf output, use CALL SayDegug '...' When being called from an  */
     306/* environment outside of EPM, the message text is processed by a SAY      */
     307/* statement instead. */
     308SayDebug: PROCEDURE EXPOSE (GlobalVars)
     309   PARSE ARG Message
     310
     311   SELECT
     312      WHEN ADDRESS() = 'EPM' THEN
     313         'dprintf' Message
     314   OTHERWISE
     315      SAY Message
     316   END
     317
     318   RETURN( '')
     319
     320/* ----------------------------------------------------------------------- */
    249321SayErrorMessage: PROCEDURE EXPOSE (GlobalVars)
    250322
     
    263335      WHEN ADDRESS() = 'EPM' THEN
    264336      DO
    265          /*'sayerror' ErrorMessage*/
    266          ThisFileName = SUBSTR( ThisFile, LASTPOS( '\', ThisFile) + 1)
    267          rcx = RxMessageBox( ErrorMessage, TRANSLATE( ThisFileName),,
     337         'sayerror' ErrorMessage
     338         rcx = RxMessageBox( ErrorMessage, TRANSLATE( ThisName),,
    268339            'OK', 'ERROR')
    269340      END
Note: See TracChangeset for help on using the changeset viewer.