zOs/REXX.O08/DBACHECK

/* rexx ****************************************************************
synopsis:     DBACHECK

edit macro to enforce CS defaults for DB2:

    createTablespace          createIndex
      stoGroup GSMS            stoGroup GSMS
      priQty     -1            priQty     -1
      secQty     -1            secQty     -1
      compress  YES            copy       NO
      segSize    64                              falls nicht part or LOB
      dssize    32G                              falls partitioniert
      large    entfernen
************************************************************************
13.11.2008 w. keller kein Absturz auf leerem input
          end of help */ /*
25.09.2008 w. keller geht auch für CDL und PartitonenAttribute
26.06.2008 w. keller scanner geht über recordGrenzen
26.06.2008 w. keller create auf last Line und  -  1 gehen jetzt
11.12.2007 w. keller dsSize 32G
26.11.2007 w. keller priqty/secQty immer auf -1
24.09.2007 w. keller priqty/secQty < 1 auf -1 übersetzen
13.07.2007 w. keller remove large option in create tablespace
09.02.2007 w. keller remove // dd * lines if first line is not jcl
07.02.2007 w. keller dssize
05.02.2007 w. keller neu erstellt

toDo & Ideas
    load data auf resume no replace umstellen, wegen RTS?
    bekommt edit error, wenn letztes Zeile mit ; --> testCase
***********************************************************************/
parse arg args
    call errReset 'h'
    if pos('?', args) > 0 then
        exit help()
    call adrIsp 'control errors return'
    if args = '' then
        if adrEdit('macro (args)', '*') <> 0 then
            exit errHelp('please run as edit macro')
    call adrEdit "(cn) = linenum .zl", 4
    if cn < 1 then
        exit 0
    /* call adrEdit 'setUndo on' nützt nicht, initMacro kann
                                 nicht undo't werden ... */
    m.debug = 0          /* debug output */
    m.cdl = isCdl()
    call debug 'isCdl' m.cdl
    call jIni
    call overrideTree mapReset(os, 'k')
    if m.debug then
        call overrideTreeShow os
    call scanWinIni
    call editReadIni
    call editReadReset oMutate(er, 'EditRead'), 1
    call scanSqlReset oMutate(es, 'ScanWin'), er
    if m.cdl then
        call scanWinOpts es, 5, 2, 9, 72
    lx = 0
    m.an.0 = 0
                        /* jedes create suchen und analysieren -> an */
    do forever
        lx = seekId(es, lx+1, 'CREATE')
        call debug 'seek found CREATE at' lx scanPos(es)
        if lx < 1 then
            leave
        call analyseCreate es, os, an
        end
    if m.debug then
        call anaShow an
    m.wr.0 = 0
                        /* overrides und adds bestimmen -> wr */
    call override an, wr
    if m.debug then
        do y=1 to m.wr.0
           w = wr'.'y
           say 'over' m.w.fPos '-' m.w.tPos '=' m.w
           end
    oCnt = m.wr.0
    ddSt = findDDStar(0)
    say oCnt 'overrides and' ddSt '//DD*'
    if (oCnt + ddSt) <= 0 then
        exit 0
    if args ^= 'dbaMulti' then do
        call applyOverrides wr          /* apply to edited file */
        if ddSt > 0 then
            call findDDStar 1
        exit 0
        end
    do forever                          /* Benutzer muss entscheiden */
        say 'bitte wählen Sie'
        say '   m = multiClone ohne overrides'
        say '   o = override Werte, save und end'
        say '   e = edit override Werte'
        say '   f = edit ohne override'
        parse upper pull w
        w = left(strip(w), 1)
        if w = 'M' then
            exit 0
        if w == 'O' | w == 'E' then do
            call applyOverrides wr      /* apply to edited file */
            if ddSt > 0 then
                call findDDStar 1
            end
        if w == 'O' then do
            call adrEdit 'SAVE'
            call adrEdit 'END'
            end
        if pos(w, 'OEF') > 0 then
            exit 4
        say 'ungültige Antwort' w
        end
    exit

isCdl: procedure expose m.
parse arg lx
    if lx = '' then do
        if isCdl(1) then
            return 1
        if isCdl('CREATE') then
            return 1
        if isCdl('DROP') then
            return 1
        return 0
        end
    if ^ datatype(lx, 'n') then do
         if adrEdit("seek" lx "word first", 4) = 4 then
             return 0
         call adrEdit "(lx) = cursor"
         end
    call adrEdit '(ll) = line' lx
    if left(ll, 8) = 'SQLID' then
        return subword(ll, 2, 2) = 'SET CURRENT'
    if left(ll, 8) = 'CREATE' then
        return wordPos(word(ll, 2), 'CREATE ALTER ADMIN --#SET') > 0
    if left(ll, 8) = 'ALTER' then
        return wordPos(word(ll, 2), 'CREATE ALTER ADMIN --#SET') > 0
    if left(ll, 8) = 'DROP' then
        return wordPos(word(ll, 2), 'DROP ADMIN --#SET') > 0
    return 0
endProcedure isCdl

seekId: procedure expose m.
parse arg es, lx, id
    if ^ m.cdl then
        return scanSqlSeekId(es, lx, id)
    do forever
        lx = scanSqlSeekId(es, lx, id, 'WORD 9 80')
        call debug 'seek found CREATE at' lx scanPos(es)
        if lx < 1 then
            return lx
        call adrEdit '(ll) = line' lx
        if word(left(ll, 8), 1) = 'CREATE' then
            return lx
        end
endProcedure seekId
/*--- we define the scan structure and overrides
         in a tree ---------------------------------------------------*/
overrideTree: procedure expose m.
parse arg rt
    ts = overrideTreeNd(rt, 'TABLESPACE', 'TS')
    us = overrideTreeNd(ts, 'USING', 'US')
    sg = overrideTreeNd(us, 'STOGROUP', 'SG', 'i GSMS')
    c  = overrideTreeNd(sg, 'PRIQTY', 'PQ', 'n -1')
    c  = overrideTreeNd(sg, 'SECQTY', 'SQ', 'n -1' , PQ)
    c  = overrideTreeNd(ts, 'SEGSIZE', 'SE', 'n 64')
    c  = overrideTreeNd(ts, 'DSSIZE', 'DS', 'G 32 G')
    c  = overrideTreeNd(ts, 'NUMPARTS', 'PA', 'n')
    co = overrideTreeNd(ts, 'COMPRESS', 'CR', 'i YES')
    br = overrideTreeNd(ts, '(', '(')
    c  = overrideTreeNd(br, 'PARTITION', 'PR?', 'n')
    call mapAdd c, 'USING', us
    call mapAdd c, 'COMPRESS', co
    call mapAdd br, 'PART', c
    ix = overrideTreeNd(rt, 'INDEX', 'IX')
    call mapAdd ix, 'USING', us
    c  = overrideTreeNd(ix, 'COPY', 'CY', 'i NO')
    br = overrideTreeNd(ix, '(', '(')
    c  = overrideTreeNd(br, 'PARTITION', 'PR?', 'n')
    call mapAdd c, 'USING', us
    call mapAdd br, 'PART', c
    return
endProcedure overrideTree

/*--- create a node in the overrideTree with
          pa=parent, scan=token, ident,
          over=data type and override value, ty=id of type node ------*/
overrideTreeNd: procedure expose m.
parse arg pa, scan, ident, over, ty
    ch = mapReset(pa'.'ident, 'k')
    call mapAdd pa, scan, ch
    m.ch.id      = ident
    m.ch.att = scan
    m.ch.dataType = word(over, 1)
    m.ch.overVal = subword(over, 2)
    if ty ^== '' then
        m.ch.overType = ty
    else
        m.ch.overType = ident
    return ch
endProcedure overrideTreeNd

/*--- show the override tree -----------------------------------------*/
overrideTreeShow: procedure expose m.
parse arg pa, pr
    ks = mapKeys(pa)
    do kx = 1 to m.ks.0
        ch = mapGet(pa, m.ks.kx)
        say left(pr m.ks.kx, 20) right(ch, 2) ,
             'over' m.ch.overVal 'type' m.ch.overType
        call overrideTreeShow ch, pr'  '
        end
    return
endProcedure overrideTreeShow

/*--- analyse a create statement -------------------------------------*/
analyseCreate: procedure expose m.
parse arg m, os, an
    if m.m.val ^== 'CREATE' then
        call scanErr m, 'analyseCreate but token' m.m.val 'not CREATE'
    fp = scanPos(m)
    if ^ scanSqlId(m) then
        call scanErr m, 'no id'
    subTyp = ''
    do while wordPos(m.m.val, 'LARGE LOB UNIQUE WHERE') > 0
        subTyp = strip(subTyp m.m.val)
        if m.m.val = 'WHERE' then do
            call checkIds m, 'NOT', 'NULL'
            subTyp = subTyp 'NOT NULL'
            end
        if ^ scanSqlId(scanSkip(m)) then
            call scanErr m, 'no id'
        end
    typ = m.m.val
    if ^ mapHasKey(os, typ) then do
        call  scanSqlQuId scanSkip(m)
        call debug 'analyseCreate skipping' subTyp typ 'name' m.m.val
        return
        end
    nP = scanPos(m)
    if ^ scanSqlQuId(scanSkip(m)) then
        call scanErr 'name missing for create' subtyp typ
    na = m.m.val
    on = ''
    if typ = 'TABLESPACE' then do
        call checkIds m, 'IN'
        if ^ scanSqlId(scanSkip(m)) then
            call scanErr m 'dbName expected'
        na = m.m.val'.'na
        end
    else if typ = 'INDEX' then do
             /* wir muessen ueber die Column List scannen,
                damit wir sie nicht mit der PartitionListe verwechseln*/
        if ^ (scanSqlId(m) & m.m.val = 'ON') then
            call scanErr m, 'ON expected after index' na
        if ^ scanSqlQuId(scanSkip(m)) then
            call scanErr m, 'table name expected'
        on = 'on' m.m.val
        if ^ scanSqlType(m) & m.m.sqlType = '(' then
            call scanErr m, '( .. expected'
        call scanSqlSkipBrackets m, 1
        end
    say left('analyse', 8) leftl(na, 17) strip(subtyp typ) on
    a = mapReset(mAdd(an, mapGet(os, typ)), 'k')
    m.a.name = na
    m.a.subType = subTyp
    m.a.fPos = fP
    m.a.nPos = nP
    call analyseNode m, a
    tP = scanPos(m)
    if m.m.sqlType = ';' then
        tP = word(tP, 1) word(tP, 2) - 1
    m.a.tPos = tP
    return
endProcedure analyseCreate

/*--- analyse the substatement at scanner sc,
           according to the description in node nd.1 -----------------*/
analyseNode: procedure expose m.
parse arg sc, nd.1, stopper
    top = 1    /* top of node stack */
    do while scanSqlType(sc) & pos(m.sc.sqlType, ';'stopper) < 1
        if m.sc.sqlType = 'i' then
            att = m.sc.val
        else if pos(m.sc.sqlType, '()') > 0 then
            att = m.sc.sqlType
        else
            iterate
        do ox=top by -1 to 1   /* search id in all nodes in stack */
            nd = nd.ox
            os = m.nd
            if mapHasKey(os, att) then
                leave
            end
        if ox < 1 then do
            if att == '(' then
                call scanSqlSkipBrackets sc, 1
            iterate
            end
        osNx = mapGet(os, att)                /* the os node */
        chfPos = scanPos(sc)
        ty = m.osNx.dataType
        if ty ^== '' then do     /* scan the value of the attribute */
            if ty = 'i' then
                res = scanSqlId(sc)
            else if ty = 'n' then
                res = scanSqlNum(sc)
            else if ty = 'G' then
                res = scanSqlNumUnit(sc, 'G M K')
            else
                call err 'overwrite type' ty 'not supported'
            if ^ res then
                call scanErr sc, ty 'value expected after' att
            res = m.sc.val
            end
        chId = m.osNx.id
        if right(chId, 1) = '?' then
            chId = chId || res
        ch = mapReset(nd.ox'.'chId, 'k') /* the new analysis node*/
        m.ch.fPos = chfPos
        m.ch.tPos = scanPos(sc)
        if ty ^== '' then
            m.ch.val = res
        call mapAdd nd.ox, chId, osNx
        if att = '(' then do
            top = ox
            call analyseNode sc, ch, ')'
            if m.sc.sqlType ^== ')' then
                call scanErr sc, 'closing ) expected'
            iterate
            end
        top = ox+1               /* pop higher nodes and push new one */
        nd.top = ch
        end
    return
endProcedure analyseNode

/*--- show the the root analysises in stem a -------------------------*/
anaShow: procedure expose m.
parse arg a
    do x=1 to m.a.0
        call anaShow1 a'.' || x
        end
    return

/*--- show the analysis node a and its subnodes ----------------------*/
anaShow1: procedure expose m.
parse arg a
    os = m.a
    say a '->' os
    if ^ abbrev(os, 'OS.') then
        return
    say '  val' m.a.val 'fr' m.a.fPos 'to' m.a.tPos
    if wordPos(m.os.id, 'TS IX') > 0 then
        say '  name' m.a.name '@' m.a.nPos
    ks = mapKeys(a)
    do kx = 1 to m.ks.0
        call anaShow1 a'.'m.ks.kx
        end
    return

/*--- generate the override for all anaysis root nodes ---------------*/
override: procedure expose m.
parse arg an, wr
    do ax=1 to m.an.0
        call overrideNode an'.'ax, an'.'ax, wr
        end
    return
endProcedure override

/*--- create the necessary overrides for node rt and it's subnodes ---*/
overrideNode: procedure expose m.
parse arg rt, an, wr
    os = m.an
    if m.os.overVal <> '' & m.os.overVal <> m.an.val then
        call overrideAtt rt, an, os, wr
    if m.os.overType = 'TS' then do
        wx = wordPos('LARGE', m.an.subType)
        if wx > 0 then  do
            o = m.an.subType
            n = subWord(o, 1, wx-1) subWord(o, wx+1)
            call overrideOne wr, n 'TABLESPACE', m.an.fPos, m.an.nPos
            call overrideSay 'override', rt, 'subType', n, o
            end
        end
    ids = ''
    keys = mapKeys(an)
    do ax=1 to m.keys.0
        nd = an'.'m.keys.ax
        o1 = m.nd
        ids = ids m.o1.id
        call overrideNode rt, nd, wr
        end
    keys = mapKeys(os)
    do ox=1 to m.keys.0
        nd = mapGet(os, m.keys.ox)
        if wordPos(m.nd.id, ids) < 1 then
            call overrideAdd rt, an, nd, wr
        end
    return
endProcedure overrideNode

/*--- add to wr the override attribute osprefixed by tokens in scPa
          for analysis node an with root rt pre ----------------------*/
overrideAdd: procedure expose m.
parse arg rt, an, os, wr, scPa
    scPa = strip(scPa m.os.att)
    if pos('?', os an) > 0 then
        return
    if m.os.overVal ^== '' then do
        ty = m.os.overType
        if ty = 'SE' then
            if mapHasKey(rt, 'PA') | pos('LOB', m.rt.subType) > 0 then
                ty = ''
        if ty = 'DS' then
            if ^mapHasKey(rt, 'PA') | pos('LOB', m.rt.subType) > 0 then
                ty = ''
        if ty <> '' then do
            call overrideOne wr, scPa m.os.overVal,
                      , m.an.tPos, m.an.tPos
            call overrideSay 'add', rt, scPa, m.os.overVal
            scPa = ''
            end
        else
            call debug 'no overrideAdd' scPa
        end
    keys = mapKeys(os)
    do ox=1 to m.keys.0
        call overrideAdd rt, an, mapGet(os, m.keys.ox), wr, scPa
        end
    return
endProcedure overrideAdd

/*--- override an attribute of cp with overrideNode on ---------------*/
overrideAtt: procedure expose m.
parse arg rt, an, os, wr
    o = mAdd(wr, m.os.overVal)
    m.o.fPos = m.an.fPos
    m.o.tPos = m.an.tPos
    call overrideSay 'override', rt, m.os.att, m.os.overVal, m.an.val' '
    return
endProcedure overrideAtt

/*--- create on override node an add it ------------------------------*/
overrideOne: procedure expose m.
parse arg wr, new, fp, tp
    o = mAdd(wr, new)
    m.o.fPos = fp
    m.o.tPos = tp
    return
endProcedure overrideOne

/*--- say what we want to override -----------------------------------*/
overrideSay: procedure expose m.
parse arg f, rt, att, new, old
    m = left(f, 8) leftl(m.rt.name, 17) leftl(att, 8) leftl(new, 8)
    if old ^== '' then
        m = m 'from' old
    say m
    return
endProcedure overrideSay

/*--- edit a sequence of overrides into data -------------------------*/
applyOverrides: procedure expose m.
parse arg wr
    call adrEdit "(w) = linenum .zl"
    w = max(w, m.wr.0) + 10
    w = length(w)
    do x=1 to m.wr.0
        m.si.x = right(word(m.wr.x.fPos, 1)+0, w, 0) ,
                 right(word(m.wr.x.fPos, 2)+0, 3, 0) right(x, w)
        end
    m.si.0 = m.wr.0
    call sort si, so

    delta = 0
    cx = 1
    wx = word(m.so.cx, 3)
    do while cx <= m.so.0
        lx = word(m.wr.wx.fPos, 1)
        line = applyGetLine(lx+delta)
        call mAdd mCut(wrk, 0), left(line, word(m.wr.wx.fPos, 2)-1)
        lStX = lx
        wy = wx
        do forever
            call app72 wrk, m.wr.wx
            cx = cx + 1
            if cx > m.so.0 then
                leave
            wx = word(m.so.cx, 3)
            if word(m.wr.wx.fPos, 1) > word(m.wr.wy.tPos, 1) then
                leave
            else if m.wr.wx.tPos == m.wr.wy.tPos ,
                     & (m.wr.wx.fPos == m.wr.wy.fPos ,
                       |m.wr.wx.fPos == m.wr.wx.tPos) then
                nop
            else if word(m.wr.wx.fPos, 1) <> word(m.wr.wy.tPos, 1) then
                call err 'bad sequence in override'
            else if word(m.wr.wx.fPos, 2) <= word(m.wr.wy.tPos, 2) then
            do
                say wy m.wr.wy.tPos
                call err 'overlap in override'
                end
            else do
                if lx <> word(m.wr.wx.fPos, 1) then do
                    lx = word(m.wr.wx.fPos, 1)
                    line = applyGetLine(lx+delta)
                    end
                px = word(m.wr.wy.tPos, 2)
                call app72 wrk, substr(line, px,
                    , word(m.wr.wx.fPos, 2) - px), px
                wy = wx
                end
            end
        if lx <> word(m.wr.wy.tPos, 1) then do
            lx = word(m.wr.wy.tPos, 1)
            line = applyGetLine(lx+delta)
            end
        px = word(m.wr.wy.tPos, 2)
        call app72 wrk, substr(line, px, 72+1-px), px, 1
        do xx = lStx to lx
            call adrEdit 'delete' (lStx+delta)
            end
        delta = delta + lStX - lx - 1
        do xx=1 to m.wrk.0
            if m.cdl then
                li = left(m.applyGetLineMark || m.wrk.xx, 80)
            else
                li = left(m.wrk.xx, 72)m.applyGetLineMark
            call adrEdit "line_after" (lx+delta) "= (li)"
            delta = delta + 1
            end
        end
    return
endProcedure applyOverrides

/*--- return the sql portion of line lx
          and put the mark field into m.applyGetLineMark -------------*/
applyGetLine: procedure expose m.
parse arg lx
    call adrEdit "(line) = line" (lx)
    if m.cdl then do
        m.applyGetLineMark = left(line, 8)
        if m.applyGetLineMark <> 'CREATE' then
            call err 'bad applyGetLine mark' m.applyGetLineMark ,
                     'in line' lx':' strip(line, 't')
        return substr(line, 9, 72)
        end
    else do
        m.applyGetLineMark = substr(line, 73, 8)
        return left(line, 72)
        end
endProcedure applyGetLine

/*--- append to stem st string val, at position miLe
          if fix=1 exactly at the position else can shift to right ---*/
app72: procedure expose m.
parse arg st, val, miLe, fix
    sx = m.st.0
    li = strip(m.st.sx, 't')
    if miLe ^== '' then do
        vx = verify(val, ' ')
        if vx = 0 then
            miLe = miLe + length(val)
        else
            miLe = miLe + vx - 1
        end
    val = strip(val)
    if fix = 1 then do
        if length(li)+1 >= miLe then do
            sx = sx + 1
            li = ''
            end
        nn = left(li, miLe-1)val
        end
    else do
        if length(li)+1 < miLe then
            nn = left(li, miLe-1)val
        else if length(li val) < 72 then
            nn = li val
        else
            nn = left(li, 80)val
        do while length(nn) >= 72
            m.st.sx = left(nn, 72)
            sx = sx + 1
            nn = substr(nn, 73)
            end
        end
    m.st.sx = nn
    m.st.0 = sx
    return
endProcedure app72

/*--- scan from scanner m the ids arg(2) ... arg(arg()) --------------*/
checkids: procedure expose m.
parse arg m
    do ax=2 to arg()
        if ^ scanSqlId(scanSkip(m)) & m.m.val <> translate(arg(ax)) then
            call scanErr m, 'sqlId' arg(ax) 'expected'
        end
    return
endProcedure checkIds

/*--- find the errously genereate // DD * statements ----------------*/
findDDStar: procedure expose m.
parse arg rem
parse arg m, lx, cmd
    c = 0
    call adrEdit "cursor = 1"
    do while adrEdit("seek '//' 1", 4) = 0 /* find each command */
        call adrEdit "(lx) = cursor"
        call adrEdit "(li) = line" lx
        if lx = 1 then do
            say 'first line looks like jcl, no search for //DD*'
            return 0
            end
        if space(li, 0) ^== '//DD*' then do
            if ^ rem then
                say 'ignoring // line' lx strip(li,'t')
            end
        else do
            c = c + 1
            if rem then do
                call adrEdit 'delete' lx
                call adrEdit "cursor =" (lx-1)
                end
            end
        end
    return c
endProcedure findDDStar

/*--- fill src with spaces to get at least length len ----------------*/
leftl: procedure
parse arg src, len
    if len > length(src) then
        return left(src, len)
    else
        return src
endProcedure leftl
/*--- define reader reading edit data from line lx -------------------*/
editReadIni: procedure expose m.
parse arg m, lx
    call oDecMethods oNewClass("EditRead", "JRW"),
        , "jRead  return editRead(m, var)",
        , "jOpen  m.m.jReading = 1"
    return m
endProcedure editReadReset
/*--- define reader reading edit data from line lx -------------------*/
editReadReset: procedure expose m.
parse arg m, lx
    m.m.lineX = lx-1
    return m
endProcedure editReadReset

/*--- read next line from edit data ----------------------------------*/
editRead: procedure expose m.
parse arg m, var
    m.m.lineX = m.m.lineX + 1
    if adrEdit('(ll) = line' m.m.lineX, 12) ^= 0 then
        return 0
    m.var = ll
    return 1
endProcedure editReadRead

/* copy sort begin ****************************************************/
sort: procedure expose m.
parse arg i, o
    call sort1 i, 1, m.i.0, o, 1, sort.work, 1
    m.o.0 = m.i.0
    return
endProcedure sort

sort1: procedure expose m.
parse arg i, i0, le, o, o0, w, w1
    if le <= 1 then do
        if le = 1 then
            m.o.o0 = m.i.i0
        return
        end
    h = (le + 1) % 2
    call sort1 i, i0,   h,    o, o0+le-h, w, w1
    call sort1 i, i0+h, le-h, w, w1,      o, o0
    call sortMerge o, o0+le-h, o0+le, w, w1, w1+le-h, o, o0
    return
endProcedure sort1

sortMerge: procedure expose m.
parse arg l, l0, le, r, r0, re, o, o0
    do while l0 < le & r0 < re
        if m.l.l0 <<= m.r.r0 then do
            m.o.o0 = m.l.l0
            l0 = l0 + 1
            end
        else do
            m.o.o0 = m.r.r0
            r0 = r0 + 1
            end
        o0 = o0 + 1
        end
    do while l0 < le
        m.o.o0 = m.l.l0
        l0 = l0 + 1
        o0 = o0 + 1
        end
    do while r0 < re
        m.o.o0 = m.r.r0
        r0 = r0 + 1
        o0 = o0 + 1
        end
    return
endProcedure sortWork
/* copy sort end   ****************************************************/
/* copy scanSql begin *************************************************/
/*--- initialize with reader inRdr ----------------------------------*/
scanSql: procedure expose m.
parse arg inRdr
    return scanSqlReset(scanWin(inRdr), inRdr)

scanSqlReset: procedure expose m.
parse arg m, rdr, scanWin
    if scanWin ^== 0 then
        call scanWinReset m, rdr, 5, 2, 1, 72
    else
        m.m.read = rdr
    return scanOpts(m, , '0123456789_' , '--')

scanSqlSeekId: procedure expose m.
parse arg m, lx, cmd, opts
    if opts = '' then
        opts = word
    if adrEdit("cursor =" max(trunc(lx), 1), 12) = 12 then
        return -1
    do while adrEdit("seek" cmd opts, 4) = 0 /* find each command*/
        call adrEdit "(fx) = cursor"
        if m.debug then do
            call adrEdit "(LI) = LINE" fx
            call debug 'scanSqlSeekId after' lx 'found' cmd 'at' fx li
            end
        call editReadReset m.m.read, fx
        call scanWinOpen es, fx
        do while word(scanPos(m), 1) <= fx & scanSqlType(m)
            if m.m.sqlType = 'i' & m.m.val == cmd then
                return fx
            end
        end
    return -1
endProcedure scanSqlSeekId
/*--- scan a sql token put type in m.sqltype:
      'i': ordinary identifier   e.g. Name
      'd': delimited identifier  e.g. "Delimited"
      'q': qualified identifier  e.g. abc."efg"
      'u': integer units         e.g. 8G
      'n': number                e.g. -234
      's': string                e.g. 'abc''ef'
      '' : at end
         : any other character   e.g. ;
      ----------------------------------------------------------------*/
scanSqlType: procedure expose m.
parse arg m, retSpace
    m.m.val = ''
    if scanSpaceNl(m) & retSpace = 1 then do
        m.m.sqlType = 'b'
        return 1
        end
    if scanString(m, "'") then
        m.m.sqlType = 's'
    else if scanSqlQuId(m) then do
        if m.m.val.0 > 1 then
            m.m.sqlType = 'q'
        else if abbrev(m.m.tok, '"') then
            m.m.sqlType = 'd'
        else
            m.m.sqlType = 'i'
        end
    else if scanSqlNum(m, 0, 1)  then
        m.m.sqlType = 'n'
    else if scanChar(m, 1) then
        m.m.sqlType = m.m.tok
    else if scanAtEnd(m) then do
        m.m.sqlType = ''
        return 0
        end
    else
        call scanErr m, 'cannot scan sql'
    return 1
endProcedure scanSqlType

scanSqlSkipBrackets: procedure expose m.
parse arg m, br
    if br ^== '' then
        nop
    else if scanLit(m, '(') then
        br = 1
    else
        return 0
    do while scanSqlType(m) & m.m.sqlType ^== ';'
        if m.m.sqlType = '('        then br = br + 1
        else if m.m.sqlType ^== ')' then iterate
        else if br > 1              then br = br - 1
        else                             return 1
        end
    call scanErr m, '; or eof, but' br 'closing ) expected'
endProcedure skipBrackets
/*--- scan an ordinary sql identifier e.g. abc, ef_12 ----------------*/
scanSqlId: procedure expose m.
parse arg m
    if ^ scanName(m) then
        return 0
    m.m.val = translate(m.m.tok)
    return 1
endProcedure scanSqlId

/*--- scan a delimited or ordinay sql identifier ---------------------*/
scanSqlDeId: procedure expose m.
parse arg m
    if scanSqlId(m) then
        return 1
    if ^ scanString(m, '"') then
        return 0
    m.m.val = strip(m.m.val, 't')
    return 1
endProcedure scanSqlDeId

/*--- scan a qualified sql identifier --------------------------------*/
scanSqlQuId: procedure expose m.
parse arg m
    res = ''
    do qx=1
        if ^ scanSqlDeId(m) then do
            if qx <> 1 then
                call scanErr m, 'id expected after .'
            return 0
            end
        m.m.val.qx = m.m.val
        res = res'.'m.m.val
        if ^ scanLit(scanSkip(m), '.') then
            leave
        call scanSpaceNl m
        end
    m.m.val.0 = qx
    m.m.val = substr(res, 2)
    return 1
endProcedure scanSqlQuId

/*--- scan a sql number ----------------------------------------------*/
scanSqlNum: procedure expose m.
parse arg m, checkEnd, noSp
    n = ''
    if scanLit(m, '+', '-') then do
        n = m.m.tok
        if noSp <> 1 then
            call scanSpaceNl m
        end
    if scanLit(m, '.') then
        n = n'.'
    if scanVerify(m, '0123456789') then
        n = n || m.m.tok
    else if n == '' then
        return 0
    else if noSp = 1 then do
        call scanBack m, n
        return 0
        end
    else
        call scanErr m, 'scanSqlNum bad number: no digits after' n
    if pos('.', n) < 1 then
        if scanLit(m, '.') then do
            if scanVerify(m, '0123456789') then
                n = n'.'m.m.tok
            end
    if scanLit(m, 'E', 'e') then do
        n = n'E'
        if scanLit(m, '+', '-') then
            n = n || m.m.tok
        if ^ scanVerify(m, '0123456789') then
            call scanErr m, 'scanSqlNum bad number: no digits after' n
        n = n || m.m.tok
        end
    if checkEnd ^= 0 then
        if pos(scanLook(m, 1), m.m.scanNameR) > 0 then
            call scanErr m, 'scanSqlNum number' n 'bad end' ,
                            scanLook(m, 1)
    m.m.val = n
    return 1
endProcedure scanSqlNum

/*--- scan a sql number with a unit which may follow without space ---*/
scanSqlNumUnit: procedure expose m.
parse arg m, both, units
    if ^ scanSqlNum(m, 0) then
        return 0
    nu = m.m.val
    sp = scanSpaceNl(m)
    if scanSqlId(m) then do
        if units == '' | wordpos(m.m.val, units) > 0 then
            nu = nu m.m.val
        else if both | ^ sp then
            call scanErr m, 'scanSqlNumUnit after' nu 'bad unit' m.m.val
        else
            call scanBack m, m.m.tok
        end
    else if both then
        call scanErr m, 'scanSqlNumUnit no unit after' nu
    else if ^sp & pos(scanLook(m, 1), m.m.scanNameR) > 0 then
        call scanErr m, 'scanSqlNumUnit bad number end after' nu
    m.m.val = nu
    return 1
endProcedure scanSqlNumUnit

/* copy scanSql end   *************************************************/
/* copy scanWin begin *************************************************
     scan the the concatenation of the lines of a reader
         any token my be split over several line
         except the end-of-line-comment-token
***********************************************************************/
scanWinIni: procedure expose m.
    if m.scanWin.ini = 1 then
        return
    m.scanWin.ini = 1
    call scanIni
    call jIni
    call oDecMethods oNewClass('ScanWin'),
        , 'scanReadNl return scanWinNl(m, unCond)',
        , 'scanSpaceNl scanWinSpaceNl(m)',
        , 'scanClose call scanWinClose m ',
        , 'scanInfo scanWinInfo(m)',
        , 'scanPos  scanWinPos(m)'
    return
endProcedure scanReadIni

/*--- instanciate a new window scanner, open rdr ---------------------*/
scanWin: procedure expose m.
parse arg rdr, wiSz, wiBa, cuPo, cuLe
    return scanWinReset(oNew('ScanWin'), rdr, wiSz, wiBa, cuPo, cuLe)

/*--- set the attributes of window scanner m, open rdr and start read*/
scanWinReset: procedure expose m.
parse arg m, rdr, wiSz, wiGa, cuPo, cuLe
    call scanReset m
    m.m.read = rdr
    m.m.atEnd = 'still closed'
    return scanWinOpts(m, wiSz, wiGa, cuPo, cuLe)
endProcedure scanWinReset

scanWinOpts: procedure expose m.
parse arg m, wiSz, wiGa, cuPo, cuLe
    wiSz = word(wiSz 5, 1)
    wiGa = word(wiGa 1, 1)
    m.m.cutPos = word(cuPo 1, 1)
    m.m.cutLen = word(cuLe 72, 1)
    m.m.winTot = (wiSz * 2 + wiGa) * m.m.cutLen
    m.m.posLim = (wiSz     + wiGa) * m.m.cutLen
    m.m.posOff =  wiGa * m.m.cutLen
    return scanWinOpen(m)
endProcedure scanWinReset

scanWinOpen: procedure expose m.
parse arg m, lx
    m.m.atEnd = 0
    if lx = '' then
        m.m.lineX = 1
    else
        m.m.lineX = lx
    m.m.pos = 1
    m.m.src = ''
    call jOpen m.m.read, 'r'
    call scanWinRead m
    return m
endProcedure scanWinOpen

scanWinClose: procedure expsoe m.
    m.m.atEnd = 'still closed'
    call jClose m.m.read
    return
endProcedure scanWinClose
/*--- move the source window: cut left side and append at right side
      return number of characters cut at left ------------------------*/
scanWinRead: procedure expose m.
parse arg m
    dlt = 0
    if m.m.atEnd then
        return 0
    if m.m.pos >= m.m.posLim then do     /*  cut left side */
        dlt = m.m.pos - (m.m.pos // m.m.cutLen + m.m.posOff)
        m.m.src = substr(m.m.src, dlt+1)
        m.m.pos = m.m.pos - dlt
        m.m.lineX = m.m.lineX + dlt % m.m.cutLen
        end
    do while length(m.m.src) < m.m.winTot /* read and fill to len */
        if ^ jRead(m.m.read, m'.'one) then do
            m.m.atEnd = 1
            return dlt
            end
        m.m.src = m.m.src || substr(m.m.one, m.m.cutPos, m.m.cutLen)
        end
    call assert 'length(m.m.src) = m.m.winTot'
    return dlt
endProcedure scanWinRead

/*--- return position of next line start -----------------------------*/
scanWinNLPos: procedure expose m.
parse arg m
    return m.m.pos + m.m.cutLen - ((m.m.pos - 1) // m.m.cutLen)

/*--- scan over spaces and comments ----------------------------------*/
scanWinSpaceNL: procedure expose m.
parse arg m
    res = 0
    do forever
        r1 = 0
        if scanVerify(m, ' ') then do
            r1 = 1
            end
        else if m.m.scanComment ^== '' ,
             & abbrev(substr(m.m.src, m.m.pos), m.m.scanComment) then do
            np = scanWinNlPos(m)
            r1 = length(m.m.scanComment) <= np - m.m.pos
            if r1 then
                m.m.pos = np
            end
        if r1 then
            res = 1
        else if scanWinRead(m) = 0 then
            return res
        end
endProcedure scanWinSpaceNl

/*--- return current position in input ------------------------------*/
scanWinPos: procedure expose m.
parse arg m
    if scanAtEnd(m) then
        return 'E'
    else
        ps = m.m.pos - 1
    return (m.m.lineX + (ps % m.m.cutLen)) (ps // m.m.cutLen + 1)
endProcedure scanWinPos

/*--- return a description of the current scan position --------------*/
scanWinInfo: procedure expose m.
parse arg m
    p = scanWinPos(m)
    if p == 'E' then do
        res = 'atEnd after'
        p = m.m.lineX - 1 + length(m.m.src) % m.m.cutLen
        end
    else do
        res = 'pos' word(p, 2) 'in'
        p = word(p, 1)
        end
    return res 'line' p':' strip(substr(m.m.src,
          , 1 + (p - m.m.lineX) * m.m.cutLen, m.m.cutLen), 't')
endProcedure scanWinInfo
/* copy scanWin end   *************************************************/
/* copy scan begin ****************************************************
Scan: scan an input:
    scanLine(m,ln) : begin scanning a single line (string)
    scanRead??(m,ln): begin scanning all lines of an opened reader
    scanAtEnd(m)   : returns whether we reached end of input
    scanLit(m,lit) : scan Literal lit if present or return 0
    scanChar(m,n)  : scan next n characters
    scanName(m)    : scan a name
    ScanNat(m)     : scan a natural number (without sign)
    scanString(m,q): scan a String with quote q. (with doubble = 1)
    scanVerify(m,c,o): verify(...,c,o,...)
    scanKeyValue(m): scan a key = value clause (with spaces)
    scanWord(m,u)  : scan a space delimited word or a string,
                          if u=1 then uppercase non-strings
    scanErr(m, txt): error with current scan location

    m is an adress, to store our state
    if a scan function succeeds, the scan posititon is moved

returns: true if scanned, false otherwise
         m.m.tok  ==> last token
         m.m.val  ==> last value for scanString/Word/KeyValue
         m.key    ==> key for scanKeyValue
         m.m.pos ==> scan position
         m.m.src ==> scan source
***********************************************************************/
scanIni: procedure expose m.
    if m.scan.ini == 1 then
        return
    m.scan.ini = 1
    m.scan.alfLC = 'abcdefghijklmnopqrstuvwxyz'
    m.scan.alfUC = translate(m.scan.alfLC)
    m.scan.alfa = m.scan.alfLC || m.scan.alfUC
    m.scan.alfNum = m.scan.alfa || '0123456789'
    return
endProcedure scanIni

scanReset: procedure expose m.
parse arg m, n1, np, co
    m.m.tok = ''
    m.m.val = ''
    m.m.key = ''
    m.m.read = ''
    return scanOpts(m, n1, np, co)
endProcedure scanReset

scanOpts: procedure expose m.
parse arg m, m.m.scanName1, namePlus, m.m.scanComment
    call scanIni
    if m.m.scanName1 == '' then
        m.m.scanName1 = m.scan.alfa
    if namePlus == '' then
        m.m.scanNameR = m.m.scanName1 || '0123456789'
    else
        m.m.scanNameR = m.m.scanName1 || namePlus
    return m
endProcedure scanReset


/*--- begin scanning a single line -----------------------------------*/
scanSrc: procedure expose m.
parse arg m, m.m.src
    m.m.atEnd = 1
    m.m.pos = 1
    return m
endProcedure scanSrc

/*--- return the next len characters ---------------------------------*/
scanLook: procedure expose m.
parse arg m, len
    if len == '' then
        return substr(m.m.src, m.m.pos)
    else
        return substr(m.m.src, m.m.pos,
                     , min(len, 1 + length(m.m.src) - m.m.pos))
endProcedure scanLook

/*--- scan the literal lit ------------------------------------------*/
scanLit: procedure expose m.
parse arg m
    do ax=2 to arg()
        if abbrev(substr(m.m.src, m.m.pos), arg(ax)) then do
            m.m.tok = arg(ax)
            m.m.pos = m.m.pos + length(arg(ax))
            return 1
            end
        end
    m.m.tok = ''
    return 0
endProcedure scanLit

/*--- scan the next len characters -----------------------------------*/
scanChar: procedure expose m.
parse arg m, len
    nx = 1 + length(m.m.src)
    if len ^= '' then
        nx = min(m.m.pos + len, nx)
    m.m.tok = substr(m.m.src, m.m.pos, nx - m.m.pos)
    m.m.pos = nx
    return m.m.tok ^== ''
endProcedure scanChar

/*--- scan a string with quote char qu -------------------------------*/
scanString: procedure expose m.
parse arg m, qu
    m.m.tok = ''
    if qu = '' then do
        qu = substr(m.m.src, m.m.pos, 1)
        if pos(qu, "'""") < 1 then
            return 0
        end
    else do
        if substr(m.m.src, m.m.pos, 1) ^== qu then
            return 0
        end
    bx = m.m.pos
    ax = bx + 1
    m.m.val = ''
    do forever
        qx = pos(qu, m.m.src, ax)
        if qx < 1 then
            return scanErr(m, 'ending Apostroph('qu') missing')
        m.m.val = m.m.val || substr(m.m.src, ax, qx-ax)
        if qx >= length(m.m.src) then
            leave
        else if substr(m.m.src, qx+1, 1) <> qu then
            leave
        ax = qx+2
        m.m.val = m.m.val || qu
        end
    m.m.tok = substr(m.m.src, bx, qx+1-bx)
    m.m.pos = qx+1
    return 1
endProcedure scanString

/*--- scan a Name, first char in *.scanName1, rest in *.scanNameR ----*/
scanName: procedure expose m.
parse arg m
    if pos(substr(m.m.src, m.m.pos, 1),
                 , m.m.scanName1) <= 0 then do
        m.m.tok = ''
        return 0
        end
    return scanVerify(m, m.m.scanNameR)
endProcedure scanName

/*--- scan with verify, vOpt is passed to verify ---------------------*/
scanVerify: procedure expose m.
parse arg m, alpha, vOpt
    if vOpt == '' then   /* empty string does not take default| */
        nx = verify(m.m.src, alpha, , m.m.pos)
    else
        nx = verify(m.m.src, alpha, vOpt, m.m.pos)
    if nx = 0 then
        nx = length(m.m.src) + 1
    m.m.tok = substr(m.m.src, m.m.pos, nx - m.m.pos)
    m.m.pos = nx
    return m.m.tok ^== ''
endProcedure scanVerify

/*--- scan a natural number (no sign, decpoint ...) ------------------*/
scanNat: procedure expose m.
parse arg m, chEn
    if ^ scanVerify(m, '0123456789') then
        return 0
    if chEn^==0 & pos(substr(m.m.src, m.m.pos,1), m.m.scanNameR)>0 then
        call scanErr m, 'illegal number end'
    return 1
endProcedure ScanNat

scanInt: procedure expose m.
parse arg m, chEn
    if scanNat(m, chEn) then
        return 1
    ox = m.scan.m.pos
    if pos(substr(m.scan.m.src, ox, 1) , '+-') < 1 then
        return 0
    m.scan.m.pos = ox + 1
    if | scanNat(m) then do
        m.scan.m.pos = ox
        return 0
        end
    m.tok =substr(m.scan.m.src, ox, 1)|| m.tok
    return 1
endProcedure scanInt

/*--- scan a word and put value into *.val
           a word is either delimited by space or stopper
                     or a string (with single or double quotes -------*/
scanWord: procedure expose m.
parse arg m, stopper

    if scanString(m)                   then return 1
    if ^scanVerify(m, ' 'stopper, 'm') then return 0
    m.m.val = m.m.tok
    return 1
endProcedure scanWord

scanBack: procedure expose m.
parse arg m, tok
    if m.m.pos <= length(tok) then
        call scanErr sc, 'cannot back "'tok'" length'
    cx = m.m.pos - length(tok)
    if substr(m.m.src, cx, length(tok)) ^== tok then
        call scanErr sc, 'cannot back "'tok'" value'
    m.m.pos = cx
    return
endProcedure scanBack

/*--- scan a key = word phrase
          put key into m.key and word into m.m.val -------*/
scanKeyValue: procedure expose m.
parse arg m, def
    if ^ scanName(m) then
        return 0
    m.m.key = m.m.tok
    if ^ scanLit(scanSkip(m), '=') then do
        m.m.val = def
        m.m.tok = ' no='
        end
    else if ^scanWord(scanSkip(m)) then
        call scanErr(m, 'word expected after' m.m.key '=')
    return 1
endProcedure scanKeyValue

scanAtEnd: procedure expose m.
parse arg m
    return m.m.atEnd & m.m.pos > length(m.m.src)
endProcedure scanAtEnd

/*--- skip over spaces, nl and comments (if option set) --------------*/
scanSpaceNL: procedure expose m.
parse arg m
    lastTok = m.m.tok
    if m.m.read ^== '' then
        interpret 'res = ' oObjMethod(m, 'scanSpaceNl')
    else
        res = scanSpaceCom(m)
    m.m.tok = lastTok
    return res
endProcedure scanSpaceNL

scanSpaceCom: procedure expose m.
parse arg m
    res = scanVerify(m, ' ')
    if m.m.scanComment ^== '' then
        if abbrev(substr(m.m.src, m.m.pos), m.m.scanComment) then do
            m.m.pos = 1 + length(m.m.src)
            return 1
            end
    return res
endProcedure scanSpaceCom

/*--- skip over space, nl and comments and return m -----------------*/
scanSkip: procedure expose m.
parse arg m
    call scanSpaceNl m
return m
endProcedure scanSkip

/*--- emit an error with current scan pos ----------------------------*/
scanErr: procedure expose m.
parse arg m, txt
    m.m.err.0 = 0
    call err 'scanErr' txt'\n'scanInfo(m, m'.ERR')
    return 0
endProcedure scanErr

scanPos: procedure expose m.
parse arg m
    if m.m.read ^== '' then
        interpret 'return' oObjMethod(m, 'scanPos')
    else if scanAtEnd(m) then
        return E
    else
        return 1 m.m.pos
endProcedure scanPos

scanInfo: procedure expose m.
parse arg m
    msg = 'last token' m.m.tok 'scanPosition' ,
          strip(left(substr(m.m.src, m.m.pos), 40), 't')
    if m.m.read == '' then
        return msg'\npos' m.m.Pos 'in string' strip(m.m.src, 't')
    else
        interpret 'return msg"\n" ||' oObjMethod(m, 'scanInfo')
endProcedure scanInfo
/* copy scan end   ****************************************************/
/* copy j begin *******************************************************
    the j framework
         jReset
         jOpen
         jClose
         jRead
         jWrite
***********************************************************************/
jRead: procedure expose m.
parse arg m, var
    if m.m.jReading then
        interpret oObjMethod(m, 'jRead')
    else
        call err 'jRead('m',' var') but not opened r'
    else
endProcedure jRead

jWrite: procedure expose m.
parse arg m, line
    if m.m.jWriting then
        interpret oObjMethod(m, 'jWrite')
    else
        call err 'jWrite('m',' line') but not opened w'
    return
endProcedure jWrite

jWriteAll: procedure expose m.
parse arg m, opt, rdr
    interpret oObjMethod(m, 'jWriteAll')
    return
endProcedure jWriteAll

jWriteAllImpl: procedure expose m.
parse arg m, opt, rdr
    if pos('-', opt) < 1 then
        call jOpen rdr, catOpt(opt)
    do while jRead(rdr, line)
        call jWrite m, m.line
        end
    if pos('-', opt) < 1 then
        call jClose rdr
    return
endProcedure jWriteAll

jReset: procedure expose m.
parse arg m, arg
    call jClose m
    interpret oObjMethod(m, 'jReset')
    return m
endProcedure jOpen

jOpen: procedure expose m.
parse arg m, arg
    interpret oObjMethod(m, 'jOpen')
    return m
endProcedure jOpen

jClose: procedure expose m.
parse arg m
    if m.m.jReading = 1 | m.m.jWriting = 1 then
        interpret oObjMethod(m, 'jClose')
    m.m.jReading = 0
    m.m.jWriting = 0
    return m
endProcedure jClose

/*--- analyze an option in oOpt and oVal -----------------------------*/
jOpt: procedure expose m.
parse arg src, alone, val
    m.j.oOpt = ''
    if left(src, 1) ^== '-' then do
        m.j.oVal = src
        return 0
        end
    sx = 2
    if alone ^== '' then do
        sx = verify(src, alone, 'n', sx)
        if sx = 0  then
            sx = length(src)+1
        end
    if length(src) < sx then
        m.j.oVal = ''
    else if val == '' then
        call err 'bad opt "'src'" should contain only "'alone'"'
    else if pos(substr(src, sx, 1), val) < 1 then
        call err 'bad opt "'src'" should contain only "'alone'"' ,
                        'and/or 1 of "'val'" with value'
    else do
        sx = sx + 1
        m.j.oVal = substr(src, sx)
        end
    m.j.oOpt = substr(src, 2, sx-2)
    return 1
endProcedure jOpt

jIni: procedure expose m.
    if m.j.ini == 1 then
        return
    m.j.ini = 1
    call oIni
    call oDecMethods oNewClass("JRW"),
        , "jRead  call err 'jRead('m',' var') but not opened r'",
        , "jWrite call err 'jWrite('m',' line') but not opened w'",
        , "jWriteAll call jWriteAllImpl m, opt, rdr",
        , "jRead drop m.arg; return 0",
        , "jWrite say 'jOut:' line",
        , "jReset ;",
        , "jOpen ;",
        , "jClose ;"
    x = oNew("JRW")
    m.j.jIn = x
    m.x.jReading = 1
    m.x.jWriting = 0
    x = oNew("JRW")
    m.j.jOut = x
    m.x.jReading = 0
    m.x.jWriting = 1
    call oDecMethods oNewClass("Jbuf", "JRW"),
        , "jOpen return jBufOpen(m, arg)",
        , "jReset return jBufReset(m, arg)",
        , "oSetTypePara call jBufSetTypePara m, type",
        , "jRead return jBufRead(m, var)",
        , "jWrite call jBufWrite m, line"
    return
endProcedure jInit

jIn: procedure expose m.
parse arg arg
    return jRead(m.j.jIn, arg)
endProcedur jIn

jOut: procedure expose m.
parse arg arg
    call jWrite m.j.jOut, arg
    return
endProcedure jOut

/*--- jBuf: buffer read or write (supports datataypes) ---------------*/
jBuf: procedure expose m.
    m = oNew('Jbuf')
    call jBufReset m
    do ax=1 to arg()
        m.m.buf.ax = arg(ax)
        end
    m.m.buf.0 = ax-1
    return m
endProcedure jBuf

jBufReset: procedure expose m.
parse arg m
    m.m.stem = m'.BUF'
    m.m.buf.0 = 0
    call oSetTypePara m
    do ax=1 to arg() - 1
        m.m.buf.ax = arg(ax+1)
        m.m.buf.0 = ax
        end
    return m
endProcedure jBufReset

jBufSetTypePara: procedure expose m.
parse arg m, type
    if m.m.buf.0 <> 0 then
        call err 'jBufSetTypePara but not empty'
    return
endProcedure jBufSetTypePara

jBufOpen: procedure expose m.
parse arg m, opt
    call jClose m
    if opt == 'r' then do
        m.m.readIx = 0
        m.m.jReading = 1
        return m
        end
    if opt == 'w' then
        m.m.buf.0 = 0
    else if opt ^== 'a' then
        call err 'jBufOpen('m',' opt') with bad opt'
    m.m.jWriting = 1
    return m
endProcedure jBufOpen

jBufRead: procedure expose m.
parse arg m, var
    nx = m.m.readIx + 1
    if nx > m.m.buf.0 then
        return 0
    m.m.readIx = nx
    ty = oGetTypePara(m)
    if abbrev(ty, '=') then
        m.var = m.m.buf.nx
    else
        call oTyCopy ty, var, m'.BUF.'nx
    return 1
endProcedure jBufRead

jBufWrite: procedure expose m.
parse arg m, line
    nx = mInc(m'.BUF.0')
    ty = oGetTypePara(m)
    if abbrev(ty, '=') then
       m.m.buf.nx = line
    else
        call oTyCopy ty, m'.BUF.'nx, line
    return 1
endProcedure jBufRead
/* copy j end *********************************************************/
/* copy o begin ********************************************************
    object layer has three freatures
    *  an object may have a class which has methods
    *  an object may have a parmeterized type
    *  a class may contain field descriptions
***********************************************************************/
oClaMethod: procedure expose m.
parse arg cl, me
     if symbol('m.o.cla.cl.met.me') = 'VAR' then
         return m.o.cla.cl.met.me
     else
         call err 'no method' me 'in class' cl
endProcedure oClaMethod

oHasMethod: procedure expose m.
parse arg obj, me
     cla = oGetClass(obj)
     return symbol('m.o.cla.cl.met.me') = 'VAR'
endProcedure oHasMethod

oGetClass: procedure expose m.
parse arg Obj
     if symbol('m.o.obj2cla.Obj') = 'VAR' then
         return m.o.obj2cla.Obj
     call err 'no class found for object' obj
endProcedure oGetClass

oObjMethod: procedure expose m.
parse arg obj, me
     if symbol('m.o.obj2cla.obj') = 'VAR' then
         return oClaMethod(m.o.obj2cla.obj, me)
     if abbrev(obj, 'oCast:') then do
         cx = pos(':', obj, 7)
         return 'M="'substr(obj, cx+1)'";' ,
                 oClaMethod(substr(obj, 7,cx-7), me)
         end
     call err 'no class found for object' obj
endProcedure oObjMethod

oCast: procedure
parse arg obj, cl
     if abbrev(obj, 'oCast:') then
         obj = substr(obj, 1 + pos(':', obj, 7))
     return 'oCast:'cl':'obj
endProcedure oCast

oNewClass: procedure expose m.
parse arg name, super
  /* call oIni */
     name = oFldNew(name)
     neMe = 'O.CLA.'name'.MET'
     neFi = 'O.CLA.'name'.FLD'
     do sx=1 to words(super)
         sup = word(super, sx)
         if symbol('m.o.cla.sup') ^== 'VAR' then
             call err 'superclass' sup 'is not defined'
         if m.o.cla.sup.val ^== '' then
              m.o.cla.name.val = m.o.cla.sup.val
         if m.o.cla.sup.stem ^== '' then
              m.o.cla.name.stem = m.o.cla.sup.stem
         st = 'O.CLA.'sup'.MET'
         do x=1 to m.st.0
             olMe = m.st.x
             call oPut neMe, olMe, m.st.olMe
             end
         st = 'O.CLA.'sup'.FLD'
         do x=1 to m.st.0
             olFi = m.st.x
             call oPut neFi, olFi, m.st.olFi
             end
         end
     call oMutate 'O.CLA.'name, 'Class'
     return name
endProcedure oNewClass

oValStemFldsWKOLD: procedure expose m.
parse arg cl, m.o.cla.cl.val, m.o.cla.cl.stem, flds
    st = 'O.CLA.'cl'.FLD'
    do wx=1 by 2 to words(flds)
        call oPut st, word(flds, wx), word(flds, wx+1)
        end
    return cl
endProcedure oValStemFlds

oNewTypeWKOLD: procedure expose m.
parse arg cl, va, st, flds
    return oValStemFlds(oNewClass(cl), va, st, flds)

/*--- a field type has only fields of type '='
      finds or creates a field Type with the fields of types tps
          and the field list aFl.
          if dup = 'e' duplicate field names are resolved ------------*/
oFiTypeWKOLD: procedure expose m.
parse arg tps, aFl, dup
    if symbol('m.o.cla.fiType.tps.aFl.dup') = 'VAR' then
        return m.o.cla.fiType.tps.aFl.dup
    fs = ''
    do wx=1 to words(tps)
        t1 = oFlds(word(tps, wx))
        do fx=1 to m.t1.0
            fs = fs m.t1.fx
            end
        end
    fs = fs aFl
    fd = ''
    do wx=1 to words(fs)
        f1 = word(fs, wx)
        if wordPos(f1, fd) < 1 then do
            fd = fd f1
            end
        else if dup == 'e' then do
            do dx=2 by 1 while wordPos(f1 || dx, fn fs) > 0
                end
            fd = fd f1 || dx
            end
        end
    fd = space(fd aFl)
    if symbol('m.o.cla.fiType.fd') = 'VAR' then do
        res = m.o.cla.fiType.fd
        end
    else do
        res = oNewClass("FiType*")
        m.o.cla.fiType.fd = res
        st = 'O.CLA.'res'.FLD'
        do wx=1 to words(fd)
            call oPut st, word(fd, wx), '='
            end
        end
    m.o.cla.fiType.tps.aFl = res
    return res
endProcedure oFiType
oDecMethods: procedure expose m.
parse arg cla
     st = 'O.CLA.'cla'.MET'
     do ax=2 to arg()
         call oPut st, word(arg(ax), 1), subWord(arg(ax), 2)
         end
     return
endProcedure oDecMethods

oNew: procedure expose m.
parse arg cla
    st = 'O.CLA.'cla
    if symbol('M.st') ^== 'VAR' then
        call err 'class' cla 'is not initialized'
    nn = m.st.inst + 1
    m.st.inst = nn
    nn = 'O.C' || m.st || 'I' || nn
    if symbol('m.o.obj2cla.nn') == 'VAR' then
        call err 'oNew already defined:' nn
    m.o.obj2cla.nn = cla
    return nn
endProcedure oNew

oMutate: procedure expose m.
parse arg obj, class
    if obj == 'O.C13I12' then do
        end
    if symbol('M.O.CLA.class') ^== 'VAR' then
        call err 'class' class 'is not initialized'
    m.o.obj2cla.obj = class

    return obj
endProcedure oMutate

oSay: procedure expose m.
parse arg type, a, aPr, mPr
    ty = 'O.CLA.'type
    msg = mPr || substr(a, length(aPr)+1)
    redir = 0
    do forever
        if type == '=' then do
            say msg '=' m.a
            return
            end
        else if abbrev(type, '=') then do
            a = m.a
            msg = msg '==>' a
            redir = 1
            type = substr(type, 2)
            end
        else if left(type, 2) = '<>' then do
            k = m.a
            a = left(a, lastPos('.', a))k
            msg = msg '=<>' k
            redir = 1
            type = substr(type, 3)
            end
        else if left(type, 1) = '.' then do
            if ^ datatype(m.a.0, 'n') then
                call err 'type' type 'not stem but m.'a'.0 is' m.a.0
            type = substr(type, 2)
            if redir then do
                say msg 'stem 1..'m.a.0':' type
                end
            else do
                do y=1 to m.a.0
                    call oSay type, a'.'y, a'.', mPr'  '
                    end
                end
            return
            end
       else if redir then do
           say msg':' type
           return
           end
       else do
          leave
          end
       end
    if m.ty.val = '=' then
        say msg '=' m.a
    else
        say msg '=' m.a':' m.ty.val
       /* call oSay m.ty.val, a,==>' m.a '(to' m.ty.val')' */
    do y=1 to m.ty.fld.0
        f = m.ty.fld.y
        call oSay m.ty.fld.f , a'.'f, a'.', mPr' '
        end
    if m.ty.stem ^== '' then
        call oSay '.'m.ty.stem, a, a, mPr
    return
endProcedure oSay

oClear: procedure expose m.
parse arg type, a, val
    if abbrev(type, '.') then do
        m.a.0 = 0
        end
    else if abbrev(type, '<>') then do
        m.a = val
        call oClear substr(type, 3), left(a, lastPos('.', a))val, val
        end
    else if abbrev(type,  '=') then do
        m.a = ''
        end
    else do
        ty = 'O.CLA.'type
        if m.ty.val ^== '' then
            m.a = val
        do x = 1 to m.ty.fld.0
            k = m.ty.fld.x
            call oClear m.ty.fld.k, a'.'k, val
            end
        if m.ty.stem ^== '' then
            call m.a.0 = 0
        end
    return a
endProcedure oClear

oCopy: procedure expose m.
parse arg t, f
    if symbol('m.o.obj2cla.f') ^== 'VAR' then
        call err f 'has no class'
    cl = m.o.obj2cla.f
    m.o.obj2cla.t = m.o.obj2cla.f
    return oTyCopy(cl, t, f)
endProcedure oCopy

oTyCopy: procedure expose m.
parse arg type, t, f
    if abbrev(type, '.') then do
        do y=1 to m.f.0
            call oTyCopy substr(type, 2), t'.'y, f'.'y
            end
        m.t.0 = m.f.0
        end
    else if abbrev(type, '<>') then do
        k = m.f
        m.t = k
        call oTyCopy substr(type, 3), left(t, lastPos('.', t))k,
                                     , left(f, lastPos('.', f))k
        end
    else if abbrev(type, '=') then do
        m.t = m.f
        end
    else do
        ty = 'O.CLA.'type
        if m.ty.val ^== '' then
            m.t = m.f
        do x = 1 to m.ty.fld.0
            k = m.ty.fld.x
            call oTyCopy m.ty.fld.k, t'.'k, f'.'k
            end
        if m.ty.stem ^== '' then
            call oTyCopy '.'m.ty.stem, t, f
        end
    return t
endProcedure oTyCopy

/*--- Run ------------------------------------------------------------*/
oRunner: procedure expose m.
parse arg code
    return oRunnerReset(oNew('ORunner'), code)

oRunnerReset: procedure expose m.
parse arg m, pCode
    m.m.code = pCode
    return m
endProcedure oRunnerReset

oRun: procedure expose m.
parse arg m
    interpret m.m.code
    return
endProcedure oRun

oIni: procedure expose m.
     if m.o.ini = 1 then
         return
     m.o.ini = 1
     call oFldIni
     call mapIni
     m.o.paTy.0 = 0
     call oFldNew '=', '='
     call oDecMethods oNewClass('ORunner'), 'oRun call oRun m'
     return
endProcedure oIni
/* copy o end *********************************************************/
/* copy oFld begin *****************************************************
     defines classes with field names
          is the base for the oo layer in copy o
***********************************************************************/
/*--- initialize the module ------------------------------------------*/
oFldIni: procedure expose m.
    if m.oFld.ini = 1 then
        return
    m.oFld.ini = 1
    call mapIni
    m.o.fldOnly = mapNew()             /* map fields -> class  */
    m.o.cla.0 = 0                      /* the stem for classes */
    call oFldNew 'Class', '=', , ,     /* MetaClass definieren */
              'INST = MET .<>= FLD .<>=Class STEM =Class'
    return
endProcedure oFldIni

/*--- create a new class
          name: name of new class, a star will be replaced by a number
          va:   type of value
          st:   type of stem
          flds: pairs of field names and types
          dup:  duplicate resolver -----------------------------------*/
oFldNew: procedure expose m.
parse arg name, va, st, flds, dup
     if pos('*', name) > 0 then
         name = oPut('O.CLA', name, , '*')
     else
         call oPut 'O.CLA', name, , 'n'
     m.o.cla.name.inst = 0
     m.o.cla.name.val  = va
     m.o.cla.name.stem = st
     m.o.cla.name.FLD.0 = 0
     m.o.cla.name.MET.0 = 0
     return oFldAdd(name, flds, dup)
endProcedure oFldNew

/*--- create or find a class with only simple fields fs --------------*/
oFldOnly: procedure expose m.
parse arg fs, dup
    kk = space(fs '?'dup, 1)
    if mapHasKey(m.o.fldOnly, kk) then
        return mapGet(m.o.fldOnly, kk)
    if dup ^== 'e' then do
        ll = space(fs, 1)
        end
    else do
        ll = ''
        do wx=1 to words(fs)
            w = word(fs, wx)
            v = w
            do x=2 while wordPos(v, ff) > 0
                v = w || x
                end
            ll = space(ll v, 1)
            end
        end
    if mapHasKey(m.o.fldOnly, ll) then do
        nn = mapGet(m.o.fldOnly, ll)
        end
    else do
        nn = oFldNew('FldType*')
        st = 'O.CLA.'nn'.FLD'
        do lx=1 to words(ll)
            call oPut st, word(ll, lx), '=', dup
        end
        call mapPut m.o.fldOnly, ll, nn
        end
    call mapPut m.o.fldOnly, kk, nn
    return nn
endProcedure oFldOnly

/*--- return the stem of flds of class type --------------------------*/
oFlds: procedure expose m.
parse arg type
    return 'O.CLA.'type'.FLD'

/*--- return the concatenation of the fields of type ty in stem st
           formated by fmt -------------------------------------------*/
oFldCat: procedure expose m.
parse arg ty, st, fmt
    flds = oFlds(ty)
    res = ''
    do ix=1 to m.flds.0
        f = m.flds.ix
        if fmt == '' then
            res = res m.st.f
        else
            res = res fmt(m.st.f, m.fmt.ix)
        end
    return substr(res, 2)
endProcedure oFldCat

/*--- add fields to class cl given as name type pairs in fs ----------*/
oFldAdd: procedure expose m.
parse arg cla, fs, dup
    st = 'O.CLA.'cla'.FLD'
    do ix=1 by 2 to words(fs)
         call oPut st, word(fs, ix), word(fs, ix+1), dup
         end
    return cla
endProcedure oFldAdd

/*--- add/put key k with value v to stem st
      duplicate handling dup:
          * replace * in k by a number until it is new
          e add a number in it is not new
          o replace old value at existing key
          = add a new key, fail if key exists and value is different
          ------------------------------------------------------------*/
oPut: procedure expose m.
parse arg st, k, v, dup
    if dup = '*' then do
        cx = pos('*', k)
        if cx < 1 then
            call err 'no * in key' k
        k = oPutDupResolve(st, left(k, cx-1), 1)
        end
    else if symbol('m.st.k') = 'VAR' then do
        if dup = '' | dup = 'o' then do
            m.st.k = v
            return k
            end
        if dup = '=' then do
            if v <> m.st.k | ^ (v = '' & datatype(m.st.k, 'n')) then
                call err 'not =: m.'st'.'k '=>' m.st.k '<>' v
            return k
            end
        if dup = 'e' then
            k = oPutDupResolve(st, k, 2)
        else
            call err 'key' k 'exists in' st 'but dup' dup
        end
    else if dup = 'o' then
        call err 'old key' k 'does not exist in' st
    if datatype(k, 'n') | words(k) <> 1 | pos('.', k) > 0 then
        call err 'illegal name' k
    x = m.st.0 + 1
    m.st.0 = x
    m.st.x = k
    if v == '' then
        m.st.k = x
    else
        m.st.k = v
    return k
endProcedure oPut

oPutDupResolve: procedure expose m.
parse arg st, k, b
     do ix=b
         a = k || ix
         if symbol('m.st.a') <> 'VAR' then
             return a
         end
endProcedure oPutDupResolve

/*--- parameterized types --------------------------------------------*/
oGetTypePara: procedure expose m.
parse arg m
    if symbol('m.o.tyPa.m') == 'VAR' then
        return m.o.tyPa.m
    else
        return '='
endProcedure oGetTypePara

oSetTypePara: procedure expose m.
parse arg m, type, noCall
    if type = '' then
        type = '='
    if oGetTypePara(m) == type then
        return
    if noCall ^== 'noCall' then
        interpret oObjMethod(m, 'oSetTypePara')
    m.o.tyPa.m = type
    return
endProcedure oSetTypePara
/* copy oFld  end   ***************************************************/
/* copy map begin ******************************************************
    a map stores values at keys
    it may also maintain a list of keys
    the basic ideas are similar to the java Interface java.util.Map
    contrary to stems we also handle keys longer then 250 bytes
***********************************************************************/
/*--- create a new map ----------------------------------------------*/
mapNew: procedure expose m.
parse arg opt
    return mapReset('MAP.'mInc('MAP.0') , opt)
endProcedure mapNew

/*--- make an empty map, opt=K means maintain a stem of keys ---------*/
mapReset: procedure expose m.
    parse arg a, opt
    if symbol('m.map.keys.a') == 'VAR' then
        call mapClear a
    upper opt
    if opt = '=' then
        st = a
    else if opt = 'K' then
        st = 'MAP.KEYS.'a
    else
        st = ''
    m.map.keys.a = st
    if st ^== '' then
        m.st.0 = 0
    if abbrev(a, 'MAP.') then
         m.map.loKy.a.0 = 0
    return a
endProcedure

/*--- remove all entries ---------------------------------------------*/
mapClear: procedure expose m.
parse arg a
    st = mapKeys(a)
    do kx=1 to m.st.0
        k = m.st.kx
        drop m.a.k m.st.kx
        end
    m.st.0 = 0
    if abbrev(a, 'MAP.') then do
        do kx=1 to m.map.loKy.a.0
            drop m.map.loKy.a.kx m.map.loVa.a.kx
            end
        m.map.loKy.a.0 = 0
        end
    return a
endProcedure mapClear

/*--- return a stem of all keys (including removed ones) -------------*/
mapKeys: procedure expose m.
parse arg a
    if m.map.keys.a == '' then
        call err 'mapKeys('a') with no keys'
     return m.map.keys.a
endProcedure mapKeys

/*--- add a new key value pair to the map ----------------------------*/
mapAdd: procedure expose m.
parse arg a, ky, val
    if mapValAdr(a, ky) ^== '' then
        call err 'duplicate key in mAdd('a',' ky',' val')'
    if length(ky) < 200 then do
        m.a.ky = val
        end
    else do
        kx = mInc('MAP.LOKY.'a'.0')
        m.map.loKy.a.kx = ky
        m.map.loVa.a.kx = val
        end
    if m.map.keys.a ^== '' then
        return mAdd(m.map.keys.a, ky)
    return
endProcedure mapAdd

/*--- change the value at a key or add key value ---------------------*/
mapPut: procedure expose m.
parse arg a, ky, val
    vv = mapValAdr(a, ky)
    if vv ^== '' then
        m.vv = val
    else
        call mapAdd a, ky, val
    return val
endProcedure mapPut

/*--- return the value pointer for a key, '' if non existang ---------*/
mapValAdr: procedure expose m.
parse arg a, ky
    if length(ky) < 200 then do
        if symbol('m.a.ky') == 'VAR' then
            return a'.'ky
        end
    else if ^ abbrev(a, 'MAP.') then do
        call err 'key too long mapValAdr('a',' ky')'
        end
    else do
        do kx=1 to m.map.loKy.a.0
            if m.map.loKy.a.kx == ky then
                return 'MAP.LOVA.'a'.'kx
            end
        end
    return ''
endProcedure mapValAdr

/*--- remove a key from the map, do nothing if it is missing ---------*/
mapRemove: procedure expose m.
parse arg a, ky
    val = m.a.ky
    vv = mapValAdr(a, ky)
    if vv == '' then
        return ''
    if abbrev(vv, 'MAP.LOVA.') then
        call err 'not implemented mapRemove('a',' ky')'
    drop m.a.ky
    return val
endProcedure mapRemove

/*--- return 1 if key ky exists in map a, 0 otherwise ----------------*/
mapHasKey: procedure expose m.
parse arg a, ky
    return mapValAdr(a, ky) ^== ''
endProcedure mapHasKey

/*--- return the value of key ky in map a,
          fail if it does not exist ----------------------------------*/
mapGet: procedure expose m.
parse arg a, ky, noKey
    vv =  mapValAdr(a, ky)
    if vv == '' then
        call err 'missing key in mapGet('a',' ky')'
    return m.vv
endProcedure mapGet

/*--- initialize the module ------------------------------------------*/
mapIni: procedure expose m.
    if m.map.ini = 1 then
        return
    m.map.ini = 1
    call mIni
    m.map.0 = 0
    return
endProcedure mapIni
/* copy map end *******************************************************/
/* 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
***********************************************************************/
/*--- increase m.a and return it (fail if undefined) -----------------*/
mInc: procedure expose m.
    parse arg a
    m.a = m.a + 1
    return m.a
endProcedure mInc

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

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

/*--- 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 all elements of a stem together ----------------------------*/
mCat: procedure expose m.
parse arg st, mid
    if m.st.0 < 1 then
        return ''
    res = m.st.1
    do x=2 to m.st.0
        res = res || mid || m.st.x
        end
    return res
endProcedure mCat

mIni: procedure expose m.
    if m.m.ini = 1 then
        return
    m.m.ini = 1
    m.mAlfLC  = 'abcdefghijklmnopqrstuvwxyz'
    m.mAlfUC  = translate(m.mAlfLC)
    m.mAlfa   = m.mAlfLC || m.mAlfUC
    m.mAlfNum = m.mAlfa || '0123456789'
    m.mAlfDot = m.mAlfNum || '.'
    return
endProcedure mIni
/* copy m end *********************************************************/
/* 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 expose m.
    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 timing() 'lmdlist save' grp lev
        call adrTso 'alloc dd('grp') shr dsn('grp'.datasets)'
        end
    else do
        call trc 'no datasets found' timing() '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 expose m.
    parse arg grp
    call readDDEnd grp
    call adrTso 'free dd('grp')'
return /* end lmdEnd */

lmd: procedure expose m.
    parse arg lev, withVol
    call lmdBegin gg1, lev
    do while lmdNext(gg1, q., withVol)
        do x=1 to q.0
           call jOut q.x
           end
        end
    call lmdEnd gg1
    return
endProcedure lmd
/**********************************************************************
    member list of a pds:
        call sequence x=lmmBegin(dsn) lmmNext(x) * lmmEnd(x)
***********************************************************************/
lmm: procedure expose m.
parse arg dsn
    id = lmmBegin(dsn)
    do ix=1 by 1
        m = lmmNext(id)
        if m = '' then
            leave
        call jOut m
        end
    call lmmEnd id
    return
endProcedure lmm

lmmBegin: procedure expose m.
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 expose m.
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 expose m.
parse arg lmmId opt
    if adrIsp("LMMLIST DATAID("lmmid")" ,
               "OPTION(LIST) MEMBER(Mbr)" opt, 4 8) = 0 then
        return strip(mbr)
    else
        return ''
endProcedure lmmNext

lmmRm: procedure expose m.
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
endProcedure lmmRm
/*--- address ispf with error checking -------------------------------*/
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

/*--- address editor with error checking -----------------------------*/
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 expose m.
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 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.
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 arg ggDD
    call adrTso 'execio 0 diskr' ggDD '(finis)'
return /* end readDDEnd */

/*--- prepare writing to DD ggDD -------------------------------------*/
writeDDBegin: procedure expose m.
    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 expose m.
    parse arg ggDD
    call adrTso 'execio 0 diskw' ggDD '(finis)'
return /* end writeDDEnd */

/*--- 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, disp, dd, retRc
    ds = ''
    m.dsnAlloc.dsn = 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))
    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
            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 abbrev(w, 'DSN(') then
            ds = strip(substr(w, 5, length(w)-5))
        else if ds = '' then
            ds = dsn2jcl(w)
        else
            leave
        end
    rest = subword(spec, wx)
    if abbrev(rest, '.') then
        rest = substr(rest, 2)
    parse var rest rest ':' nn
    if dd <> '' & ds = '' & rest = '' & ^ abbrev(disp, 'SYSO') then
        call err "'return" dd"' no longer supported please use -"dd
    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 disp = '' then
        disp = 'SHR'
    else if pos('(', ds) < 1 then
        nop
    else if disp = 'MOD' then
        call err 'disp mod for' ds
    else
        disp = 'SHR'
    m.dsnAlloc.dsn = ds
    if pos('/', ds) > 0 then
        return csmAlloc(dd, disp, ds, rest, nn, retRc)
    else
        return tsoAlloc(dd, disp, ds, rest, nn, retRc)
endProcedure dsnAlloc

tsoAlloc: procedure expose m.
parse arg dd, disp, dsn, rest, nn, retRc
    c = 'alloc dd('dd')' disp
    if dsn <> '' then
        c = c "DSN('"dsn"')"
    if retRc <> '' | nn = '' then do
        alRc = adrTso(c rest, retRc)
        if alRc <> 0 then
            return alRc
        return dd 'call adrTso "free dd('dd')";'
        end
    do retry=0 by 1
        alRc = adrTso(c rest, '*')
        if alRc = 0 then
            return dd 'call adrTso "free dd('dd')";'
        if retry > 0 | nn = '' | wordPos(disp, 'OLD SHR') < 1 ,
            | sysDsn("'"m.dsnAlloc.dsn"'") ^== 'DATASET NOT FOUND' then
            call err 'tsoAlloc rc' alRc 'for' c rest
        say 'tsoAlloc rc' alRc 'for' c rest '...trying to create'
        call adrTso 'alloc dd('dd') new catalog' dsnCreateAtts(dsn, nn)
        call adrTso 'free  dd('dd')'
        end
endProcedure tsoAlloc

dsnCreateAtts: procedure expose m.
parse arg dsn, atts, forCsm
    bl = 32760
    if abbrev(atts, ':') then do
        rl = substr(atts, 3)
        if abbrev(atts, ':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(atts, 2, 1) 'B'
            end
        end
    if pos('(', dsn) > 0 then
        po = 'dsntype(library) dsorg(po)'
    else
        po = ''
    dsn = dsnSetMbr(dsn)
    if forCsm == 1 then
        return "dataset('"dsn"')" po,
                "recfm("space(recfm, 0)") lrecl("rl") blkSize("bl")" ,
                "mgmtclas(s005y000) space(10, 1000) cylinder"
    else
        return "dsn('"dsn"')" po,
                "recfm("recfm") lrecl("rl") block("bl")" ,
                "mgmtclas(s005y000) space(10, 1000) cyl"
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 ******************************************************
    messages, errorhandling,help
***********************************************************************/
/* configure err -----------------------------------------------------*/
errReset: procedure expose m.
parse arg oo, ha
    if pos('I', translate(oo)) > 0 then
        call adrIsp 'control errors return'
    m.err.opt = translate(oo, 'h', 'H')
    if ha == '' then
        drop m.err.handler
    else
        m.err.handler = ha
    return
endSubroutine errReset

/*--- error routine: abend with message ------------------------------*/
err:
    parse arg ggTxt, ggOpt
    drop err handler opt
    if ggOpt == '' & symbol('m.err.handler') == 'VAR' then
        interpret m.err.handler
    call errSay ggTxt
    parse source . . ggS3 .                           /* current rexx */
    if ggOpt == '' | ggOpt == '*' then
        ggOpt = translate(value('m.err.opt'), 'ht', 'HT')
    if pos('h', ggOpt) > 0  then do
        say 'fatal error in' ggS3': divide by zero to show stackHistory'
        x = 1 / 0
        end
    say 'fatal error in' ggS3': exit(12)'
    exit errSetRc(12)
endSubroutine err

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

/*--- say an errorMessage msg with pref pref
           split message in lines at '/n'
           say addition message in stem st ---------------------------*/
errSay: procedure expose m.
parse arg msg, st, pref
    parse source . . ggS3 .                           /* current rexx */
    if pref == 'e' | (pref == '' & st == '') then
        msg = 'fatal error:' msg
    else if pref == 'w' then
        msgf = 'warning:' msg
    else if pref == 0 then
        nop
    else if right(pref, 1) ^== ' ' then
        msg = pref':' msg
    else
        msg = pref || msg
    sx = 0
    bx = -1
    do lx=1 until bx >= length(msg)
        ex = pos('\n', msg, bx+2)
        if ex < 1 then
            ex = length(msg)+1
        if st == '' then do
            say substr(msg, bx+2, ex-bx-2)
            end
        else do
            sx = sx+1
            m.st.sx = substr(msg, bx+2, ex-bx-2)
            m.st.0 = sx
            end
        bx = ex
        end
    return
endProcedure errSay

/*--- abend with Message after displaying help -----------------------*/
errHelp: procedure expose m.
parse arg msg, op
    say 'fatal error:' msg
    call help
    call err msg, op
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
----------------------------------------------------------------------*/
errSetRc: procedure expose m.
parse arg zIspfRc
    if sysVar('sysISPF') = 'ACTIVE' then do
        address ispExec vput 'zIspfRc' shared
        end
    return zIspfRc
endProcedure errSetRc

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

debug: procedure expose m.
parse arg msg
    if m.debug == 1 then
        say 'debug' msg
    return
endProcedure debug

/*--- return current time and cpu usage ------------------------------*/
timing: procedure expose m.
return time() time('E') sysvar('syscpu') /* sysvar('syssrv') */

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