ConvCase

From Pickwiki
Jump to navigationJump to search

This program will convert the case of records or @IDs.

!
** Convert case of record
** (C) Copyright 1985-2007, Advantos Systems, Inc.  All Rights Reserved.
!
** Last Modified: 11 Mar 2007, wph
** First Created: 01 Jul 1992, wph
** Program Type-: Utility
!
** Notes:
**
** This process changes the case of record items.
**
**-------------------------------------------------------------------**
**                                                                   **
**                    I N I T I A L I Z A T I O N                    **
**                                                                   **
**-------------------------------------------------------------------**
*
** initialize local variables
*$OPTIONS EXT                     ; ** D3 version

SP1     = ' '
[[UpdCnt]]  = 0
[[ReadCnt]] = 0
NULL$   = ''
[[DictSw]]  = NULL$
*
** read tcl line
[[TclLine]] = @SENTENCE                      ; ** UD version
*[[TclLine]] = @COMMAND                       ; ** UV version
*TCLREAD [[TclLine]]                          ; ** D3 version
[[TclLine]]  = TRIM([[TclLine]])
*
** parse out command and options
OPTIONS = FIELD([[TclLine]], '(', 2)         ; ** U2 version
*OPTIONS  = SYSTEM(15)                    ; ** D3 version
[[TclLine]] = TRIM(FIELD([[TclLine]], '(', 1))
OPTIONS = TRIM(OPTIONS)
*
** convert spaces to attribute marks for string manipulation
CONVERT ' ' TO @AM IN [[TclLine]]
[[TclLine]] = DELETE([[TclLine]], 1)     ; ** remove command from line
FNAME   = [[TclLine]]<1>
IF INDEX(OPTIONS, '?', 1) THEN FNAME = '?'
*
** help option
IF FNAME = '?' THEN GOTO DISPLAY.HELP
*
** get file name
IF FNAME = '' THEN STOP 10
IF FNAME = 'DICT' OR FNAME = 'DATA' THEN
   IF FNAME = 'DICT' THEN [[DictSw]] = 'DICT'
   FNAME   = TRIM([[TclLine]]<2>)
   [[TclLine]] = DELETE([[TclLine]],1)
END
*
** open file to process
OPEN [[DictSw]], FNAME TO FNAME.FV ELSE
   CRT '...No ' : FNAME : ' file available'
   GOTO END.OF.PROGRAM
END
*
IF FNAME[LEN(FNAME),1] = ',' THEN
   ANAME = FIELD(FNAME, ',', 1)
   DNAME = FIELD(FNAME, ',', 2)
   IF DNAME = '' ELSE DNAME = DNAME:','
END ELSE
   ACCTP = 2                                   ; ** U2 version
*  IF SYSTEM(29) THEN ACCTP = 2 ELSE ACCTP = 3 ; ** D3 version
   OPUT  = OCONV('', '[[U50BB]]')
   ANAME = FIELD(OPUT, ' ', ACCTP)
   DNAME = ''
END
*
** remove file from command and parse options
[[TclLine]] = DELETE([[TclLine]], 1)
IF [[TclLine]] = ''           THEN TCLFLG = 0 ELSE TCLFLG = 1
IF INDEX(OPTIONS, 'I', 1) THEN IDSUPP = 1 ELSE IDSUPP = 0
IF INDEX(OPTIONS, 'O', 1) THEN OFLG   = 1 ELSE OFLG   = 0
IF INDEX(OPTIONS, 'U', 1) THEN UCSW   = 1 ELSE UCSW   = 0
IF INDEX(OPTIONS, 'L', 1) THEN
   LCSW  = 1
   CASCV = 'MCL'
END ELSE
   LCSW  = 0
   CASCV = 'MCU'
END
IF INDEX(OPTIONS, 'Q', 1) THEN
   QUOTESW = 1
   IF INDEX(OPTIONS, 'E', 1) THEN EXEC = 1 ELSE EXEC = 0
END ELSE
   QUOTESW = 0
END
*
** make sure if Key Only is chosen 'Q' & 'E' options are deactivated
IF INDEX(OPTIONS, 'K', 1) THEN
   UPDKEY  = 1
   EXEC    = 0
   QUOTESW = 0
END ELSE
   UPDKEY = 0
END
**
**-------------------------------------------------------------------**
**                                                                   **
**                 S T A R T   P R O G R A M   R U N                 **
**                                                                   **
**-------------------------------------------------------------------**
*
** Process record(s)
EOJ      = 0
FTIME    = 1
SEL.LIST = SYSTEM(11)
LOOP
   IF SEL.LIST THEN
      READNEXT ID ELSE EOJ = 1
   END ELSE
      IF TCLFLG THEN
         ID      = [[TclLine]]<1>
         [[TclLine]] = DELETE([[TclLine]], 1)
         IF ID = '' THEN EOJ = 1
      END ELSE
         CRT 'ENTER ID: ':
         INPUT ID
         IF ID = '' THEN EOJ = 1
      END
   END
   ID = TRIM(ID)
UNTIL EOJ DO
   IF FTIME THEN
      FTIME = 0
      IF ID = '*' THEN
         SEL.LIST = 1
         SELECT
         READNEXT ID ELSE GOTO END.OF.PROGRAM
      END
   END
   [[ReadCnt]] += 1                        ; ** increment read count
   READU ITEM FROM FNAME.FV, ID THEN
*     IF SYSTEM(0) = 10 THEN                      ; ** D3 version
*        RELEASE FNAME.FV, ID          ; ** binary  ** D3 version
*     END ELSE                                    ; ** D3 version
         IF NOT(UPDKEY) AND (UCSW OR LCSW) THEN
            [[NoOfAms]] = DCOUNT(ITEM, @AM)
            FOR A = 1 TO [[NoOfAms]]
               LN  = ITEM<A>
               IND = INDEX(LN, 'CHAIN ', 1)
               IF IND ELSE IND = INDEX(LN, 'TCL ',     1)
               IF IND ELSE IND = INDEX(LN, 'EXECUTE ', 1)
               GOSUB CASE.CONVERT 
               ITEM<A> = LN
            NEXT A
         END
         IF UPDKEY THEN
            DELETE FNAME.FV, ID
            ID = OCONV(ID, CASCV)     ; ** convert ID to upper/lower case
         END
         WRITE ITEM ON FNAME.FV, ID

** increment update count and display progress
         [[UpdCnt]] += 1
         IF NOT(IDSUPP) THEN 
            IF OFLG THEN
               CRT ID : SP1 :
            END ELSE
               IF NOT(MOD([[UpdCnt]], 100)) THEN CRT '.' :
            END
         END
*     END                                         ; ** D3 version
   END ELSE
      RELEASE FNAME.FV, ID
      STOP 202, ID
   END
REPEAT
*
GOTO END.OF.PROGRAM
*
**----------------------------------------------------------------**
**                                                                **
**                     S U B R O U T I N E S                      **
**                                                                **
**----------------------------------------------------------------**
*
** Convert the case of a line
***************
CASE.CONVERT:
***************
*
FIRST.CHAR.YET = 0             ; ** non-space character
COMMENT.SW     = 0             ; ** is this a comment
IF QUOTESW THEN
   DQ.SW   = 0                 ; ** double-quote switch
   SQ.SW   = 0                 ; ** single-quote switch
   BS.SW   = 0                 ; ** back-slash switch
   CC.HIGH = LEN(LN)
   FOR CCX = 1 TO CC.HIGH
      CC.CHAR = LN[CCX,1]      ; ** get the character
*
** process if we're not in a string$
      IF NOT(DQ.SW) AND NOT(SQ.SW) AND NOT(BS.SW) THEN
*
** is the 1st non-space character of the line?      
         IF NOT(FIRST.CHAR.YET) THEN
            BEGIN CASE
               CASE CC.CHAR   = ' '  ; GOTO NEXT.CCX
               CASE CC.CHAR   = '*'  ; COMMENT.SW = 1
               CASE CC.CHAR   = '!'  ; COMMENT.SW = 1
               CASE LN[CCX,4] = 'REM '
                  COMMENT.SW = 1
                  CCX       += 4
                  CC.CHAR    = LN[CCX,1]
            END CASE
            FIRST.CHAR.YET = 1
         END
*
** determine if we're starting an un-commented string$
         IF NOT(COMMENT.SW) THEN
            BEGIN CASE
               CASE CC.CHAR = '"'  ; DQ.SW = 1
               CASE CC.CHAR = "'"  ; SQ.SW = 1
               CASE CC.CHAR = '\'  ; BS.SW = 1
               CASE CC.CHAR = ';'  ; FIRST.CHAR.YET = 0
               CASE 1
                  CC.CHAR = OCONV(CC.CHAR, CASCV)
                  LN[CCX,1] = CC.CHAR
            END CASE
         END
      END ELSE
*
* see if we need to un-string$ the string otherwise leave it alone
         IF NOT(COMMENT.SW) THEN
            BEGIN CASE
               CASE DQ.SW AND CC.CHAR = '"' ; DQ.SW = 0
               CASE SQ.SW AND CC.CHAR = "'" ; SQ.SW = 0
               CASE BS.SW AND CC.CHAR = '\' ; BS.SW = 0
            END CASE
         END
      END
*
NEXT.CCX:
*
   NEXT CCX
END ELSE
   LN = OCONV(LN, CASCV)        ; ** convert entire line
END
RETURN
*
** Help display
***************
DISPLAY.HELP:
***************
*
CRT
CRT 'Convert CASE of data from Upper-to-Lower or Lower-to-Upper.  This'
CRT 'is usually done for program files, but can be done for any files.'
CRT
CRT 'Syntax:'
CRT '  CONV.CASE [[FileName]] {Item Criteria} {(OPTIONS)}'
CRT
CRT '  * options:'
CRT '       E - Used with Q-Option to Convert Case of Items'
CRT '           within quotes due to CHAIN, TCL, or EXECUTE'
CRT '       I - Suppresses Item-Id output'
CRT '       K - Converts Record [K]eys (item Ids) only'
CRT '       L - Convert Upper to Lower Case'
CRT '       O - Output Item-Ids on Same Line'
CRT '       Q - Leaves Text within quotes Unchanged.   Also leaves'
CRT '           program comments unchanged.'
CRT '       U - Convert Lower to Upper Case (default)'
CRT
CRT 'Note: If you select the [K]ey option only the key will be updated'
STOP
*
**----------------------------------------------------------------**
**                                                                **
**                  E N D   O F   P R O G R A M                   **
**                                                                **
**----------------------------------------------------------------**
*
***************
END.OF.PROGRAM:
***************
*
CRT
CRT [[ReadCnt]] : " items read for updating."
CRT [[UpdCnt]]  : " items updated."
END