zOs/REXX/CHKSTART

/* rexx                  chkStart   */
parse arg aa
call errReset
/* parse value 'ANA DSN.DBXDBAF.ANA(WK40300T)' with fun ddl */
say 'chkStart version 1.1'
fun = ''
ofAna = ''
do wx=1 to words(aa)
    w1 = translate(word(aa,wx))
    if abbrev(w1, 'DBSYS=') then
        dbSys = substr(w1, 7)
    else if abbrev(w1, 'DDL=') then
        ddl = substr(w1, 5)
    else if abbrev(w1, 'ANA=') | abbrev(w1, 'REC=') then do
        if fun \== '' then
            call err 'duplicate clause' w1 'in' aa
        fun = left(w1, 3)
        ana = substr(w1, 5)
        wx = wx+1
        tst = tst2db2(word(aa, wx))
        end
    else if abbrev(w1, 'OF=') then do
        if ofAna \== '' then
            call err 'duplicate clause' w1 'in' aa
        ofAna = substr(w1, 4)
        wx = wx+1
        ofTst = word(aa, wx)
        end
    else
        call err 'bad clause' w1 'in' aa
    end
say 'fun='fun 'dbsys='dbSys 'ddl='ddl
say 'ana='ana 'tst='tst
if fun == 'REC' then do
    if ofAna == '' then
        call err 'of missing in' aa
    say 'ofAna' ofAna ofTst
    ofTst = tst2db2(ofTst, 'bad of timestamp in args')
        call err 'bad ofTimestamp' ofTst 'in' aa
    end
else if fun \== 'ANA' then
    call err 'ana or rec missing in' aa
if pos('.', ana) > 0 then
    parse var ana anaC '.' anaN
else
    parse var ana anaN   anaC
if anaN \== dsnGetMbr(ddl) then
    call err 'analysis' anaN '<> mbr of' ddl
staF = listFile(start)
say 'start dd ==>' staF
tt = 'DSN.DBY'dbSys'.'left(anaN, 7)'.START'
if staF \== tt then
    call err 'dd start' staF '<>' tt
call readDDBegin start
call readDD start, 'M.I.'
call readDDEnd   start
say 'start' m.i.0 'lines'
curTst = tst2db2(date('s') time())
do ix=1 to m.i.0 while m.i.ix = ''
    end
if ix <= m.i.0 then do
    parse var m.i.ix lSt lFu lAn lAnT .
    lSt = tst2db2(lSt, 'bad startTst' lSt 'in' ix':' m.i.ix)
    if wordPos(translate(lFu), 'ANA REC') < 1 then
        call err 'bad fun' lFu 'in' ix':' m.i.ix
    if length(lAn) <> 8 | left(lAn, 7) <> left(anaN, 7) then
        call err 'bad ana' lAn 'not' left(anaN, 7)'?' 'in' ix':' m.i.ix
    lAnt = tst2Db2(lAnT,'bad anaTimstamp' lAnT 'in' ix':' m.i.ix)
    say 'last start' lSt 'ana' lAn lAnT
    if fun == 'REC' & (ofAna \== lAn | ofTst \== lAnT) then
        call err 'recovery on different analysis'
    if lSt >= tst then
        if tst = lAnT & lAn = anaN then
            call err 'start of same analysis without reAnalyse:' ,
                     ana tst
        else
            call err 'last start' lSt 'ana' lAn lAnT ,
                 'was after analysis time' tst 'of' ana
    end
m.o.1 = curTst fun anaN tst
if fun == 'REC' then
    m.o.2 =  '    of' ofAna ofTst
m.o.0 = 1 + (fun = 'REC')
call mAddSt o, i, ix
call writeDDBegin start
call writeDD start, 'M.O.'
call writeDDEnd start
say 'chkStart registered start at' curTst 'ana' anaN tst
exit

tst2db2: procedure expose m.
parse arg i, eMsg
    t = 'yz34-56-78-hi.mn.st'
    t3 =  '34-56-78-hi.mn.st'
    j = translate(i, '999999999', '012345678')
    if abbrev('999999:999999.9', j, 7) then
        return '20'translate(t3'.a' ,
             , i || substr('000000.0', length(i)-6), '345678:himnst.a')
    else if abbrev('9999-99-99-99.99.99.9999999999', j, 19) then
        return i
    else if j == '99999999 99:99:99' then
        return translate(t, i, 'yz345678 hi:mn:st')
    else if j == '99/99/99 99:99' then
        return '20'translate(left(t3, 14), i, '56/78/34 hi:mn')'.00'
    else if eMsg == '-' then
        return '-'
    else if eMsg == '' then
        call err 'bad timestamp' i
    else
        call err eMsg
endProcedure tst2db2

listFile: procedure expose m.
parse upper arg fi
    sysDSName = '???'
    lc = listDsi(fi "file")
    if lc = 0 then
        return sysDSName
 /* 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
        call err 'listDsi cc='lc', sysReason='sysReason ,
                          'm2='sysMsgLvl2', m1='sysMsgLvl1
endProcedur listFile

/* copy m begin ********************************************************
  we use variables as follows
    m. stem m: all global data and object data that must survive
               a procedure call  (m for memory in Memoria of B5000)
        m.<mbr>.** to avoid conflicts: every rexx Module (copy) should
               only allocate addresses m.<mbr>.** with <mbr> the name of
               the rexx module
        we pass parameters around (e.g. a=address, m=memory, st=stem)
            and the called function may use m.a or m.a.subField etc.
    gg*: local variable in subroutines without procedure
    everything else: temporary data within procedure

  every subroutine is declared as procedure expose m.
        (also if no m. variable is used, because e.g. of error handling)
  the few subroutines that cannot use procedure, should use only
        variables starting with gg
***********************************************************************/
/*---make an area -----*/

mNewArea: procedure expose m.
parse arg nm, adr, newCd, freeCd
    m.m.area.0 = m.m.area.0 + 1
    a = 'M.AREA.'m.m.area.0
    if adr == '=' then
        adr = nm
    else if adr == '' then
        adr = 'M.'m.m.area.0
    if symbol('m.m.n2a.adr') == 'VAR' then
        call err 'adr' adr 'for area' nm 'already used'
    m.m.n2a.adr = a
    call mAlias adr, nm
    m.m.p2a.adr = a

    m.a.0 = 0
    m.a.free.0 = 0
    m.a.address = adr
    m.a.newCode = newCd
    m.a.freeCode = freeCd
    return nm
endProcedure mNewArea

mAlias: procedure expose m.
parse arg oldNa, newNa
    if symbol('m.m.n2a.oldNa') \== 'VAR' then
        call err 'area' oldNa 'does not exist'
    if oldNa == newNa then
        return
    if symbol('m.m.n2a.newNa') == 'VAR' then
        call err 'newName' newNa 'for old' oldNa 'already used'
    m.m.n2a.newNa = m.m.n2a.oldNa
    return
endProcedure mAlias

mBasicNew: procedure expose m. ggArea
parse arg name
    if symbol('m.m.n2a.name') \== 'VAR' then
        call err 'area' name 'does not exists'
    ggArea = m.m.n2a.name
    if m.ggArea.free.0 > 0 then do
        fx = m.ggArea.free.0
        m.ggArea.free.0 = fx-1
        m = m.ggArea.free.fx
        end
    else do
        m.ggArea.0 = m.ggArea.0 + 1
        m = m.ggArea.address'.'m.ggArea.0
        end
    return m
endProcedure mBasicNew

mNew: procedure expose m.
labelMNew:
parse arg name, arg, arg2, arg3
    m = mBasicNew(name)
    interpret m.ggArea.newCode
    return m
endProcedure mNew

mReset: procedure expose m.
parse arg a, name
    ggArea = m.m.n2a.name
    m = a
    interpret m.ggArea.newCode
    return m
endProcedure mReset

mFree: procedure expose m.
parse arg m
    p = 'M.P2A.'left(m, lastPos('.', m)-1)
    area = m.p
    if m.area.freeCode \== '' then
        interpret m.area.freeCode
    fx = m.area.free.0 + 1
    m.area.free.0 = fx
    m.area.free.fx = m
    return
endProcedure mFree
/*--- iterate over all allocate elements of an area ------------------*/
mIterBegin: procedure expose m.
parse arg nm
    a = m.m.n2a.nm
    return m.a.address'.0'
endProcedure mIterBegin

mIter: procedure expose m.
parse arg cur
    if cur == '' then
        return ''
    lx = lastPos('.', cur)
    p = 'M.P2A.'left(cur, lx-1)
    a = m.p
    ix = substr(cur, lx+1)
    do ix=ix+1 to m.a.0
        n = m.a.address'.'ix
        do fx=1 to m.a.free.0 while m.a.free \== n
            end
        if fx > m.a.free.0 then
            return n
        end
    return ''
endProcedure mIter

/*--- get m.a --------------------------------------------------------*/
mGet: procedure expose m.
parse arg a
    return m.a
endProcedure mGet

/*--- cut stem a to length len ---------------------------------------*/
mCut: procedure expose m.
parse arg a, len
    m.a.0 = len
    return a
endProcedure mCut

/*--- add one or several arguments to stem m.a -----------------------*/
mAdd: procedure expose m.
parse arg a
    ix = m.a.0
    do ax = 2 to arg()
        ix = ix + 1
        m.a.ix = arg(ax)
        end
    m.a.0 = ix
    return a'.'ix
endProcedure mAdd

/*--- pop last element from stem m.a ---------------------------------*/
mPop: procedure expose m.
parse arg a
    ix = m.a.0
    if ix < 1 then
        call err 'pop from empty stem' a
    m.a.0 = ix-1
    return m.a.ix
endProcedure mPop

/*--- add to m.dst.* a (sub)sequence of m.src.* ----------------------*/
mAddSt: procedure expose m.
    parse arg dst, src, fx , tx
    dx = m.dst.0
    if fx == '' then
        fx = 1
    if tx == '' then
        tx = m.src.0
    do sx = fx to tx
        dx = dx + 1
        m.dst.dx = m.src.sx
        end
    m.dst.0 = dx
    return
endProcedure mAddSt

/*--- find position of first occurrence of ele in stem m,
        return 0 if nonemove a part of a stem -----------------------*/
mPos: procedure expose m.
parse arg m, ele, sx
    if sx == '' then
        sx = 1
    do x=sx to m.m.0
        if m.m.x = ele then
            return x
        end
    return 0
endProcedure mPos

/*--- move a part of a stem ------------------------------------------*/
mMove: procedure expose m.
parse arg m, sx, dx
    if dx < sx then do
        y = dx
        do x=sx to m.m.0
            m.m.y = m.m.x
            y = y + 1
            end
        end
    else if dx > sx then do
        y = m.m.0 + dx - sx
        do x=m.m.0 by -1 to sx
            m.m.y = m.m.x
            y = y - 1
            end
        end
    m.m.0 = m.m.0 + dx - sx
    return
endProcedure mMove

/*--- insert a stem into another ------------------------------------*/
mInsert: procedure expose m.
parse arg m, tx, st
    call mMove m, tx, tx+m.st.0
    do sx=1 to m.st.0
        dx = tx-1+sx
            m.m.dx = m.st.sx
            end
    return
endProcedure mInsert

/*--- strip all elements of a stem -----------------------------------*/
mStrip: procedure expose m.
parse arg st, opt
    if opt == '' then
        opt = 'b'
    do x=1 to m.st.0
        m.st.x = strip(m.st.x, opt)
        end
    return st
endProcedure mStrip


/* cat the lines of a stem, possibly repeated --------------------------
       args: stem, fmt see fGen: -------------------------------------*/
mCat: procedure expose m.
parse arg st, fmt
    fmt = '%s%qn%s%qe%q^'fmt
    if m.st.0 < 1 then
        return ''
    res = f(fmt, m.st.1)
    do sx=2 to m.st.0
        res = res || f(fmt'%Qn', m.st.sx)
        end
    return res || f(fmt'%Qe')
endProcedure mCat

mIni: procedure expose m.
    if m.m.ini = 1 then
        return
    m.m.ini = 1
    m.mDigits = '0123456789'
    m.mAlfLC  = 'abcdefghijklmnopqrstuvwxyz'
    m.mAlfUC  = translate(m.mAlfLC)
    m.mAlfa   = m.mAlfLC || m.mAlfUC
    m.mAlfNum = m.mAlfa || m.mDigits
    m.mAlfDot = m.mAlfNum || '.'
    m.mBase64 = m.mAlfUC || m.mAlfLC || m.mDigits'+-'
    m.mId     = m.mAlfNum'_'   /* avoid rexx allowed @ # $ ¬ . | ? */
    m.mAlfRex1 = m.mAlfa'@#$?'  /* charset problem with ¬|  */
    m.mAlfRexR = m.mAlfRex1'.0123456789'
    m.mPrint = m.mAlfNum'+-*/=()[]{}<> .:,;?|''"%&#@$£\_'
    m.m.area.0 = 0
    call mNewArea
    return
endProcedure mIni

verifId: procedure expose m.
    parse arg src, extra, sx
    if sx == '' then
        sx = 1
    if pos(substr(src, sx, 1), m.mDigits) > 0 then
        return sx
    else
        return verify(src, m.mId || extra, 'n', sx)
endProcedure verifId

/* copy m 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:  readDDBegin, readDD*,  readDDEnd
        write: writeBegin,  writeDD*, writeEnd

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

/*--- prepare reading from a DD --------------------------------------*/
readDDBegin: procedure expose m.
    parse upper arg ggDD
    call errAddCleanup 'call readDDEnd' ggDD', "*"'
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 expose m.
    parse upper arg ggDD, ggRet
    call errRmCleanup 'call readDDEnd' ggDD', "*"'
    return adrTso('execio 0 diskr' ggDD '(finis)', ggRet)
endProcedure readDDEnd

/*--- prepare writing to DD ggDD -------------------------------------*/
writeDDBegin: procedure expose m.
    parse upper arg ggDD
                  /* ensure file is erased, if no records are written */
    call adrTso 'execio' 0 'diskw' ggDD '(open)'
    call errAddCleanup 'call writeDDEnd' ggDD', "*"'
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 expose m.
parse upper arg ggDD, ggRet
    call errRmCleanup 'call writeDDEnd' ggDD', "*"'
    return adrTso('execio 0 diskw' ggDD '(finis)', ggRet)
endProcedure writeDDEnd

/*--- 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
    m.m.free = subword(dsnAlloc('dd('m.m.dd')' m.m.dsn), 2)
    call readDDBegin m.m.dd
    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 readDDEnd m.m.dd
    interpret 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 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 \ abbrev(res, ' ') 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 na == '-' & dd \== '-' & di == '-' & rest = '' then
        return dd
    if dd == '-' & pDD \== '' then
        dd = pDD
    if dd == '-' then do
        if symbol('m.adrTso.ddNum') = 'VAR' then
            dd = m.adrTso.ddNum + 1
        else
            dd = 1
        m.adrTso.ddNum = dd
        dd = 'DD' || dd
        end
    if di = '-' & pDi \== '' then
        di = pDi
    if di = '-' then
        di = 'SHR'
    else 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
        return csmAlloc(na dd di rest, retRc)
    else
        return tsoAlloc(na dd di rest, retRc)
endProcedure dsnAlloc

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 do
        call errAddCleanup 'call tsoFree' dd', "*"'
        return dd 'call tsoFree' dd';'
        end
    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
    do ax=1 to m.adrTsoAl.0
        say m.adrTsoal.ax
        end
    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 = 'UNITCNT(30)'
        say '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'
    al = al "DSORG("sysDSorg") MGMTCLAS("sysMgmtClass")",
        "DATACLAS("sysDataClass")" ,
        "RECFM("translate('1 2 3', ' 'sysREcFM, ' 123')")",
        "LRECL("SYSLRECL")",
        "blksize("sysBLkSIZE")",
        "SPACE("sysPrimary"," sysSeconds")" sysUnits mv
    return al
endProcedure tsoAtts

tsoFree: procedure expose m.
parse arg dd, ggRet
    call adrTso 'free dd('dd')', ggRet
    call errRmCleanup 'call tsoFree' dd', "*"'
    return
endProcedure tsoFree

dsnCreateAtts: procedure expose m.
parse arg dsn, atts, forCsm
    forCsm = forCsm == 1
    aU = ' 'translate(atts)
    if abbrev(atts, ':') then do
        parse var atts a1 atts
        bl = 32760
        rl = substr(a1, 3)
        if abbrev(a1, ':F') then do
            if rl = '' then
                rl = 80
            recfm='f b'
            bl = bl - (bl // rl)
            end
        else do
            if rl = '' then
                rl = bl-4
            recfm = substr(a1, 2, 1) 'b'
            end
        if forCsm then
            atts =  atts "recfm("space(recfm, 0)") lrecl("rl")",
                    "blkSize("bl")"
        else
            atts = atts "recfm("recfm") lrecl("rl") block("bl")"
        end
    if pos('(', dsn) > 0 & pos(' DSNTYPE(', aU) < 1 ,
                         & pos(' DSORG(',   aU) < 1 then
        atts = atts 'dsntype(library) dsorg(po)'
    if pos(' MGMTCLAS(', aU) < 1 then
        atts = atts 'mgmtclas(COM#A091)'
    if pos(' SPACE(', aU) < 1 then
        if forCsm then
            atts = atts 'space(10, 1000) cylinder'
        else
            atts = atts 'space(10, 1000) cyl'
    if dsn == '' then
       return atts
    return "dataset('"dsnSetMbr(dsn)"')" atts
endProcedure dsnCreateAtts

/*--- 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)'
    interpret subword(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)'
    interpret subword(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
    frDD = dsnAlloc(frSpec, 'SHR', 'FRDD')
    toDD = dsnAlloc(toSpec, 'OLD', 'TODD')
    call readDDBegin word(frDD, 1)
    call writeDDBegin word(toDD, 1)
    cnt = 0
    do while readDD(word(frDD, 1), r.)
        call writeDD word(toDD, 1), r.
        cnt = cnt + r.0
        end
    call readDDEnd word(frDD, 1)
    call writeDDEnd word(toDD, 1)
    interpret ';' subword(frDD, 2) '; ; ;' subword(toDD, 2)
    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
    m.err.ini     = 1
    m.err.handler = ''
    m.err.cleanup = ';'
    m.err.opt     = ''
    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 then
        if errOS() \== 'LINUX' then
            if sysVar('sysISPF') = 'ACTIVE' then
                    call adrIsp '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 ggTxt, 'e'
    call errCleanup
    if ggOpt == '' then
        ggOpt = m.err.opt
    ggOpt = translate(ggOpt)
    if pos('T', ggOpt) > 0  then do
        trace ?r
        say 'trace ?r in err'
        end
    if pos('H', ggOpt) > 0  then do
        call errSay 'divide by zero to show stackHistory', 'e'
        x = 1 / 0
        end
    call errSay 'exit(12)', 'e'
    exit errSetRc(12)
endSubroutine err

/*--- return the Operating System we are running on: TSO or LINUX ---*/
errOS: procedure expose m.
    parse source os .
    return os
endProcedure errOS

/*--- 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 errOS() \== 'LINUX' then
        if sysVar('sysISPF') = 'ACTIVE' 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
        return
    m.err.cleanup = ';'
    say 'err cleanup begin' errCleanup
    interpret errCleanup
    say 'err cleanup end' errCleanup
    return
endProcedure errCleanup

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

/*--- prefix an errormessage with pref,
          split it into lines at \n to stem m.err -------------------*/
errMsg: procedure expose m.
parse arg msg, pref
    parse source . . ggS3 .                           /* current rexx */
    if pref == 'e' then
        msg = 'fatal error in' ggS3':' msg
    else if pref == 'w' then
        msg = 'warning in' ggS3':' msg
    else if pref \== '' then
        msg = pref':' msg
    return splitNl(err, msg)           /* 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 'assertRes =' arg(1)
    if assertRes \==1 then
        call err 'assert failed' arg(1) '==>' assertRes':' arg(2)
    return
endProcedure assert

/*--- abend with Message after displaying help -----------------------*/
errHelp: procedure expose m.
parse arg msg, op
    call errSay msg, 'e'
    call help
    call err msg, op
endProcedure errHelp

/*--- display the first comment block of the source as help ----------*/
help: procedure expose m.
    parse source . . s3 .
    say right(' help for rexx' s3, 79, '*')
    do ax=1 to arg()
        say ' ' arg(ax)
        end
    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   *****************************************************/