zOs/REXX/SENDJOB

/* rexx ****************************************************************
       send files, job and receceive outputs with CSM

       node destNode       set destination node
       send fn             send fn (filename or -dd)
       job  fn opt? cf mark send job from fn (filename or -dd),
                           communication file cf and mark mark
                           opt: leer                                 or
                                123     timout secs (default 3600)   or
                                //??    replace leading ?? by //     or
                                123//?? timeout and replace
       mark cf mark res    mark communicationfile cf with mark mark
                           and result res (ok or errorMessage)
       wait ti? cf mark    wait with timeout ti secs (default 3600)
                           until communicationfile cf is marked ok
       receive fn          receive (filename or -dd)
************************************************************************
10.01.14 W. Keller wieder csm.div
27.09.13 W. Keller Anpassungen RZ4, neue Copies
07.12.09 W. Keller csm.div -> csm.rz1
05.09.08 W. Keller neu
***********************************************************************/
parse arg args
call errReset 'h'
if args = '?' then /* no help for //?? || */
    return help()
else if args = '' then do
    if 1 then
        return errHelp('no args')
    args = 'node rz1 mark A540769.tmp.ganz.neu(eins) hier submit' ,
           'node rr2' ,
           'job A540769.WK.JCL(sendJobI) 9//?? ' ,
           '    A540769.tmp.e.d(sejoTest) sejoTest' ,
           'receive A540769.TMP.TEXT(BBB)'
    end
 /*        'mark A540769.tmp.b.c(d) markMarjk ok',
           'job A540769.WK.TEST(RUN) 13 A540769.tmp.b.c(cf)   jobEins'
 */
    defTimeOut = 3600
    ax = 1
    do forever
        parse value subword(args, ax, 5) with w1 w2 w3 w4 w5 .
        upper w1
        em = w1 '(word' ax' in' space(args, 1)')'
        if w1 = '' then
            leave
        if w2 = '' then
             call errHelp 'argument missing for' em
        if w1 = 'NODE' then do
            m.node = w2
            ax = ax + 2
            end
        else if m.node = '' then do
            call errHelp 'first statement not NODE in' em
            end
        else if w1 = 'JOB' then do
            cc = (datatype(w3, 'N') | pos('//', w3) > 0) + 4
            ax = ax + cc
            if value('w'cc) = '' then
                call errHelp 'argument missing for' em
            if cc = 5 & abbrev(w3, '//') then
                w3 = defTimeOut || w3
            if cc = 5 then
                call job w2, w3, w4, w5
            else
                call job w2, defTimeOut, w3, w4
            end
        else if  w1 = 'MARK' then do
            if w4 = '' then
                call errHelp 'argument missing for' em
            call mark w2, w3, w4
            ax = ax + 4
            end
        else if  w1 = 'RECEIVE' then do
            say 'copying' m.node'/'w2 'to */'w2
            call csmCopy  m.node'/'w2, '*/'w2
            ax = ax + 2
            end
        else if  w1 = 'SEND' then do
            say  'copying'  '*/'w2 'to' m.node'/'w2
            call csmCopy  '*/'w2, m.node'/'w2
            ax = ax + 2
            end
        else if w1 = 'WAIT' then do
            cc = datatype(w2, 'N')+3
            ax = ax + cc
            if value('w'cc) = '' then
                call errHelp 'argument missing for' em
            if datatype(w3, 'N') then
                call wait w2, w3, w4
            else
                call wait defTimeOut, w2, w3
            end
        else do
            call errHelp 'bad statement' em
            end
        end
exit

job: procedure expose m.
parse arg jo, tiOu '//' rep, cf, mark
    sysl = csmSysDsn(m.node'/')
    if sysl = '*/' then
        sysl = ''
    say 'job from' jo 'tiOu' tiOu 'communicationfile' cf 'mark' mark
    call mark sysl || cf, mark, 'submit'
    call readDsn jo, j.
    if rep ^= '' then
        do jx=1 to j.0
            if abbrev(j.jx, rep) then
                j.jx = '//'substr(j.jx, length(rep)+1)
            end
    call writeDsn sysl 'SYSOUT(T) dd(ir) .WRITER(INTRDR)', j.
    call wait tiOu, cf, mark
    return
endProcedure job

wait: procedure expose m.
parse arg tiOu, cf, mark
    sysl = csmSysDsn(m.node'/')
    if sysl = '*/' then
        sysl = ''
    cf = sysl || cf
    tot = 0
    info = 'job' mark 'on' cf
    do dly=1 by 1
        say time() 'after' tot 'secs, waiting for' info
        call sleep min(dly, 60)
        tot = tot + min(dly, 60)
        call readDsn cf, j.
        if j.0 ^== 1 then
            call err 'communicationFile' cf 'has' j.0 'records not 1'
        if ^ abbrev(j.1, mark' ') then
            call err 'communicationFile' cf 'should start with' mark,
                     'not' strip(j.1, 't')
        rst = strip(substr(j.1, length(mark)+2))' '
        upper rst
        if abbrev(rst, 'OK') then do
            say time() 'after' tot 'secs' info 'ended ok:' strip(j.1)
            return
            end
        if ^ abbrev(rst, 'SUBMIT') then
            call err info 'ended with error' strip(j.1, 't')
        else if tot >= tiOu then
            call err info 'timed out after' tot 'secs'
        end
    return
endProcedure job

mark: procedure expose m.
parse arg cf, mark, res
    o.1 = mark res
    say 'mark communicationfile' cf 'with' o.1
    call writeDsn cf '::F', o., 1, 1
    return
endProcedure mark

sleep: procedure expose m.
parse arg secs, sayIt
    if sayit <> 0 then
        say 'sleeping' secs 'secs' time()
    CALL SYSCALLS 'ON'
    ADDRESS SYSCALL "sleep" secs
    CALL SYSCALLS 'OFF'
    if sayit <> 0 then
        say 'slept' secs 'secs' time()
    return
endProcedure sleep
/* copy csm begin ******************************************************
    interface to csm,
        it is integrate with adrTso, eg. dsnAlloc , 'RZ3/..' uses csm
***********************************************************************/
adrCsm:
    return adrTso('csmExec' arg(1), arg(2))
endProcedure adrCsm

csmCopy: procedure expose m.
parse arg csnFr, csnTo, retOk
    if dsnGetMbr(csnTo) \= '' & dsnGetMbr(csnTo) \= '' then do
        if dsnGetMbr(csnFr) <> dsnGetMbr(csnTo) then
            call err 'member rename' csnFr 'to' csnTo
        csnTo = dsnSetMbr(csnTo)
        end
    parse value csmSysDsn(csnFr) with sysFr '/' dsnFr
    parse value csmSysDsn(csnTo) with sysTo '/' dsnTo
    if sysTo = '*' then do
        old = sysDsn("'"dsnTo"'")
        end
    else if sysFr = '*' then do
        pdsTo = dsnSetMbr(dsnTo)
        al = "SYSTEM("sysTo") DDNAME(COPYTo)",
             "DATASET('"pdsTo"') DISP(SHR)"
        alRes = dsnAlloc(systo'/'pdsTo, ,'COPYTO', '*')
        if datatype(alRes, 'n') then do
                   /* wir müssen es selbst allozieren csmxUtil
                      vergisst management class ||||| */
            say 'could not allocate' al
            say 'trying to create'
            rc = listDsi("'"dsnSetMbr(dsnFr)"' SMSINFO")
            if rc = 0 then
                mv = ''
            else if rc = 4 & sysReason = 19 then do
                mv = 'UCOUNT(30)' /* 7.8.13 corrected attribute */
                mv = 'UNITCNT(30)' /* 3.10.13 wieder zurueck */
                say 'creating' dsn 'with multi volume' mv
                end
            else if rc \= 0 then
                call err 'listDsi rc' rc 'reason' sysReason,
                                     sysMsgLvl1 sysMsgLvl2
            al = left(al, length(al)-4)'CAT)'
            if right(sysDsSms, 7) == 'LIBRARY' ,
                | abbrev(sysDsSms, 'PDS') then
                 al = al 'DSNTYPE(LIBRARY)'
            if sysUnits = 'TRACK' then
                sysUnits = 'TRACKS'
            al = al "DSORG("sysDSorg") MGMTCLAS("sysMgmtClass")",
                "RECFM("sysREcFM") LRECL("SYSLRECL")",
                "blksize("sysBLkSIZE")",
                "SPACE("sysPrimary"," sysSeconds")" sysUnits mv
            call adrCsm "allocate" al
            end
        call tsoFree word(alRes, 2)
        end
    c = "'COPY" sysFr"/''"dsnFr"'' TO" ,
                        sysTo"/''"dsnSetMbr(dsnTo)"'' REPLACE'"
    csmRc = adrTso("exec 'CSM.DIV.P0.EXEC(CSRXUTIL)'",
           c , retOk)
    if sysTo = '*' & old <> 'OK' then do
        /* csm normally does not set mgmtclass - avoid delete | */
        call adrTso "ALTER '"dsnTo"' mgmtclas(COM#A091)"
        end
    return csmRc
endProcedure csmCopy

csmAlloc: procedure expose m.
parse arg dsn dd disp rest ':' nn, retRc
    sys = ''
    a2 = ''
    parse value csmSysDsn(dsn) with sys '/' dsn
    if disp = '' then
        disp = 'shr'
    al = "SYSTEM("sys") DDNAME("dd")"
    if dsn <> '' then do
        a2 = "DATASET('"dsnSetMbr(dsn)"')"
        mbr = dsnGetMbr(dsn)
        if mbr <> '' then
            a2 = a2 'MEMBER('mbr')'
        end
    if abbrev(disp, 'SYSOUT(') then
        a2 = a2 disp
    else
        a2 = a2 "DISP("disp")"
    if disp = 'NEW' & nn \== '' then
        a2 = a2 dsnCreateAtts( , nn, 1)
    if retRc <> '' | nn = '' then
        return adrCsm('allocate' al a2 rest, retRc)
    do retry=0 by 1
        alRc = adrCsm('allocate' al a2 rest, '*')
        if alRc = 0 then
            return 0
        if retry > 0 | nn = '' | wordPos(disp, 'OLD SHR') < 1 then
            return err('cmsAlloc rc' alRc 'for' al rest)
        say 'csmAlloc rc' alRc 'for' al a2 rest '...trying to create'
        nn = al 'disp(cat)' dsnCreateAtts(dsn, nn, 1)
        call adrCsm 'allocate' nn
        call adrTso 'free  dd('dd')'
        end
endProcedure csmAlloc

csmSysDsn: procedure expose m.
parse upper arg dsn, withStar
    if pos('/', dsn) < 1 then
        sys = '*'
    else
        parse var dsn sys '/' dsn
    if sys <> '' & sys <> '*' & sys <> sysvar(sysnode) then
        return sys'/'dsn
    else if withStar == 0 then
        return dsn
    else
        return '*/'dsn
endProcedure csmSysDsn

/*--- execute a rexx (under tso) in another rz
           here we use rexx TPSYSIKJ which was written for
           jcl procedure RM@IKJ01
arguments
rz   which rz to run rexx
proc the (remote) procedure library to use
opt  options
cmd  the tso command to execute
----------------------------------------------------------------------*/
/*--- execute a rexx (under tso) in another rz
          directly (without TPSYSIKJ) --------------------------------*/
csmExRx: procedure expose m.
parse arg rz, proc, opt, cmd
    pStem = opt
    if pStem = '' then
        pStem ='CSMEXRX'
    do cx=1 to (length(cmd)-1) % 68
        cmd.cx = substr(cmd, 68*cx-67,68)'-'
        end
    cmd.cx = substr(cmd, 68*cx-67)
    cmd.0 = cx
    timeout = 11
    if 0 then do
        call adrTso  'free ed(rmtSys)'  ,'*'
        call tsoFree tsoDD(rmtsPrt, 'a')
        call adrTso  'free dd(rmtsIn)','*'
        call adrTso  'free dd(sysproc)' ,'*'
        end
    call dsnAlloc rz"/"proc "dd(rmSyPro) rmtDDn(sysProc)"
    call dsnAlloc rz"/tmp.tsin new dd(rmTsIn) rmtDdn(sysTsIn) ::f "
    call tsoOpen rmTsIn, 'w'
    call writeDD rmTsIn, cmd.
    call tsoClose rmtsin
    call dsnAlloc rz"/tmp.prt new dd(rmtsprt) rmtDdn(sysTsPrt)",
                    "::f133"
    call dsnAlloc rz"/tmp.rmt new dd(rmtSys) timeout("timeout")"
    call adrtso "csmappc start pgm(csmexec)" ,
           "parm('select tsocmd(''csmappc allocate plu(*.rmtSys)" ,
                 "tpname(sysikj) dealloc '')')",
           "timeout("timeOut")", '*'
    if rc <> 0 | appc_rc <> 0 then do
        ee = 'csm tso exec rc='rc 'appc_rc='appc_rc
        say ee
        say '  rexx rz='rz 'proc='proc 'opt='opt
        say '  cmd='cmd
        call csmappcRcSay ggTsoCmd
        call readDD 'rmTsPrt', 'M.'pStem'.'
        call tsoClose rmtsPrt
        say m.pStem.0 'tso output lines'
        do px=1 to m.pStem.0
            say ' ' strip(m.pStem.px, 't')
            end
        call err ee
        end
    if opt <> '' then do
        call readDD 'rmTsPrt', 'M.'pStem'.'
        call tsoClose rmtsPrt
        end
    call tsoFree rmSyPro rmtsPrt rmtSys rmtsIn
    return
/*--- sys the re and result variables from csmAppcRc -----------------*/
 csmappcRcSay: procedure expose appc_rc appc_reason appc_msg. ,
           appc_state_c appc_state_f
 parse arg cmd
     say 'rc='appc_rc 'reason='appc_reason ,
         'state_c='appc_state_c appc_state_f
     say '  for' cmd
     do ix=1 to appc_msg.0
         say ' ' appc_msg.ix
         end
     return appc_rc
 endProcedure csmappcRcSay
/* copy csm 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 expose m.
parse upper 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 expose m.
parse arg dsn .
    return "'"dsn"'"
endProcedure jcl2dsn

dsnSetMbr: procedure expose m.
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 expose m.
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:  tsoOpen...'R', readDD*,  tsoClose
        write: tsoOpen...'W', writeDD*, tsoClose

        readDD returns true if data read, false at eof
        do not forget that open is mandatory to write empty file|
***********************************************************************/

/*--- open dd for read (rw='R') or write (rw='W') --------------------*/
tsoOpen: procedure expose m.
parse upper arg dd, rw
    return adrTso('execio' 0 'disk'RW tsoDD(dd, 'o') '(open)')
return /* end tsoOpen */

/*--- close dd -----------------------------------------------------*/
tsoClose: procedure expose m.
    parse upper arg dd
    return adrTso('execio 0 diskW' dd '(finis)')
endProcedure tsoClose

/*--- 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 */

/*--- 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

/*--- readNx: read next line, using buffer ---------------------------*/
/*--- begin: allocate dsnSpec and ini ------------------------ -------*/
readNxBegin: procedure expose m.
    parse arg m, m.m.dsn, m.m.dd, m.m.Cnt
    if m.m.dd = '' then
        m.m.dd = 'DDNX*'
    if m.m.cnt = '' then
        m.m.cnt = 1000
    m.m.cx = m.m.cnt + 999
    m.m.buf0x = 0
    m.m.0 = 0
    parse value dsnAlloc('dd('m.m.dd')' m.m.dsn) with m.m.dd m.m.free
    call tsoOpen m.m.dd, 'R'
    return m
endProcedure readDDNxBegin

/*--- return the stem of the next line, or '' at end -----------------*/
readNx: procedure expose m.
parse arg m
    m.m.cx = m.m.cx + 1
    if m.m.cx <= m.m.0 then
        return m'.'m.m.cx
    m.m.buf0x = m.m.buf0x + m.m.0
    if \ readDD(m.m.dd, 'M.'m'.', m.m.cnt)then
        return ''
    m.m.cx = 1
    return m'.1'
endProcedure readDDNx
/*--- return the stem of the curr line, '' at end --------------------*/
readNxCur: procedure expose m.
parse arg m
    if m.m.cx <= m.m.0 then
        return m'.'m.m.cx
    else
        return ''
endProcedure readNxCur

/*--- return the position (line number) of reader
           plus le characters of the current line (default 50) ------*/
readnxPos: procedure expose m.
parse arg m, le
    li = m'.'m.m.cx
    li = strip(m.li, 't')
    if arg() < 2 then
        le = 50
    if le < 1 then
        li = ''
    else if length(li) <= le then
        li = ':' li
    else
        li = ':' left(li, le-3)'...'
    return 'line' (m.m.buf0x + m.m.cx)li
endProcedure readnxPos

/*--- close and deallocate ------------------------------------------*/
readNxEnd: procedure expose m.
parse arg m
    call tsoClose m.m.dd
    call tsoFree m.m.free
    return
endProcedure readDDNxEnd

/*--- standardise a dsn spec
       word1             dsName or -
       word2             dd     or -
       word3             disp   or -
       word4 to first :  attributes in tso format
       after first :     attributes for new allocation
----------------------------------------------------------------------*/
dsnSpec: procedure expose m.
parse upper arg spec
    rr = ''      /* put leading - in separate words */
    do sx=1 while words(rr) < 3 & wx \= ''
        wx = word(spec, sx)
        do while abbrev(wx, '-') & words(rr) < 3
            wx = substr(wx, 2)
            rr = rr '-'
            end
        rr = rr wx
        end
    spec = rr subWord(spec, sx)
    na = ''
    dd = ''
    di = ''
    if left(spec, 1) = '&' then /* external spec is handled ok */
        spec = strip(substr(spec, 2))
    do wx=1 by 1
        w = word(spec, wx)
        if w = '' | abbrev(w, '.') | abbrev(w, ':') then
            leave
        else if wordPos(w, 'OLD SHR MOD NEW')>0 | abbrev(w, 'SYSO') then
            di = w
        else if w = 'CATALOG' then
            di = di w
        else if abbrev(w, 'DD(') then
            dd = substr(w, 4, length(w)-4)
        else if abbrev(w, 'DSN(') then
            na = strip(substr(w, 5, length(w)-5))
        else if na == '' then
            na = dsn2jcl(w)
        else if pos('(', w) > 0 then
            leave
        else if dd == '' then
            dd = w
        else if di == '' then
            di = w
        else
            leave
        end
    if na == '' then
        na = '-'
    else if abbrev(na, "'") then
        na = substr(na, 2, length(na)-2)
    if dd == '' then dd = '-'
    if di == '' then di = '-'
    re = subword(spec, wx)
    if abbrev(re, '.') then
        re = substr(re, 2)
    return na dd di re
endProcedure dsnSpec

/*--- alloc a dsn with dsnAlloc
          if the dsn is inuse wait and retry
          until either the allocation is successfull
          or the timeout occurs --------------------------------------*/
dsnAllocWait: procedure expose m.
parse upper arg spec, pDi, pDD, timeOut
    x = max(1, arg() - 1)
    do rt=0
        m.adrTsoAl.1 = ''
        m.adrTsoAl.2 = ''
        m.adrTsoAl.3 = ''
        call outtrap m.adrTsoAl.
        res = dsnAlloc(spec, pDi, pDD, '*')
        call outtrap off
        if \ datatype(res, 'n') then
            return res
        msg = m.adrTsoAl.1'\n'm.adrTsoAl.2'\n'm.adrTsoAl.3
        if rt > timeOut & timeOut \== '' then
            return err('timeout allocating' spec time() '\n'msg)
        if pos('DATA SET IS ALLOCATED TO ANOTHER', msg) < 1 then
            return err('allocating' spec'\n'msg)
        say time() 'sleep and retry alloc' spec
        call sleep 1, 0
        end
endProcedure dsnAllocWait

/*--- alloc a dsn or a dd
          spec '-'<ddName>
               datasetName? disposition? '.'? attributes? (':' newAtts)?
          disp default disposition
          dd   default dd name
          retRc   erlaubte ReturnCodes (leer = 0)
          returns if ok then ddName <rexx for free> otherwise rc -----*/
dsnAlloc: procedure expose m.
parse upper arg spec, pDi, pDD, retRc
    parse value dsnSpec(spec) with na dd di rest
    if na = '-' then
        m.dsnAlloc.dsn = ''
    else
        m.dsnAlloc.dsn = na
    if dd == '-' & pDD \== '' then
        dd = pDD
    if dd == '-' then
        dd = 'DD*'
    dd = tsoDD(dd, 'a')
    if na == '-' & di == '-' & rest = '' then
        return dd
    if di = '-' then
        if pDi == '' then
            di = 'SHR'
        else
            di = pDi
    if pos('(', na) < 1 then
        nop
    else if di = 'MOD' then
        call err 'disp mod for' na
    else
        di = 'SHR'
    if pos('/', na) > 0 then
        rx = csmAlloc(na dd di rest, retRc)
    else
        rx = tsoAlloc(na dd di rest, retRc)
    if rx = 0 then
        return dd dd
    else
        return rx
endProcedure dsnAlloc

/*--- find a free dd with prefix dd ----------------------------------*/
tsoDD: procedure expose m.
parse arg dd, f
    if symbol('m.tso.ddAlloc') \== 'VAR' then do
        call errIni
        m.tso.ddAlloc = ''
        m.tso.ddOpen  = ''
        end
    if m.err.ispf then
        address ispExec 'vget wshTsoDD shared'
    else
        wshTsoDD = m.tso.ddAlloc
    if f == '-' then do
        ax = wordPos(dd, m.tso.ddAlloc)
        if ax > 0 then
            m.tso.ddAlloc = delWord(m.tso.ddAlloc, ax, 1)
        ox = wordPos(dd, m.tso.ddOpen)
        if ox > 0 then
            m.tso.ddOpen  = delWord(m.tso.ddOpen , ox, 1)
        if ax < 1 & ox < 1 then
            call err 'tsoDD dd' dd 'not used' m.tso.ddAlloc m.tso.ddOpen
        sx = wordPos(dd, wshTsoDD)
        if sx > 0 then
            wshTsoDD  = delWord(wshTsoDD , sx, 1)
        end
    else if f == 'o' then do
        if wordPos(dd, m.tso.ddOpen m.tso.ddAlloc) < 1 then
            m.tso.ddOpen = strip(m.tso.ddOpen dd)
        end
    else if f <> 'a' then do
        call err 'tsoDD bad fun' f
        end
    else do
        if right(dd, 1) = '*' then do
            dd = left(dd, length(dd)-1) || m.err.screen
            cx = lastPos(' 'dd, ' 'm.tso.ddAlloc)
            if cx > 0 then do
                old = word(substr(m.tso.ddAlloc, cx), 1)
                if old = dd then
                    dd = dd'1'
                else if datatype(substr(old, length(dd)+1), 'n') then
                    dd = dd || (substr(old, length(dd)+1) + 1)
                else
                    call err 'tsoDD old' old 'suffix not numeric dd' dd
                end
            end
        if wordPos(dd, m.tso.ddAlloc) < 1 then
            m.tso.ddAlloc = strip(m.tso.ddAlloc dd)
        if wordPos(dd, wshTsoDD) < 1 then
            wshTsoDD = strip(wshTsoDD dd)
        end
    if m.err.ispf then
        address ispExec 'vPut wshTsoDD shared'
    return dd
endProcedure tsoDD

tsoAlloc: procedure expose m.
parse arg na dd disp rest ':' nn, retRc
    c = 'alloc dd('dd')' disp
    if na \== '-' then
        c = c "DSN('"na"')"
    else if disp = 'NEW' and nn \== '' then
        c = c dsnCreateAtts(,nn)
    call outtrap m.adrTsoAl.
    alRc = adrTso(c rest, '*')
    call outtrap off
    if alRc =  0 then
        return 0
    if nn \= '' & wordPos(disp, 'OLD SHR') > 0 ,
          & sysDsn("'"m.dsnAlloc.dsn"'") == 'DATASET NOT FOUND' then do
        say 'tsoAlloc creating' c rest ':'nn
        call adrTso 'alloc dd('dd') new catalog' dsnCreateAtts(na, nn)
        call adrTso 'free  dd('dd')'
        return tsoAlloc(na dd disp rest, retRc)
        end
    say 'rc='alRc 'for' c rest
    call saySt adrTsoal
    if retRc = '*' | wordPos(alRc, retRc) > 0 then
        return alRc
    call err 'tsoAlloc rc' alRc 'for' c rest
endProcedure tsoAlloc

tsoAtts: procedure expose m.
parse arg dsn
    rc = listDsi("'"dsn"' SMSINFO")
    if rc = 0 then
        mv = ''
    else if rc = 4 & sysReason = 19 then do
        mv = 'UCOUNT(30)' /* 7.8.13 corrected attribute */
        say 'creating' dsn 'with multi volume' mv
        end
    else if rc ^= 0 then
        call err 'listDsi rc' rc 'reason' sysReason,
                             sysMsgLvl1 sysMsgLvl2
    al = 'CAT'
    al = ''
    if right(sysDsSms, 7) == 'LIBRARY' ,
        | abbrev(sysDsSms, 'PDS') then
         al = al 'DSNTYPE(LIBRARY)'
    if sysUnits = 'TRACK' then
        sysUnits = 'TRACKS'
    return al "DSORG("sysDSorg") MGMTCLAS("sysMgmtClass")",
        "DATACLAS("sysDataClass")" ,
        "RECFM("translate('1 2 3', ' 'sysREcFM, ' 123')")",
        "LRECL("SYSLRECL")",
        "SPACE("sysPrimary"," sysSeconds")" sysUnits mv
    /*  "blksize("sysBLkSIZE")" removed 3.4.13: let sms do the magic */
endProcedure tsoAtts

tsoFree: procedure expose m.
parse arg ddList, ggRet
    do dx=1 to words(ddList)
        dd = word(ddList, dx)
        call adrTso 'free dd('dd')', ggRet
        call tsoDD dd, '-'
        end
    return
endProcedure tsoFree

tsoFreeAll: procedure expose m.
    all = m.tso.ddAlloc m.tso.ddOpen
    do ax = 1 to words(all)
        call adrTso 'execio 0 diskW' word(all, ax) '(finis)', '*'
        end
    m.tso.ddOpen = ''
    call tsoFree m.tso.ddAlloc, '*'
    return
endProcedure tsoFreeAll

dsnCreateAtts: procedure expose m.
parse arg dsn, atts, forCsm
    forCsm = forCsm == 1
    aU = ' 'translate(atts)
    res = ''
    if dsn \== '' then
        res = "dataset('"dsnSetMbr(dsn)"')"
    if abbrev(atts, '~') then
        return res tsoAtts(substr(atts, 2))
    if abbrev(atts, ':') then do
        parse var atts a1 atts
        rl = substr(a1, 3)
        if abbrev(a1, ':F') then do
            if rl = '' then
                rl = 80
            recfm='f b'
            end
        else do
            if rl = '' then
                rl = 32756
            recfm = substr(a1, 2, 1) 'b'
            end
        res =  res "recfm("space(recfm, 1-forCsm)") lrecl("rl")"
        end
    if pos('(', dsn) > 0 & pos(' DSNTYPE(', aU) < 1 ,
                         & pos(' DSORG(',   aU) < 1 then
        res = res 'dsntype(library) dsorg(po)'
    if pos(' MGMTCLAS(', aU) < 1 then
        res = res 'mgmtclas(COM#A091)'
    if pos(' SPACE(', aU) < 1 then
        res = res 'space(100, 500) cyl' || copies('inder', forCsm)
    return res atts
endProcedure dsnCreateAtts
/*--- check if a dataset is archive ------------------------------------
          returns 'ok'                    if dataset on disk
                  'not'                   if dataset is not catalogued
                  'arc'                   if dataset archived
                  listDsi errorMsg        otherwise ------------------*/
dsnArc: procedure expose m.
parse upper arg dsn
    lc = listDsi("'"strip(dsn)"' noRecall")
    if lc = 0 then
        return 'ok'
    else if lc=4 & sysReason = 19 then  /* multiple volumes */
        return 'ok'
    else if lc=16 & sysReason = 5 then
        return 'notCat'
    else if lc=16 & sysReason = 9 then
        return 'arc'
    else
        return 'listDsi cc='lc', sysReason='sysReason ,
                          'm2='sysMsgLvl2', m1='sysMsgLvl1
endProcedure dsnArc
/*--- read the dataset specified in ggDsnSpec to stem ggSt -----------*/
readDSN:
parse arg ggDsnSpec, ggSt
    ggAlloc = dsnAlloc(ggDsnSpec, 'SHR', 'readDsN')
    call adrTso 'execio * diskr' word(ggAlloc, 1) '(stem' ggSt' finis)'
    call tsoFree word(ggAlloc, 2)
    return
endSubroutine readDsn

/*--- write the dataset specified in ggDsnSpec from stem ggSt
          write ggCnt records if not empty otherwise ggst0
          if ggSay 1 then say ... records written to ... -------------*/
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 'open finis)'
    call tsoFree word(ggAlloc, 2)
    if ggSay == 1 | m.debug == 1 then
       say ggCnt 'records written to' ggDsnSpec
    return
endSubroutine writeDsn

copyDSN: procedure expose m.
parse arg frSpec, toSpec, ggSay
    parse value dsnAlloc(frSpec, 'SHR', 'FRDD') with frDD frFr
    parse value dsnAlloc(toSpec, 'OLD', 'TODD') with toDD toFr
    call tsoOpen frDD, 'R'
    call tsoOpen toDD, 'W'
    cnt = 0
    do while readDD(frDD, r.)
        call writeDD toDD, r.
        cnt = cnt + r.0
        end
    call tsoClose frDD
    call tsoClose toDD
    call tsoFree frFr toFr
    if ggSay == 1 | m.debug == 1 then
       say cnt 'records copied from' frSpec 'to' to toSpec
    return
endSubroutine writeDsn
/* copy adrTso end ****************************************************/
/* copy err begin *** errorhandling, messages, help    ****************/
errIni: procedure expose m.
    if m.err.ini == 1 then
        return
    call utIni
    m.err.ini     = 1
    m.err.handler = ''
    m.err.cleanup = ';'
    m.err.opt     = ''
    parse source m.err.os .
    m.err.ispf    = 0
    m.err.screen  = 0
    if m.err.os \== 'LINUX' then
        if sysVar('sysISPF') = 'ACTIVE' then do
            m.err.ispf = 1
            address ispExec 'vget zScreen shared'
            m.err.screen = zScreen
            end
    return
endProcedure errIni

/* configure err -----------------------------------------------------*/
errReset: procedure expose m.
    call errIni
    parse arg m.err.opt, m.err.handler
    if pos('I', translate(m.err.opt)) > 0 & m.err.ispf then
        address ispExec 'control errors return'
    return
endSubroutine errReset

/*--- error routine: abend with message ------------------------------*/
err:
    parse arg ggTxt, ggOpt
    call errIni
    drop err handler cleanup opt call return
    if ggOpt == '' & m.err.handler \== '' then
        interpret m.err.handler
    call errSay 'f}'ggTxt
    call errCleanup
    if ggOpt == '' then
        ggOpt = m.err.opt
    upper ggOpt
    if pos('T', ggOpt) > 0  then do
        trace ?r
        say 'trace ?r in err'
        end
    if pos('H', ggOpt) > 0 & m.err.eCat == 'f' then do
        call errSay ' }errorhandler exiting with divide by zero' ,
                                   'to show stackHistory'
        x = 1 / 0
        end
    call errSay ' }errorhandler exiting with exit(12)'
    exit errSetRc(12)
endSubroutine err

/*--- set rc for ispf: -------------------------------------------------
    if a cmd is run by ispStart, its RC is ignored,
         but ISPF passes the value of the shared variable zIspfRc
         back as return code
----------------------------------------------------------------------*/
errSetRc: procedure expose m.
parse arg zIspfRc
    if m.err.ispf then
        address ispExec vput 'zIspfRc' shared
    return zIspfRc
endProcedure errSetRc

/*--- error routine: user message cleanup exit -----------------------*/
errAddCleanup: procedure expose m.
parse arg code
    call errIni
        /* concatenate backwards, then it is executed also backwards */
    m.err.cleanup = ';'code || m.err.cleanup
    return
endProcedure errAddCleanup

errRmCleanup: procedure expose m.
parse arg code
    call errIni
    cx = pos(';'code';', m.err.cleanup)
    if cx > 0 then
        m.err.cleanup = left(m.err.cleanup, cx) ,
                     || substr(m.err.cleanup, cx + length(code)+2)
    return
endProcedure errRmCleanup

errCleanup: procedure expose m.
    call errIni
    errCleanup = m.err.cleanup
    if errCleanup <> ';' then do
        m.err.cleanup = ';'
        say 'err cleanup begin' errCleanup
        interpret errCleanup
        say 'err cleanup end' errCleanup
        end
    if symbol('m.tso.ddAlloc') == 'VAR' then
        call tsoFreeAll
    return
endProcedure errCleanup

/*--- say an errorMessage msg with pref and linesplits --------------*/
errSay: procedure expose m.
parse arg msg
    return saySt(errMsg(msg))

/*--- prefix an errormessage with pref,
          split it into lines at \n to stem m.err -------------------*/
errMsg: procedure expose m.
parse arg msg
    m.err.eCat = 'f'
    do while substr(msg, 2, 1) == '}'
        parse var msg m.err.eCat '}' msg
        end
    res = msg
    if m.err.eCat <> '' then do
       pTxt = ',error,fatal error,input error,s-}scanErr,warning,'
 /*    pTxt = ',error,fatal error,input error,syntax error,warning,' */
       px = pos(','m.err.eCat, pTxt)
       if px < 1 then do
           m.err.eCat = 'f'
           px = pos(','m.err.eCat, pTxt)
           end
       res = substr(pTxt, px+1, pos(',', pTxt, px+2)-px-1)
       if substr(res, 3, 1) == '}' then
           parse var res 2 opt 3 br 4 res
       if opt == '-' then
           res = res msg
       else do
           parse source . . s3 .              /* current rexx */
           res = res 'in' s3':' msg
           end
       end
    return splitNl(err, res)           /* split lines at \n */
endProcedure errMsg

splitNL: procedure expose m.
parse arg st, msg
    bx = 1
    do lx=1 to 20
        ex = pos('\n', msg, bx)
        if ex < bx then
            leave
        m.st.lx = substr(msg, bx, ex-bx)
        bx = ex+2
        end
    m.st.lx = substr(msg, bx)
    m.st.0 = lx
    return st
endProcedure splitNL

/*--- say (part of) the lines of a stem ----------------------------*/
saySt: procedure expose m.
parse arg st, fx, tx
    do lx=word(fx 1, 1) to word(tx m.st.0, 1)
        say m.st.lx
        end
    return st
endProcedure saySt

/*--- out (part of) the lines of a stem ----------------------------*/
outSt: procedure expose m.
parse arg st, fx, tx
    do lx=word(fx 1, 1) to word(tx m.st.0, 1)
        call out m.st.lx
        end
    return st
endProcedure outSt

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

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

/*--- assert that the passed rexx expression evaluates to true -------*/
assert:
    interpret 'if ('arg(1)') == 1 then return 1'
    interpret 'call err' quote('assert failed' arg(1) ':' arg(2) '==>'),
                        arg(2)
endProcedure assert

/*--- abend with Message after displaying help -----------------------*/
errHelp: procedure expose m.
parse arg msg
    call errSay 'i}'msg
    call help 0
    call err 'i}'msg
endProcedure errHelp

/*--- display the first comment block of the source as help ----------*/
help: procedure expose m.
parse arg doClear
    if doClear \== 0 then
        address tso 'clear'
    parse source . . s3 .
    say right(' help for rexx' s3, 72, '*')
    do lx=1 while pos('/*', sourceLine(lx)) < 1
        if lx > 10 then
            return err('initial commentblock not found for help')
        end
    doInc = 1
    ho = m.err.helpOpt
    do lx=lx+1 to sourceline() while pos('*/', sourceline(lx)) = 0
        li = strip(sourceLine(lx), 't')
        cx = lastPos('{', li)
        if cx > 0 then do
            if length(ho) = 1 then
                doInc = cx = length(li) | pos(ho, li, cx+1) > 0
            li = left(li, cx-1)
            end
        if doInc then
            say li
        end
    say right(' end help for rexx' s3, 72, '*')
    return 4
endProcedure help

/* copy err end   *****************************************************/
/* copy ut begin  *****************************************************/
utIni: procedure expose m.
    if m.ut_ini == 1 then
        return
    m.ut_ini = 1
    m.ut_digits = '0123456789'
    m.ut_alfLC  = 'abcdefghijklmnopqrstuvwxyz'
    m.ut_alfUC  = translate(m.ut_alfLc)
    m.ut_Alfa   = m.ut_alfLc || m.ut_alfUC
    m.ut_alfNum = m.ut_alfa || m.ut_digits
    m.ut_alfDot = m.ut_alfNum || '.'
    m.ut_alfId  = m.ut_alfNum'_' /* avoid rexx allowed @ # $ ¬ . | ? */
    m.ut_alfIdN1 = m.ut_digits    /* not as first character */
    m.ut_rxId   = m.ut_AlfNum'@#$?' /* charset puff mit ¬*/
    m.ut_rxDot  = '.'m.ut_rxId
    m.ut_rxN1   = '.0123456789'
    m.ut_alfPrint = m.ut_alfNum'+-*/=()[]{}<> .:,;?|''"%&#@$£\_'
    return
endProcedure utIni
/*--- if function  warning all3 arguments get evaluated|
                   e.g if(x=0, 'infinity', 1/0) will fail| -----------*/
if: procedure expose m.
parse arg co, ifTrue, ifFalse
    if co then
        return ifTrue
    else
        return ifFalse
endProcedure if
/*--- embedded ASSignement:
      assign the second argument to the variable with name in first arg
      and return the value assigned ----------------------------------*/
ass:
    call value arg(1), arg(2)
    return arg(2)
/*--- embedded ASSignement return NotNull:
      assign the second argument to the variable with name in first arg
      and return 1 if value not null, 0 if null ----------------------*/
assNN:
    call value arg(1), arg(2)
    return arg(2) \== ''

/*--- return current time and cpu usage ------------------------------*/
utTime: procedure expose m.
    return time() 'ela='time('E') 'cpu='sysvar('syscpu'),
            'su='sysvar('syssrv')

tstUtTime: procedure expose m.
    say 'begin' utTime()  sysvar('sysnode')
    do 3000000
       end
    say 'end  ' utTime()
return

/*--- sleep several seconds ------------------------------------------*/
sleep: procedure expose m.
parse arg secs, sayIt
    if sayit <> 0 then
        say 'sleeping' secs 'secs' time()
    CALL SYSCALLS 'ON'
    ADDRESS SYSCALL "sleep" secs
    CALL SYSCALLS 'OFF'
    if sayit <> 0 then
        say 'slept' secs 'secs' time()
    return
endProcedure sleep

/*--- left without truncation ----------------------------------------*/
lefPad: procedure expose m
parse arg s, len
    if length(s) >= len then
        return s
    return left(s, len)
endProcedure lefPad

/*--- right without truncation ---------------------------------------*/
rigPad: procedure expose m
parse arg s, len
    if length(s) >= len then
        return s
    return right(s, len)
endProcedure rigPad

/*--- quote string txt using quoteChar qu ("" ==> ") -----------------*/
quote: procedure expose m.
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

/*--- translate to lowercase -----------------------------------------*/
ut2lc: procedure expose m.
parse arg s
    return translate(s, m.ut_alfLc, m.ut_alfUc)

/*--- verify an id ---------------------------------------------------*/
verifId: procedure expose m.
    parse arg src, extra
    if pos(left(src, 1), m.ut_alfIdN1) > 0 then
        return 1
    else
        return verify(src, m.ut_alfId || extra, 'n')

/*--- return the count of occurrences of needle in heyStack ----------*/
posCount: procedure expose m.
parse arg needle, hayStack, start, fin
    if start = '' then
        start = 1
    if fin = '' then
        fin = length(hayStack) + 1 - length(needle)
    do cnt = 0 by 1
        start = pos(needle, haystack, start)
        if start < 1 | start > fin then
             return cnt
        start = start + length(needle)
        end
endProcedure posCount

repAll: procedure expose m.
parse arg src
    do ax = 2 by 2 to arg()
        src = repAl2(src, src, arg(ax), arg(ax+1))
        end
    return src
endProcedure repAll

repAl2: procedure expose m.
parse arg src, sPos, old, new
    res = ''
    cx = 1
    do forever
        nx = pos(old, sPos, cx)
        if nx < 1 then
            return res || substr(src, cx)
        res = res || substr(src, cx, nx-cx) || new
        cx = nx + length(old)
        end
endProcedure repAl2

repAllWords: procedure expose m.
parse arg src, w, new
    res = ''
    wx = 0
    cx = 1
    do forever
        wx = wordPos(w, src, wx+1)
        if wx < 1 then
            return res || substr(src, cx)
        nx = wordindex(src, wx)
        res = res || substr(src, cx, nx-cx) || new
        cx = nx + length(w)
        end
endProcedure repAllWords
tstUtc2d: procedure expose m.
numeric digits 33
say c2d('ffffff'x)
say utc2d('ffffff'x)
say utc2d('01000000'x)    256*256*256
say utc2d('01000001'x)
say utc2d('020000FF'x)    256*256*256*2+255
say utc2d('03020000EF'x)    256*256*256*770+239
return
endProcedure tstUtc2d
utc2d: procedure expose m.
parse arg ch
    cx = length(ch) // 3
    if cx = 0 then
        cx = 3
    res = c2d(left(ch, cx))
    do cx=cx+1 by 3 to length(ch)
        res = res * 16777216 + c2d(substr(ch, cx, 3))
        end
    return res
/* copy ut end ********************************************************/