zOs/REXX.O08/ZUEGEL

/* rexx ***************************************************************
    synopsys: TSO ZUEGEL fun

    fun
        leer oder ? diese Hilfe
        d qual      wsl Member (in DSN.DBA.qual.WSL) und IFF pruefen,
                        im Batch laufen lassen um IFF zu restoren |
        x prd       xmit wsl members and iff to production
        x pta       xmit wsl members and iff to pta
        c           clone alle WSL (nur im RZ2 oder RR2)


    die WSL's sind in einem Dataset(Member) definiert mit Layout
        wsl    user     auft rz date       time        mask
        1               19   24            38          50

    rz: 2, 4, 24: welche RZ's
    mask: falls ein spezielles MaskingDataset verwendet werden soll
                .ODV ==> DSN.DBA.MASK.DBAFDBOF.ODV

************************************************************************
05.05.2007 w. keller neu
***********************************************************************/
    call adrIsp 'Control errors return'
    parse upper arg fun opt
    skels = 'ORG.U0009.B0106.KIUT23.SKELS'
    list = skels'(zglAug)'
    gen = '~tmp.jcl'
    if fun = '' | pos('?', fun opt) > 0 then do
        say 'zuegel mit wsl-Liste in' list
        exit help()
        end
    call wslList list
    if fun = 'D' then
        call wslDsns opt
    else if fun = 'X' then
        call makeJobs skels'(zglXm'dest(opt)')', gen'(zueXm'dest(opt)')'
    else if fun = 'C' then
        call makeClon skels'(zglClone)', gen'(zueClone)'
    else if fun = 'R' then
        call rmMembers DSN.DBA.DBOF.WSL
    else
        call errHelp 'bad fun' fun 'in arguments' fun opt
exit

dest: procedure
parse arg opt
    if abbrev('PROD', opt) | abbrev('PRD', opt) then
        return 'PRD'
    else if abbrev('PTA', opt) then
        return 'PTA'
    else
        call errHelp 'ungueltiges RZ' opt
endProcedure dest

wslList: procedure expose m.
parse arg dsn
    call readDsn dsn, m.wsl.
    wx = 0
    do sx = 1 to m.wsl.0
        sl = m.wsl.sx
        if left(sl, 1) = '*' then
            say 'ignoring' strip(sl, 't')
        else do
            wx = wx+1
            m.wx.name = substr(sl,  1, 8)
            m.wx.auft = substr(sl, 19, 2)
            m.wx.rz   = substr(sl, 24, 2)
            m.wx.tim  = substr(sl, 38, 5)
            m.wx.mask = word(substr(sl, 50, 5), 1)
        /*  say m.wx.name 'auft' m.wx.auft 'rz' m.wx.rz 'um' m.wx.tim */
            end
        end
    m.0 = wx
    say m.0 'WSLs' form m.wsl.0 'lines from' dsn
    return
endProcedure wlsList

wslDsns: procedure expose m.
    parse arg mid
    if mid = '' then
        mid = 'CLON'
    pds = 'DSN.DBA.'mid'.WSL'
    pre = 'DSN.DBA.'
    suf = '.IFF'
    do wx=1 to m.0
        say m.wx.name sysDsn("'"pds"("strip(m.wx.name)")'")
        fn = pre || overlay('Q', m.wx.name, 8) || suf
        say fn sysDsn("'"fn"'")
        end
    return
endProcedure wslDsns

makeJobs: procedure expose m.
parse arg iDs, oDs
    call readDsn iDs, j.
    do ex=1 to j.0 while pos('EXEC', j.ex) < 4
        end
    say 'exec' ex strip(left(j.ex, 72), 't')
    o = 0
    do wx=1 to m.0
        if m.wx.rz = '' then do
            say 'ignoring' m.wx.name 'rz' m.wx.rz 'tim' m.wx.tim
            iterate
            end
        do j=1 to ex-1
            o = o + 1
            o.o = chg(j.j, '???', left(m.wx.name, 7))
            end
        do r=2 to 4
            if pos(r, m.wx.rz) < 1 then
                iterate
            do j=ex to j.0
                o = o + 1
                o.o = chg(j.j, '???', left(m.wx.name, 7), '|', r)
                end
            end
        end
    call writeDsn oDs '::F', o., o, 1
    call adrIsp "edit dataset('"dsn2jcl(oDs)"')", 4
    return
endProcedure makeJobs

makeClon: procedure expose m.
parse arg iDs, oDs
    call readDsn iDs, j.
    o = 0
    do wx=1 to m.0
        isOld = translate(substr(m.wx.name, 8, 1), 'YN', 'CW')
        isNew = translate(substr(m.wx.name, 8, 1), 'NY', 'CW')
        say m.wx.name '==> isNew' isNew 'isOld' isOld
        if ^ (isNew == 'Y' | isNew == 'N') then
            call err 'isNew not Y or N but' isNew 'wsl' m.wx.name
        do j=1 to j.0
            if left(j.j, 3) = '---' then do
                if isNew == 'Y' then
                    j.j = substr(j.j, 4)
                else
                    iterate
                end
            o = o + 1
            o.o = chg(j.j, '????', m.wx.name,
                         , '???',  left(m.wx.name, 7) ,
                         , '[',  isNew,
                         , ']',  isOld,
                         , '+++',  m.wx.mask)
            end
        end
    call writeDsn oDs "::F", o., o, 1
    call adrIsp "edit dataset('"dsn2jcl(oDs)"')", 4
    return
endProcedure makeClon

rmMembers: procedure expose m.
parse arg dsn
    mm = ''
    do wx=1 to m.0
        mm = mm m.wx.name
        end
    say 'remove from' dsn
    say mm
    parse upper pull an 2 .
    if an ^== 'R' then
        call err 'not removing answer was' an
    call lmmRmMbr "'"dsn"'", mm
    return
endProcedure makeClon

chg: procedure
parse arg text 73 over
    do ax=2 by 2 to arg()
        ol = arg(ax)
        ne = arg(ax+1)
        cx = 1
        do forever
            cx = pos(ol, text, cx)
            if cx < 1 then
                leave
            text = left(text, cx-1) || ne ,
                   || substr(text, cx + length(ol))
            cx = cx + length(ne)
            end
        end
    return strip(text, 't')
endProcedure chg

err:
    call errA arg(1), 1
endSubroutine err
/* rexx */
call lmmTest
exit
/* copy adrIsp begin *************************************************/
/**********************************************************************
    lmd: catalog read
    call sequence: lmdBegin, lmdNext*, lmdEnd
        mit lmd service (mit save in file und read,
                         weil list zu langsam und listcat abstürzt)
        1. arg (grp)     als group dataset für lmd save
                         und dd name für file read
***********************************************************************/
lmdBegin: procedure
    parse arg grp, lev
    call adrIsp 'lmdinit listid(lmdId) level('lev')'
    res = adrIsp('lmdlist listid(&lmdId) option(save) group('grp')', 4)
    call adrIsp 'lmdfree listid(&lmdId)'
    if res = 0 then do
        call trc showTime() 'lmdlist save' grp lev
        call adrTso 'alloc dd('grp') shr dsn('grp'.datasets)'
        end
    else do
        call trc 'no datasets found' showTime() 'lmdlist save' grp lev
        call adrTso 'alloc dd('grp') dummy'
        end
    call readDDBegin grp
return /* end lmdBegin */

lmdNext:
    parse arg ggGrp, ggSt, withVolume
    if ^ readDD(ggGrp, ggSt) then
         return 0
    if withVolume ^== 1 then
        do ggIx=1 to value(ggSt'0')
            x = value(ggSt || ggIx, word(value(ggSt || ggIx), 1))
            end
    return 1
endSubroutin lmdNext

lmdEnd: procedure
    parse arg grp
    call readDDEnd grp
    call adrTso 'free dd('grp')'
return /* end lmdEnd */

/**********************************************************************
    member list of a pds:
        call sequence x=lmmBegin(dsn) lmmNext(x) * lmmEnd(x)
***********************************************************************/
lmmTest: procedure
parse arg dsn
    if dsn = '' then
        dsn = 'wk.pli(*)'
    say 'lmmTest for dsn' dsn
    id = lmmBegin(dsn2Jcl(dsn, 1))
    do ix=1 by 1
        m = lmmNext(id)
        if m = '' then
            leave
        say ix m
        end
    call lmmEnd id
    say  'lmmTest end' (ix-1) 'members in' dsn
    return
endProcedure lmmTest

lmmBegin: procedure
parse arg dsn
    mbr = dsnGetMbr(dsn)
    pds = dsnSetMbr(dsn, )
    call adrIsp "LMINIT DATAID(lmmId) DATASET('"pds"') ENQ(SHRW)"
    call adrIsp "LMOPEN DATAID("lmmId") OPTION(INPUT) "
    res = lmmId
    if mbr <> '' then
        res = res 'pattern('mbr')'
    return res
endProcedure lmmBegin

lmmEnd: procedure
parse arg lmmId opt
    call adrIsp "LMMLIST DATAID("lmmId") option(free)", 8
    call adrIsp "LMCLOSE DATAID("lmmId")"
    call adrIsp "LMFREE DATAID("lmmId")"
    return
endProcedure lmmEnd

lmmNext: procedure
parse arg lmmId opt
    if adrIsp("LMMLIST DATAID("lmmid")" ,
               "OPTION(LIST) MEMBER(Mbr)" opt, 4 8) = 0 then
        return mbr
    else
        return ''
endProcedure lmmNext

lmmRmMbr: procedure
parse arg dsn, mbrs
    mbrs = dsnGetMbr(dsn) mbrs
    pds = dsnSetMbr(dsn, )
    call adrIsp "LMINIT DATAID(lmmId) DATASET("pds") ENQ(SHRW)"
    call adrIsp "LMOPEN DATAID("lmmId") OPTION(OUTPUT) "
    err = ''
    do wx=1 to words(mbrs)
        m1 = word(mbrs, wx)
        rr = adrIsp("lmmDel dataid("lmmId") member("m1")", 0 8 12)
        if rc = 0 then
            say 'removed' m1 'from' pds
        else if rc = 8 then
            say 'not found' m1 'in' pds
        else do
            err = 'error deleting' m1 'in' pds 'rc' rr strip(zerrlm)
            say err
            leave
            end
        end
    call adrIsp "LMCLOSE DATAID("lmmId")"
    call adrIsp "LMFREE DATAID("lmmId")"
    if err <> '' then
        call err err
    return
/**********************************************************************
    adr*: address an environment
***********************************************************************/

adrIsp:
    parse arg ggIspCmd, ggRet
    address ispexec ggIspCmd
    if rc = 0 then return 0
    else if ggRet == '*' then return rc
    else if wordPOS(rc, ggRet) > 0 then return rc
    else
        call err 'adr ispExec rc' rc 'in' ggIspCmd':' strip(zerrlm)
endSubroutine adrIsp

adrEdit:
    parse arg ggEditCmd, ggRet
    address isrEdit ggEditCmd
    if rc = 0 then return 0
    else if ggRet == '*' then return rc
    else if wordPOS(rc, ggRet) > 0 then return rc
    else
        call err 'adr isrEdit rc' rc 'for' ggEditCmd
endSubroutine adrEdit

/* copy adrIsp end   *************************************************/
/* copy adrTso begin *************************************************/
/*--- send ggTsoCmd to tso, fail if rc <> 0 or not listed in ggRet ---*/
adrTso:
    parse arg ggTsoCmd, ggRet
    address tso ggTsoCmd
    if rc == 0                     then return 0
    else if ggRet == '*'           then return rc
    else if wordPos(rc, ggRet) > 0 then return rc
    else
        call err 'adrTso rc' rc 'for' ggTsoCmd
return /* end adrTso */
/*--- format dsn from tso format to jcl format -----------------------*/
dsn2jcl: procedure
parse arg dsn ., addPrefix
    if left(dsn,1) = "'" then
        return strip(dsn, 'b', "'")
    sp = sysvar('SYSPREF')
    if sp == '' then
        sp = userid()
    cx = pos('~', dsn)
    if cx < 1 & addPrefix == 1 then
        return sp'.'dsn
    do while cx ^== 0
        le = left(dsn, cx-1)
        ri = substr(dsn, cx+1)
        if right(le, 1) == '.' | left(ri, 1) == '.' then
            dsn = le || sp || ri
        else
            dsn = le || left('.', le ^== '') || sp ,
                     || left('.', ri ^== '') || ri
        cx = pos('~', spec, cx)
        end
    return dsn
endProcedure dsn2Jcl

/*--- format dsn from jcl format to tso format -----------------------*/
jcl2dsn: procedure
parse arg dsn .
    return "'"dsn"'"
endProcedure jcl2dsn

dsnSetMbr: procedure
parse arg dsn, mbr
     bx = pos('(', dsn)
     if bx > 0 then
         dsn = strip(left(dsn, bx-1))
     if mbr <> '' then
         dsn = dsn'('strip(mbr)')'
     return dsn
endProcedure dsnSetMbr

dsnGetMbr: procedure
parse arg dsn
     lx = pos('(', dsn)
     rx = pos(')', dsn, lx+1)
     if lx < 1 then
         return ''
     else if lx < rx then
         return substr(dsn, lx+1, rx-lx-1)
     else
         return strip(substr(dsn,lx+1))
endProcedure dsnGetMbr
/**********************************************************************
    io: read or write a dataset with the following callsequences:
        read:  readDDBegin, readDD*,  readDDEnd
        write: writeBegin,  writeDD*, writeEnd

        readDD returns true if data read, false at eof
***********************************************************************/

/*--- prepare reading from a DD --------------------------------------*/
readDDBegin: procedure
return /* end readDDBegin */

/*--- read from DD ggDD into ggSt, return false at eof ---------------*/
readDD:
    parse arg ggDD, ggSt, ggCnt
    if ggCnt = '' then
        ggCnt = 100
    call adrTso 'execio' ggCnt 'diskr' ggDD '(stem' ggSt')', 2
    return (value(ggSt'0') > 0)
return /* end readDD */

/*--- finish reading DD  ggDD ----------------------------------------*/
readDDEnd: procedure
    parse arg ggDD
    call adrTso 'execio 0 diskr' ggDD '(finis)'
return /* end readDDEnd */

/*--- prepare writing to DD ggDD -------------------------------------*/
writeDDBegin: procedure
    parse arg ggDD
                  /* ensure file is erased, if no records are written */
    call adrTso 'execio' 0 'diskw' ggDD '(open)'
return /* end writeDDBegin */

/*--- write to gg ggDD from stem ggSt, ggCnt records -----------------*/
writeDD:
    parse arg ggDD, ggSt, ggCnt
    if ggCnt == '' then
        ggCnt = value(ggst'0')
    call adrTso 'execio' ggCnt 'diskw' ggDD '(stem' ggSt')'
    return
endSubroutine writeDD

/*--- end writing to dd ggDD (close) --------------------------------*/
writeDDEnd: procedure
    parse arg ggDD
    call adrTso 'execio 0 diskw' ggDD '(finis)'
return /* end writeDDEnd */

/*--- alloc a dsn or a dd -------------------------------------------*/
dsnAlloc: procedure expose m.
parse upper arg spec, disp, dd
    ds = ''
    if left(spec, 1) = '-' then
        return strip(substr(spec, 2))
    if left(spec, 1) = '&' then /* external spec is handled ok */
        spec = strip(substr(spec, 2))
    rest = ''
    do wx=1 by 1
        w = word(spec, wx)
        if w = '' then
            leave
        if abbrev(w, '.') then do
            rest = substr(subword(spec, wx),  2)
            leave
            end
        if abbrev(w, ':') then do
            nn = substr(subword(spec, wx),  2)
            leave
            end
        if wordPos(w, 'OLD SHR MOD NEW')>0 | abbrev(w, 'SYSO') then
            disp = w
        else if w = 'CATALOG' then
            disp = disp w
        else if abbrev(w, 'DD(') then
            dd = substr(w, 4, length(w)-4)
        else if ds = '' then
            ds = dsn2jcl(w)
        else
            leave
        end
    if dd = '' then
        dd = 'DD' || ooNew()
    if disp = '' | (disp = 'OLD' & pos('(', dsn) > 0) then
        disp = 'SHR'
    m.dsnAlloc.dsn = ds
    if ds <> '' then
        ds = "DSN('"ds"')"
    alRc = adrTso('alloc dd('dd')' disp ds rest, '*')
    if alRc ^== 0 then do
        if nn = 'NN' | wordPos(disp, 'OLD SHR') < 1 ,
            | sysDsn("'"m.dsnAlloc.dsn"'") ^== 'DATASET NOT FOUND' then
          call err 'tsoAlloc rc' alRc 'for alloc dd('dd')' disp ds rest
        say 'tsoAlloc rc' alRc 'for alloc dd('dd')' disp ds rest ,
            '...trying to create'
        call dsnAllocCreate m.dsnAlloc.dsn, nn
        call adrTso 'alloc dd('dd')' disp ds rest
        end
    return dd 'call adrTso "free dd('dd')";'
endProcedure dsnAlloc

dsnAllocCreate: procedure expose m.
parse arg dsn, atts
    if abbrev(atts, ':') then do
        rl = substr(atts, 3)
        if abbrev(atts, ':F') then do
            if rl = '' then
                rl = 80
             atts = 'recfm(f b) lrecl('rl')' ,
                       'block(' (32760 - 32760 // rl)')'
            end
        else do
            if rl = '' then
                rl = 32756
            atts = 'recfm('substr(atts, 2, 1) 'b) lrecl('rl')' ,
                   'block(32760)'
            end
        if pos('(', dsn) > 0 then
            atts = atts 'dsntype(library) dsorg(po)' ,
                   "dsn('"dsnSetMbr(dsn)"')"
        else
            atts = atts "dsn('"dsn"')"
        atts = 'new catalog' atts 'mgmtclas(s005y000) space(10, 1000)'
        end
    call adrTso 'alloc dd(dsnAlloc)' atts
    call adrTso 'free  dd(dsnAlloc)'
    return
endProcedure dsnAllocCreate

readDSN:
parse arg ggDsnSpec, ggSt
    ggAlloc = dsnAlloc(ggDsnSpec, 'SHR', 'readDsN')
    call adrTso 'execio * diskr' word(ggAlloc, 1) '(stem' ggSt' finis)'
    interpret subword(ggAlloc, 2)
    return
endSubroutine readDsn

writeDSN:
parse arg ggDsnSpec, ggSt, ggCnt, ggSay
    if ggCnt == '' then
        ggCnt = value(ggst'0')
    ggAlloc = dsnAlloc(ggDsnSpec, 'OLD', 'readDsN')
    call adrTso 'execio' ggCnt 'diskw' word(ggAlloc, 1) ,
            '(stem' ggSt 'finis)'
    interpret subword(ggAlloc, 2)
    if ggSay == 1 | m.debug == 1 then
       say ggCnt 'records written to' ggDsnSpec
    return
endSubroutine writeDsn

/* copy adrTso end ****************************************************/
/* copy err begin ******************************************************
    messages, errorhandling,help
***********************************************************************/
/* caller should define err as follows ---------------------------------
err:
    call errA arg(1), 1
endSubroutine err
   end call should define err ----------------------------------------*/

/*--- error routine: abend with message ------------------------------*/
errA:
    parse arg ggTxt, ggHist
    parse source . . ggS3 .                           /* current rexx */
    say 'fatal error in' ggS3':' ggTxt
    if ggHist ^== 1  then
        exit setRc(12)
    say 'divide by zero to show stack history'
    x = 1 / 0
endSubroutine errA

/*--- abend with Message after displaying help -----------------------*/
errHelp: procedure
parse arg ggMsg
    parse source . . ggS3 .                           /* current rexx */
    say 'fatal error in' ggS3':' ggMsg
    call help
    call err ggMsg
endProcedure errHelp

/*--- set rc for ispf: -------------------------------------------------
    if a cmd is run by ispStart, its RC is ignored,
         but ISPF passes the value of the shared varible 3IspfRc
         back as return code
----------------------------------------------------------------------*/
setRc: procedure
parse arg zIspfRc
    if sysVar('sysISPF') = 'ACTIVE' then do
        say 'exitRc setting zIspfRc='zIspfRc
        address ispExec vput 'zIspfRc' shared
        end
    return zIspfRc
endProcedure setRc

/*--- output a trace message if m.trace is set -----------------------*/
trc: procedure expose m.
parse arg msg
    if m.trace == 1 then
        say 'trc:' msg
    return
endProcedure trc

/*--- quote string txt using quoteChar qu ("""" ==> ") ---------------*/
quote: procedure
parse arg txt, qu
    if qu = '' then
        qu = '"'
    res = qu
    ix = 1
    do forever
        qx = pos(qu, txt, ix)
        if qx = 0 then
            return res || substr(txt, ix) || qu
        res = res || substr(txt, ix, qx-ix) || qu || qu
        ix = qx + length(qu)
        end
endProcedure quote

/*--- return current time and cpu usage ------------------------------*/
showtime: procedure
return time() time('E') sysvar('syscpu') /* sysvar('syssrv') */

/--- display the first comment block of the source as help -----------*/
help: procedure
    parse source . . s3 .
    say right(' help for rexx' s3, 79, '*')
    do lx=1 by 1
        if pos('/*', sourceLine(lx)) > 0 then
            leave
        else if lx > 10 then do
            say 'initial commentblock not found for help'
            return
            end
        end
    do lx=lx+1 by 1
        li = strip(sourceLine(lx), 't', ' ')
        if pos('*/', li) > 0 then
            leave
        say li
        end
    say right(' end help for rexx' s3, 79, '*')
    return 4
endProcedure help
/* copy err end   *****************************************************/