Tuesday, December 19, 2017

A simple , efficient and low cost buffer pool tool

Buffer pool tuning in its simplest form is quite easy to explain : group objects that have a similar profile together   .... Like in the farm , you won't put the wolf and a sheep together ...
So we start be putting catalog objects in BP0,  In BP1 tablespaces and BP2 indexes ...
Then we can zoom in BP1 can be divided in 2 BP  : Objects with random profile and Objects with Sequential profiles ....etc...

The question is , how can i get the informations. Their cost (overhead) is important. And your  program must be very quick to catch all the IOs in your system (ideally written in Assembler with the higher run priority than DB2 itself ) ... all the things difficult to have.  BufferPool Tool from Joel Goldstein is based on this principle. And more then 10 years i tried to catch and decode IFCID 6, 7 ...    
I had fun writing these programs to catch the IFCID  in C language , than to process it using Cobol ... 
But IBM then provides this  precious data in DIS BP LSTATS command, it costs nothing, and you have what you need with these commands.


Here is a simple , but efficient buffer pool tool based on the command display bp() db() sp() lstats that gives i/O stats for an object.
If you submit this command for all the objects of your DB2 subsystem , each x minutes , than you have the I/O stats for your entire system without any noticeable overhead as these data are already "inside" your Db2.

So the steps are :
1/ Generate the display commands for your system. You can easily do this with DSNTEP2, and using this SQL :
SELECT
  '-DIS BUFFERPOOL(' !! RTRIM(A.BPOOL) !! ') LSTATS(*)'
  !! ' DBN('
  !! RTRIM(A.DBNAME) !! ') SP('
  !! A.PAGESET !! ')'  AS CMD
FROM(
  SELECT DISTINCT BPOOL, DBNAME, NAME AS PAGESET,
    PARTITIONS AS PARTS
    FROM SYSIBM.SYSTABLESPACE
  UNION
  -- THE MAX(PARTITION) IS USED TO RETURN ONE ROW ONLY FOR EACH INDEX
  SELECT DISTINCT BPOOL, DBNAME, INDEXSPACE AS PAGESET
  , MAX(PARTITION) AS PARTS
  FROM SYSIBM.SYSINDEXES X, SYSIBM.SYSINDEXPART P
  WHERE X.NAME=P.IXNAME
    AND X.CREATOR=P.IXCREATOR
  GROUP BY BPOOL, DBNAME, INDEXSPACE 
) A 
You can customize the SQL to get only the objects you want to (Example : Check I/O stats for all objects in BP32K) 



2/ Prepare a JCL which submits  these commands and store the output in a sequential file with DISP=MOD settings (So create the output file with RECFM=FB, LRECL=133)
//jobcard
//DISDB    EXEC PGM=IKJEFT01,DYNAMNBR=20
//SYSTSPRT  DD DSN=SYSTMP.OUTPUT.DISBP,DISP=MOD
//SYSTSIN   DD *
DSN SYSTEM(DBPX)
-DIS BUFFERPOOL(BP32K) LSTATS(*) DBN(BA2PENB1) SP(NYSAI85 )
(...)

3/ Submit this REXX : this rexx submits the JCL  'hlv(ZZ)'  previously prepared every x minutes (5 in this sample) 
I use the REXXWAIT assembler provided in CBTTAPE , but the call to SLEEP is OK (uncomment the  appropriate code section, using SLEEP , duree is number of seconds , duree=300 for 5 minutes)

/*REXX*/
filen='SYSTMP.OUTPUT.DISBP'
duree='00050000'   /*hhmmsscc*/
DSNA="'HLV(ZZ)'"
i=0
do  72              /* boucle */
    i=i+1
    say time() 'submit' DSNA 'iteration' i
    call logw
    ADDRESS TSO "SUBMIT " DSNA
    call gosleep
end
 
exit
 
LOGW:
     Say 'Output to ' oufw
     oufw = "'" !! filen !!  "'"
     Say 'Output to' oufw
     "ALLOC FI(OUFw) DA("oufw") MOD CATALOG REUSE" ,
     "LRECL(133) RECFM(F B) TRACKS SPACE(50,50) RELEASE"
     rec.0=1
     rec.1=date() time()
     say 'record:' rec.1
     "EXECIO 1 DISKW OUFw (STEM rec. "
     "EXECIO 0 DISKW OUFw (FINIS"
     "FREE DD(OUFW)"
    return
Gosleep:
  /*  need UNIX Services active
  Call SYSCALLS 'ON'
  Address SYSCALL 'SLEEP' duree
  say 'Sleep RC=' RC
  Call SYSCALLS 'OFF'    */
  rc=rexxwait(duree)
  if rc>0 then do; say 'error calling REXXWAIT' rc; exit 8; end
return

 4/ When the JCL is ended, submit this Rexx to decode the output , and produce a CSV dataset that you will export to Excel 



/*REXX*/                                                                00160003/*cette version est une version manuelle du display BP          */      00160003/*on lance le jcl display toutes les x minutes, il alimente un  */      00160003/*fichier , et ce rexx traite ce fichier                        */      00160003/*La version Instream s'appelle REXBP2                          */      00160003TRACE O                                                                 00170003ARG NOMINP  DEL                                                         00190003"FREE  FI(INP)"                                                         00200003"ALLOC FI(INP) DSNAME('"NOMINP"') SHR"                                  00210003"FREE  FI(OUT)"                                                         00220003                                                                        00250003month = 'Jan Feb Mar Apr May Jun Jul Aug Sep Oct Nov Dec'               00250003NOMOUTP = NOMINP !! '.OUT'                                              00260003If DEL = 'D' then                                                       00260003    "DELETE '"NOMOUTP"'"                                                00260003"ALLOC F(OUT) DA('"NOMOUTP"') LRECL(150) SPACE(10,5),                   00270003  CYL BLKSIZE(15000)  RECFM(F,B) NEW"                                   00280003if rc > 0 then do; say "File allocation error" ; exit 8; end            00280003ENDF=0                                                                  00280003FINDK=0                                                                 00280003"execio 0 diskw out (OPEN"      /*Open */                               680003"execio 0 diskr INP (OPEN"      /*Open */                               680003/*ecrire 1er record for CSV = header */rec1= 'Date,Time,Hour,ObjType,DbName,ObjName,DsNum,bpname,' ,      'vpcur,vpmax,' ,      'vpccur,vpcmax,' ,      'avgwtsync,maxwtsync,' ,      'syncio,' ,      'avgwtasync,maxwtasync,' ,      'asynpg,' ,      'asynio'"execio 1 diskw out (stem rec  )"i=0                                                                       003220Tem467I=0                                                                 003220Tem453I=0                                                                 003220Tem455I=0                                                                 003220Tem456I=0                                                                 003220DO UNTIL ENDF=1  "EXECIO 1  DISKR INP (STEM TRC. )"                                      002900  IF TRC.0   < 1   THEN ENDF=1                                            003100  i=i+1  Msgid  = word(TRC.1,1)  /* Date value */  if words(TRC.1) = 4 & pos(word(trc.1,2),month) > 0 then            do               datex = word(trc.1,1) word(trc.1,2) word(trc.1,3)               timex = word(trc.1,4)               hourx = substr(word(trc.1,4),1,2)               iterate            end  if  Msgid  = 'DSNB401I' then                  do                     BpnameO=BpnameN  /* Old / New */                     BpnameN=strip(word(trc.1,5),,',')                     iterate                  end  if Msgid  = 'DSNB499I' then                  do                     say  '!!! DSNB499I Missing data !!!'                     rec1='!!! DSNB499I Missing data !!!'                     "execio 1 diskw out (stem rec  )"                  680003                     iterate                  end  if Msgid  = 'DSNB467I' then             do                 /* write previous DSNB467I record*/                 call procrec                 Tem467I=1                 vpcur=0                 vpmax=0                 vpccur=0                 vpcmax=0                 syncio=0                 avgwtasync=0;maxwtasync=0                 avgwtsync=0;maxwtsync=0                 asynpg=0                 asynio=0                 /* try to ensure that we are well aligned */                 y= pos('FOR',trc.1)                 if y = 30  then                          y = 34 else y = 33                 Libel  =substr(trc.1,y,35)                 parse var Libel Dum1 ObjType Dum2 DBName '.' ObjName                 say Libel                 say Objtype                 If Objtype = 'TABLE' then Objtype= 'T'                                      else Objtype= 'I'                 /* on avance de 2 lignes */                              002900                 "EXECIO 2  DISKR INP (STEM TRC. )"                       002900                   x=pos(':',trc.2,1)                   if x=0 then do;say "error : nfd";exit 8;end                   x=x+1                 dsnum=substr(trc.2,x,6)             end  /* tant qu'on a pas trouve dsndb467i on cherche */  if  Tem467I = 0 then iterate  /*ici on a trouvĂ© Tem467I dans ce record ou dans les precedents */  /* on s'attend a trouver soit 453I, soit 455I, soit 456I*/  if Msgid  = 'DSNB453I' then do                 Tem453I=1                 "EXECIO 1  DISKR INP (STEM TRC. )"                       002900                   x=pos('=',trc.1,1)                   if x=0 then do;say "error = nfd";exit 8;end                   x=x+1                 vpcur=substr(trc.1,x,9)                   x=pos('=',trc.1,x)                   if x=0 then do;say "error = nfd";exit 8;end                   x=x+1                 vpmax=substr(trc.1,x,9)                 "EXECIO 1  DISKR INP (STEM TRC. )"                       002900                   x=pos('=',trc.1,1)                   if x=0 then do;say "error = nfd";exit 8;end                   x=x+1                 vpccur=substr(trc.1,x,9)                   x=pos('=',trc.1,x)                   if x=0 then do;say "error = nfd";exit 8;end                   x=x+1                 vpcmax=substr(trc.1,x,9)                 iterate                end  if Msgid  = 'DSNB455I' then do                 Tem455I=1                 "EXECIO 1  DISKR INP (STEM TRC. )"                       002900                   x=pos('=',trc.1,1)                   if x=0 then do;say "error = nfd";exit 8;end                   x=x+1                 avgwtsync=substr(trc.1,x,9)                   x=pos('=',trc.1,x)                   if x=0 then do;say "error = nfd";exit 8;end                   x=x+1                 maxwtsync=substr(trc.1,x,9)                 "EXECIO 1  DISKR INP (STEM TRC. )"                       002900                   x=pos('=',trc.1,1)                   if x=0 then do;say "error = nfd";exit 8;end                   x=x+1                 syncio=substr(trc.1,x,9)                 iterate                end  if Msgid  = 'DSNB456I' then do                 Tem456I=1                 "EXECIO 1  DISKR INP (STEM TRC. )"                       002900                   x=pos('=',trc.1,1)                   if x=0 then do;say "error = nfd";exit 8;end                   x=x+1                 avgwtasync=substr(trc.1,x,9)                   x=pos('=',trc.1,x)                   if x=0 then do;say "error = nfd";exit 8;end                   x=x+1                 maxwtasync=substr(trc.1,x,9)                 "EXECIO 1  DISKR INP (STEM TRC. )"                       002900                   x=pos('=',trc.1,1)                   if x=0 then do;say "error = nfd";exit 8;end                   x=x+1                 asynpg=substr(trc.1,x,9)                   x=pos('=',trc.1,x)                   if x=0 then do;say "error = nfd";exit 8;end                   x=x+1                 asynio=substr(trc.1,x,9)                 iterate                endEND /* end do until   *//* flush du record encours*/call procrec"execio 0 diskw out (FINIS"      /*close file */"EXECIO 0 diskr inp (FINIS""free  fi(out)""free fi(inp)"say 'fin du programme'exit                                                                        00718608procrec:                                                                00718608  if (tem453i = 1 !  tem 455i = 1 !  tem456i=1)  then  do     /*ecrire le record */ 
     rec1= Datex !! ',' !! Timex !! ',',          !! hourx   !! ',' ,          !! ObjType !! ',' !! DbName!! ',' !! ObjName !! ',' ,          !! Dsnum !! ',' !! BpnameO !! ',' ,          !! vpcur !! ',' !! vpmax !! ',' ,          !! vpccur !! ',' !! vpcmax !! ',' ,          !! avgwtsync !! ',' !! maxwtsync !! ',' ,          !! syncio !! ',' ,          !! avgwtasync !! ',' !! maxwtasync !! ',' ,          !! asynpg !! ',' ,          !! asynio     /*       say 'ecrire'   */                                         680003     "execio 1 diskw out (stem rec  )"                                  680003     tem453i=0                                                          680003     tem455i=0                                                          680003     tem456i=0                                                          680003  endret
urn


The  jcl which submits this Rexx is :
//* 1ST PARAM : THE RESULT OF  DISPLAY BP LSTATS
//* 2E PARAM : IF D = DELETE .OUT DATASET BEFORE PROCESSING
//REXBPF    EXEC PGM=IKJEFT01,DYNAMNBR=20,REGION=0M,COND=(4,LT)
//SYSEXEC  DD DISP=SHR,DSN=Your REXX PDS
//SYSTSPRT DD SYSOUT=*
//SYSPRINT DD SYSOUT=*
//SYSTSIN  DD  *
 REXBPF SYSTMP.OUTPUT.DISBP D
/*

The Rexx provides an SYSTMP.OUTPUT.DISBP.OUT   which looks like this 
Date,Time,Hour,ObjType,DbName,ObjName,DsNum,bpname, vpcur,vpmax, vpccur,vpcmax, avgwtsync,maxwtsync, syncio, avgwtasync,maxwtasync, asynpg, asynio19 Dec 2017,07:16:45,07,T,BA2PENB1,NYSAI85   ,    1 ,BP32K,   568   ,  2056   ,     0   ,     2   ,     1   ,     6   ,  2099   ,     0   ,     2   ,19 Dec 2017,07:16:45,07,T,BA2PENB1,NYSAI96   ,    1 ,BP32K,   699   ,   699   ,     0   ,     0   ,     1   ,     5   ,   196   ,     0   ,     3   ,19 Dec 2017,07:16:45,07,T,BA2PENB1,NYSAI97   ,    1 ,BP32K,     5   ,  3094   ,     0   ,     0   ,     2   ,    11   ,   439   ,     0   ,     2   ,19 Dec 2017,07:16:45,07,T,BA2PENB1,NYSAJTS   ,    1 ,BP32K,     7   ,     7   ,     0   ,     4   ,     1   ,     1   ,     1   ,0,0,0,019 Dec 2017,07:16:45,07,T,BA2PENB1,NYSAR73   ,    1 ,BP32K,     0   ,   434   ,     0   ,     0   ,     1   ,     5   ,   236   ,     0   ,     2   ,19 Dec 2017,07:16:45,07,T,BA2PENB1,NYTSAI0B  ,    1 ,BP32K,     4   ,  2544   ,     0   ,     0   ,     1   ,     5   ,   190   ,     0   ,     1   ,

In Excel, with analysis :
This shows the BP32K bufferpool usage by objects by SyncIO  


Friday, October 6, 2017

Assembler to select only 101 records for a particular connection type


Original post 06/10/2017

31/10/2017 : Teasing  ... Coming Soon , Assembler to select 101 records by specifying  an SSID,  a beginning and ending period, and a connection type

Rexx is fun, but rexx is slow.
When you have millions of accounting record to process, and you run a rexx to read it, sooner or later you will hit the problem of performance ( cpu consumption).
That's why my aim before retirement [... still 20 years :-( ]  is to write all the accounting stuffs in assembler. But there is still a long road ahead as with assembler , if you don't write programs you quickly forget all ...

So here is an assembler which reads 101 records and preselect a particular connection type (in this example DDF  runs) , i also have another similar program to select a particular DB2 ID (useful when there is more than 1 DB2 on the LPAR)


BAL      OPSYN     BAS
BALR     OPSYN     BASR
SMF101   START       0
*----------------------------------------------------------*
* Program     : SMF101                                    -*
* Written on  : 21.09.2017                                -*
* Author      : Nguyen Duc Tuan                           -*
* DESCRIPTION : The SMF101 decoder project                -*
*----------------------------------------------------------*
BEGIN    SAVE  (14,12)
         BALR  3,0
         USING *,3
         ST    13,SAVE+4
         LA    13,SAVE
*
         OPEN      (SMFIN,INPUT,SMFOUT,OUTPUT)   OPEN INPUT OUTPUT
         OPEN      (SNAPDD,OUTPUT)
         SR        8,8               0=>R8 READ COUNT
         SR        9,9               0=>R9 WR COUNT
*----------------------------------------------------------*
*- MAIN LOOP                                              -*
*----------------------------------------------------------*
READON   BAL       6,READREC                     READ RECORD
         BAL       6,SELREC                      SELECT RECORD
         B         READON                        GET NEXT RECORD
*                                                END OF FILE
ENDFILE  SNAP      DCB=SNAPDD,ID=99,PDATA=(REGS)   SNAPSHOT
         CLOSE     (SMFIN,,SMFOUT,,SNAPDD)       CLOSE FILES
*
* STANDARD EXIT SEQUENCE
         L     13,SAVE+4
         LM    14,12,12(13)
         SR    15,15
         BR    14            R14 = RETURNED ADDRESS
*----------------------------------------------------------*
*- READREC ROUTINE                                        -*
*----------------------------------------------------------*
READREC  DS        0H
         USING     SM101,4     SET UP ADDR.ABILITY
         GET       SMFIN       GET RECORD LOCATE MODE
         LR        4,1         LOAD R4 WITH RECORD
         A         8,=F'1'     Increment R8 by 1
         BR        6
*----------------------------------------------------------*
*- SELREC  ROUTINE : SELECT ONLY SMF 101 RECORDS          -*
*----------------------------------------------------------*
SELREC   CLI       SM101RTY,X'65'       IS THIS SMF101 ?
         BE        PROCREC               YES
         BR        6
*----------------------------------------------------------*
*- PROCREC ROUTINE                                        -*
*----------------------------------------------------------*
PROCREC  DS        0H
* Begin processing
         LA        5,SM101END      Adresse de debut self-def
         USING     QWS0,5           --> Self def-Section
         L         7,QWS00PSO      QWD00PSO est un Offset par rapport
         AR        7,4             au debut du record, pour avoir
*                                  l'ad.absolue il faut + R4
         USING     QWHS,7           --> Prod section
         MVC       WKSSID,QWHSSSID
         MVC       WKIFCID,QWHSIID
*        WTO       MF=(E,WTOBLOCK),ROUTCDE=11
*        CLC       QWHSSSID,=C'DBT1'     SSID= DBT1
*        BE        FOUNDI
*        LA        15,4
         LA        5,QWHSEND       Adresse Correlation header
         USING     QWHC,5           --> adressabilite
*        MVC       WTOCONN,QWHCATYP
*        WTO       MF=(E,WTOBLOCK),ROUTCDE=11
         CLC       QWHCATYP,=F'8'   CONNTYPE DDF
         BE        FOUNDI
         BR        6                        RETURN
DBWORD   DS        D                DBLE WORD POUR CONVERSION
TOTRD    DS        PL5              PACK DECIMAL 5 (9 CHIFFRE + SIGNE)
PATTERN1 DC        X'40202020202020202020' MASQUE
WTOBLOC2 DC        H'84'
         DC        XL2'0000'
PRTTOTR  DS        CL10             TOTAL READ EN FORMAT DISPLAY
         DC        CL66'A'
WTOBLOCK DC        H'60'
         DC        XL2'0000'
WTOCONN  DS        F
         DC        CL72'ASM my test is ended'
WKSSID   DC        CL4'????'
WKIFCID  DC        CL4'????'
FOUNDI   DS        0H
         A         9,=F'1'   Increment R9 by 1
         PUT       SMFOUT,SM101
*        WTO       'FOUNDI',ROUTCDE=11
         BR        6
*----------------------------------------------------------*
*- FILE SECTION                                           -*
*----------------------------------------------------------*
SMFIN    DCB   DDNAME=SMFIN,                                           X
               DSORG=PS,                                               X
               MACRF=GL,                                               X
               EODAD=ENDFILE,                                          X
               BFTEK=A,                                                X
               RECFM=VBS
SMFOUT   DCB   DDNAME=SMFOUT,                                          X
               DSORG=PS,                                               X
               MACRF=PM,                                               X
               LRECL=32767,                                            X
               RECFM=VBS,                                              X
               BLKSIZE=27998
SNAPDD   DCB   DSORG=PS,RECFM=VBA,MACRF=W,LRECL=125,BLKSIZE=882,       X
               DDNAME=SNAPDD
*----------------------------------------------------------*
*- WORKING STORAGE SECTION                                -*
*----------------------------------------------------------*
SAVE     DS        18F
*----------------------------------------------------------*
*- DSECT/MACRO     SECTION                                -*
*----------------------------------------------------------*
SMFTYPDB DS        0H
         DSNDQWAS  DSECT=YES,SUBTYPE=
SMF101 CSECT
SELFDEFS DS        0H
         DSNDQWS0  DSECT=YES
SMF101 CSECT
PRODSECT DS        0H  Production Standard header
         DSNDQWHS  DSECT=YES
SMF101 CSECT
PRODSEC2 DS        0H Production Header type 2 for correlation Id
         DSNDQWHC  DSECT=YES
SMF101 CSECT
DATASECT DS        0H
         DSNDQW01  IFCID(QWHS0090)
SMF101 CSECT
LAST     DS    CL1
         END       BEGIN

Thursday, September 7, 2017

General recommendations before going to changes

Before going to changes, it is essential  to evaluate the figures. What is the total CPU,  hundred seconds/ hour it becomes interesting ... otherwise :
1/ the gain will be so slow so it is not worth doing the changes
2/ the gain will be so slow that the changes effect (statistics figures) will be difficult to detect
3/ Finally, even if the CPU is high, but if it does not happen during your peak 4HRA, you can also forget it , because it will reduce nothing on the IBM bill (for DB2 guys , you can read a good presentation from Phil Grainger about this : "How to save real dollars with SQL tuning")


I know this, but i often forget this rules ....


 

Thursday, May 11, 2017

Rexx to aggregate daily accounting in 1 hour interval summary

Last update : 11/5/2017

Same principles as the Rexx to Aggregate acct to 1 hour interval

/*REXX*/                                                                00010003
/*********************************************************************/ 00020003
/* Ce programme reporte les accounting DB2 sur chaque LPAR en format */ 00021003
/* summary : 1 enregistrement / heure/ type de connexion (Batch,     */ 00022003
/* CICS, DDF ... ) . Il s'exĂ©cute tous les jours et produit un       */ 00023003
/* fichier qui sera par la suite charger en table DB2                */ 00024003
/*********************************************************************/ 00025003
arg Smforig                                                             00026003
clnt=''                                                                 00027018
lpar=MVSVAR(SYSNAME)                                                    00027118
lpar='IPO4'                                                             00027221
hlq='SYSTMP.DBDC.DB2'                                                   00028003
/* Input SMF file */                                                    00029003
call SetSmfDS                                                           00030003
/*************************************************/                     00040003
/*  Label start_pgm for repeated runs            */                     00050003
/*  (If several DB2 by LPAR)                     */                     00060003
/*************************************************/                     00070003
if SmfOrig='B' then do                                                  00081017
    /* Input file : SMF dataset from z/OS 2.1 */                        00090003
    address TSO                                                         00100003
    "ALLOC DD(INP) SHR     bufno(80)"                                   00110003
    say 'Alloc SMF dd INP rc =' rc                                      00120003
end                                                                     00130003
else do                                                                 00140003
    address TSO                                                         00150003
    "ALLOC DD(INP) DS('"oufl"')    SHR REU bufno(80)"                   00160003
    say 'Alloc SMF dsn rc =' rc                                         00170003
end                                                                     00180003
                                                                        00181017
                                                                        00190003
start_pgm:                                                              00200003
                                                                        00210003
/* compteurs input/output */                                            00360003
reci= 0                                                                 00370003
reco= 0                                                                 00380003
recs= 0                                                                 00390003
rupture = 0                                                             00400003
nbr_conntype=0                                                          00410003
/* Ecriture Header pour CSV */                                          00420003
/* Call Write_Header */                                                 00430003
                                                                        00440003
/*==================*/                                                  00450003
/* START PROCESSING */                                                  00460003
/*==================*/                                                  00470003
Do Forever                                                              00480003
  /* Read SMF record */                                                 00490003
  "EXECIO 1 DISKR INP"                                                  00500003
  IF RC > 0 THEN DO                                                     00510003
            rcalloc=rc                                                  00520003
            if rc = 2 then                                              00530003
              do                                                        00540003
                  SAY 'End of SMF dataset - input records' reci         00550003
                  call write_summary                                    00560003
              end                                                       00570003
            else                                                        00580003
              say 'SMF read error' rc                                   00590003
            LEAVE /* sortir de la boucle Do Forever */                  00600003
  END                                                                   00610003
  PARSE PULL INPUT_REC                                                  00620003
  reci = reci+1                                                         00630003
  OFFSET = 1                                                            00640003
  /* Decode SMF HEADER */                                               00650003
  CALL DSNDQWAS                                                         00660003
  IF result = 0 then  /* SSID Ok And SMF101 */                          00670008
  DO                                                                    00680003
    recs=recs+1  /* compteurs records smf101*/                          00690003
    /*DSNDQWA0 MAP SELF-DEFINING SECT */                                00700003
    CALL DSNDQWA0 /* MAP SELF-DEFINING SECT */                          00710003
    OFFSET = QWA01PSO - 4 + 1                                           00720003
    /* These headers are always present */                              00730003
    CALL DSNDQWHS /* MAP product section STANDARD HEADER */             00740003
    CALL DSNDQWHC /* MAP CORRELATED HEADER, just after the standard*/   00750003
                  /* header Product Section */                          00760003
                                                                        00770003
    /* pointeur vers accounting section DSNDQWAC */                     00780003
    OFFSET = QWA01R1O - 4 + 1                                           00790003
    /* process each ifcid */                                            00800003
    Select                                                              00810003
         When ifcid = 3  Then                                           00820003
              do                                                        00830003
                 /* general accounting data */                          00840003
                 CALL DSNDQWAC                                          00850003
                 /* sql stats */                                        00860003
                 if QWA01R2O > 0 & lg > 0 then                          00870012
                           do                                           00871012
                            OFFSET = QWA01R2O - 4 + 1                   00880003
                            CALL DSNDQXST                               00890003
                           end                                          00900003
                        else do                                         00910003
                        /* pas de donnĂ©es sql*/                         00920003
                           selects   =0                                 00930003
                           inserts   =0                                 00940003
                           updates   =0                                 00950003
                           deletes   =0                                 00960003
                           opens     =0                                 00970003
                           fetchs    =0                                 00980003
                        end                                             00990003
                 /* s'il existe des donnees buffer, les chercher*/      01000003
                 if QWA01R3O > 0 then do                                01010003
                            OFFSET = QWA01R3O - 4 + 1                   01020003
                            CALL DSNDQBAC                               01030003
                           end                                          01040003
                        else do                                         01050003
                        /* pas de donnĂ©es buffer manager */             01060003
                           getp      =0                                 01070003
                           syncio    =0                                 01080003
                           syncwr    =0                                 01090003
                           sio       =0                                 01100003
                        end                                             01110003
              end /* end when ifcid=3*/                                 01120003
         Otherwise                                                      01130003
              do                                                        01140003
                 nop                                                    01150003
              end                                                       01160003
    end   /* select */                                                  01170003
    /* on part du principe que ifcid03 est le record accounting */      01180003
    /* maitre , a voir si on commence a traiter les autres      */      01190003
    if ifcid=3 then                                                     01200003
    do                                                                  01210003
         CALL process_summary                                           01220003
    end                                                                 01230003
  END /*    IF SM101RTY = 101  */                                       01240003
END /* Do forever */                                                    01250003
                                                                        01260003
/* close output file */                                                 01270003
"EXECIO 0 DISKW OUFS (STEM INL. FINIS"                                  01280003
"FREE DD(OUFS)"                                                         01290003
/* close input file (SMF ) */                                           01300003
"EXECIO 0 DISKR INP (STEM INL. FINIS"                                   01310003
                                                                        01320003
/* report counters  */                                                  01330003
Say 'Output records : ' reco                                            01340003
if lpar = 'IPO4' then                                                   01350003
   do                                                                   01360003
         /* process DSNI now */                                         01370003
         if ssid = 'DSNI' then /* avoid forever loop */                 01380003
         do                                                             01390003
              say 'End processing'                                      01400003
         end                                                            01410003
         else                                                           01420003
         do                                                             01430003
              ssid = 'DSNI'                                             01440003
              signal start_pgm                                          01450003
         end                                                            01460003
   end                                                                  01470003
if lpar = 'ZPR1' then                                                   01471006
   do                                                                   01472006
         /* process DSNH now */                                         01473006
         if ssid = 'DB2E' then /* avoid forever loop */                 01474007
         do                                                             01475006
              ssid = 'DB2H'                                             01475107
              signal start_pgm                                          01475206
         end                                                            01477006
         else                                                           01478006
         do                                                             01479006
              if ssid = 'DB2H' then                                     01479107
              do                                                        01479206
                   ssid = 'DB2I'                                        01479307
                   signal start_pgm                                     01479406
              end                                                       01479506
              else                                                      01479606
              do                                                        01479706
                   /* je suis la parce que ssid = 'DSNI'*/              01479806
                   say 'Tous les DB2 de ZPR1 sont traitĂ©s'              01479906
              end                                                       01480006
         end                                                            01480806
   end                                                                  01480906
"FREE DD(INP)"                                                          01481006
EXIT rcalloc                                                            01490003
                                                                        01500003
                                                                        01510003
/* decode smf header */                                                 01520003
DSNDQWAS:                                                               01530003
   OFFSET = OFFSET + 1                                                  01540003
   /* SM100RTY DS XL1 RECORD TYPE X'64' OR 101 */                       01550003
   SM101RTY = C2D(SUBSTR(INPUT_REC,OFFSET,1))                           01560003
   if sm101rty <> 101 then return 4;                                    01570008
   sm101ssi = SUBSTR(INPUT_REC,OFFSET+13,4)                             01571008
   if clnt <> 'CAAGIS' then                                             01572018
   if sm101ssi <> ssid then return 4;                                   01573018
   OFFSET = OFFSET + 1                                                  01580003
                                                                        01590003
   /* SM101TME DS XL4 TIME SMF MOVED RECORD */                          01600003
   SM101TME = C2D(SUBSTR(INPUT_REC,OFFSET,4))                           01610003
   OFFSET = OFFSET + 4                                                  01620003
   CALL GET_FMT_TIME                                                    01630003
   field    = C2X(SUBSTR(INPUT_REC,OFFSET,4))                           01640003
     parse value field with 1 . 2 c 3 yy 5 ddd 8 .                      01650003
     if (c = 0) then                                                    01660003
       yyyy = '19'!!yy                                                  01670003
     else                                                               01680003
       yyyy = '20'!!yy                                                  01690003
   sm101dte    = yyyy!!'.'!!ddd                                         01700003
   OFFSET = OFFSET + 4                                                  01710003
   /* smf id */                                                         01720003
   sm101sid = SUBSTR(INPUT_REC,OFFSET,4)                                01730003
   OFFSET = OFFSET + 4                                                  01740003
   /* SM100SSI DS CL4 SSID         */                                   01750003
   /* sm101ssi = SUBSTR(INPUT_REC,OFFSET,4) */                          01760008
   OFFSET = OFFSET + 10                                                 01770003
   /* TOTAL LENGTH = 28 */                                              01780003
   RETURN 0                                                             01790008
                                                                        01800003
DSNDQWA0: /* MAP SELF-DEFINING SECT */                                  01810003
  /* QWA01PSO DS AL4 OFFSET TO THE PRODUCT SECTION */                   01820003
  QWA01PSO = C2D(SUBSTR(INPUT_REC,OFFSET,4))                            01830003
  OFFSET = OFFSET + 8                                                   01840003
  /* QWA01R1O DS AL4 OFFSET TO THE ACCOUNTING SECTION */                01850003
  /* DSNDQWAC ACCOUNTING SECTION */                                     01860003
  QWA01R1O = C2D(SUBSTR(INPUT_REC,OFFSET,4))                            01870003
  OFFSET = OFFSET + 8 /* 4+2+2 */                                       01880003
  /* DSNDQXST RDS DATA : NB selects ... */                              01890003
  QWA01R2O = C2D(SUBSTR(INPUT_REC,OFFSET,4))                            01900003
  OFFSET = OFFSET + 4                                                   01900109
  lg       = C2D(SUBSTR(INPUT_REC,OFFSET,2))                            01901009
  OFFSET = OFFSET + 4                                                   01902009
  /* DSNDQBAC Buffer manager  */                                        01920003
  QWA01R3O = C2D(SUBSTR(INPUT_REC,OFFSET,4))                            01930003
  offset = offset +6                                                    01940003
  nb_pools = C2D(SUBSTR(INPUT_REC,OFFSET,2))                            01950003
  /* DSNDQTXA Lock manager  */                                          01960003
  /* DSNDQTXA Lock manager  */                                          01970003
  /* DSNDQLAC DDF */                                                    01980003
  /* DSNDQMDA DDF DRDA > V2R3 */                                        01990003
  /* DSNDQIFA IFI */                                                    02000003
  /* DSNDQWAR Rollup acct info */                                       02010003
  /* DSNDQBGA GroupBuffer */                                            02020003
  /* DSNDQTGA Global Locking */                                         02030003
  /* DSNDQWDA DataSharing (pas encore utilise) */                       02040003
  /* DSNDQWAX Acctg overflow */                                         02050003
  /* DSNDQ8AC Accelerator acctg */                                      02060003
  /*OFFSET = OFFSET + 96  */                                            02070003
  return                                                                02080003
                                                                        02090003
/* product section std header  */                                       02100003
DSNDQWHS:                                                               02110003
  QWHSLEN = C2D(SUBSTR(INPUT_REC,OFFSET,2))                             02120003
  OFFSET = OFFSET + 2                                                   02130003
  QWHSTYP = C2D(SUBSTR(INPUT_REC,OFFSET,1))                             02140003
  OFFSET = OFFSET + 1 + 1                                               02150003
  /* QWHSIID DS XL2 Ifcid */                                            02160003
  Ifcid = C2D(SUBSTR(INPUT_REC,OFFSET,2))                               02170003
  OFFSET = OFFSET + 2                                                   02180003
  OFFSET = OFFSET + 6                                                   02190003
  /* QWHSSSID DS CL4 SUBSYSTEM NAME */                                  02200003
  QWHSSSID = SUBSTR(INPUT_REC,OFFSET,4)                                 02210003
  OFFSET = OFFSET +  74                                                 02220003
  RETURN                                                                02230003
                                                                        02240003
/* correlation header */                                                02250003
DSNDQWHC:                                                               02260003
  offset_corr=offset                                                    02270003
  QWHCLEN = C2D(SUBSTR(INPUT_REC,OFFSET,2))                             02280003
  OFFSET = OFFSET + 2                                                   02290003
  OFFSET = OFFSET + 2                                                   02300003
  OFFSET = OFFSET + 8                                                   02310003
  OFFSET = OFFSET + 12                                                  02320003
  OFFSET = OFFSET + 8                                                   02330003
  OFFSET = OFFSET + 8                                                   02340003
  OFFSET = OFFSET + 8                                                   02350003
  /* QWHCATYP  Type de connection*/                                     02360003
  QWHCATYP  = C2D(SUBSTR(INPUT_REC,OFFSET,4))                           02370003
      Select                                                            02380003
           When QWHCATYP  = 4  Then do                                  02390003
                                        conntype='CICS'                 02400003
                                    end                                 02410003
           When QWHCATYP  = 2  Then do                                  02420003
                                        conntype='DB2CAL'               02430003
                                    end                                 02440003
           When QWHCATYP  = 1  Then do                                  02450003
                                        conntype='BATCH'                02460003
                                    end                                 02470003
           When QWHCATYP  = 3  Then do                                  02480003
                                        conntype='DL1'                  02490003
                                    end                                 02500003
           When QWHCATYP  = 5  Then do                                  02510003
                                        conntype='IMSBMP'               02520003
                                    end                                 02530003
           When QWHCATYP  = 6  Then do                                  02540003
                                        conntype='IMSMPP'               02550003
                                    end                                 02560003
           When QWHCATYP  = 8  Then do                                  02570003
                                        conntype='DRDA'                 02580003
                                    end                                 02590003
           When QWHCATYP  = 9  Then do                                  02600003
                                        conntype='IMSCTR'               02610003
                                    end                                 02620003
           When QWHCATYP  = 10 Then do                                  02630003
                                        conntype='TRNBMP' /*IMS */      02640003
                                    end                                 02650003
           When QWHCATYP  = 11 Then do                                  02660003
                                        conntype='DB2UTI'               02670003
                                    end                                 02680003
           When QWHCATYP  = 12 Then do                                  02690003
                                        conntype='RRSAF'                02700003
                                    end                                 02710003
           Otherwise      say 'QWHCATYP' QWHCATYP 'not processed'       02720003
      end   /* select */                                                02730003
  /* Record in Conntype List */                                         02740003
  Call record_conntype                                                  02750003
                                                                        02760003
  OFFSET = OFFSET + 28                                                  02770003
  RETURN                                                                02780003
                                                                        02790003
DSNDQWAC: /* MAP ACCOUNTING DATA SECTION */                             02800003
  /* QWACBSC DS XL8 CLASS 1 BEGINNING STORE CLOCK VALUE*/               02810003
  NUMERIC DIGITS 30                                                     02820003
  OFFSET = OFFSET + 8                                                   02830003
  OFFSET = OFFSET + 8                                                   02840003
  /* QWACBJST DS XL8 BEGINNING TCB CPU TIME FROM MVS (CLASS 1)*/        02850003
  QWACBJST = C2X(SUBSTR(INPUT_REC,OFFSET,8)) /*CONVERT INTO HEX VALUE*/ 02860003
  QWACBJST = X2D(SUBSTR(QWACBJST,1,13)) /*ELIMINATE 1.5 BYTES */        02870003
  OFFSET = OFFSET + 8                                                   02880003
  /* QWACEJST DS XL8 ENDING TCB CPU TIME IN ALL ENVIRONMENTS */         02890003
  QWACEJST = C2X(SUBSTR(INPUT_REC,OFFSET,8)) /*CONVERT INTO HEX VALUE*/ 02900003
  QWACEJST = X2D(SUBSTR(QWACEJST,1,13)) /*ELIMINATE 1.5 BYTES */        02910003
  TCB_TIME = (QWACEJST - QWACBJST)/1000000                              02920003
  OFFSET = OFFSET + 24                                                  02930003
  OFFSET = OFFSET + 20                                                  02940003
  OFFSET = OFFSET + 4                                                   02950003
  OFFSET = OFFSET + 12                                                  02960003
  /* QWACAJST DB2 CPU en stck value */                                  02970003
  /* attention : this is stck time , not local time ! */                02980003
  DB2_cpu  = C2X(SUBSTR(INPUT_REC,OFFSET,8))                            02990003
  offset=offset + 8                                                     03000003
  DB2_cpu  = X2D(SUBSTR(DB2_cpu,1,13))                                  03010003
  DB2_cpu   = DB2_cpu/1000000                                           03020003
  /* Skip next 8   bytes */                                             03030003
  offset=offset + 8                                                     03040003
  /* Wait I/O    QWACAWTI */                                            03050003
  time8=c2x(SUBSTR(INPUT_REC,OFFSET,8))                                 03060003
  offset=offset + 8                                                     03070003
  WaitIO  =x_time(time8)                                                03080003
  offset=offset + 8 + 8                                                 03090003
  /* Wait other Read */                                                 03100003
  offset=offset + 8                                                     03110003
  /* Wait other write*/                                                 03120003
  offset=offset + 8                                                     03130003
  offset=offset + 16+24                                                 03140003
  /* Wait write log  QWACAWLG*/                                         03150003
  time8=c2x(SUBSTR(INPUT_REC,OFFSET,8))                                 03160003
  WaitWrLog=x_time(time8)                                               03170003
  /* skip xx bytes */                                                   03180003
  offset=offset + 48                                                    03190003
  /* Wait global locks  QWACAWTJ */                                     03200003
  offset=offset + 8                                                     03210003
  time8=c2x(SUBSTR(INPUT_REC,OFFSET,8))                                 03220003
  WaitGlLock=x_time(time8)                                              03230003
  /* skip xx bytes */                                                   03240003
  offset=offset + 68                                                    03250003
  /* log records QWACLRN */                                             03260003
  logrec   = C2D(SUBSTR(INPUT_REC,OFFSET,4))                            03270003
  offset=offset + 4 + 2                                                 03280003
  /* log bytes written QWACLRAB */                                      03290003
  logbytes = C2D(SUBSTR(INPUT_REC,OFFSET,6))                            03300003
  RETURN                                                                03310003
                                                                        03320003
/* buffer manager data */                                               03330003
DSNDQBAC:                                                               03340003
numeric digits 15                                                       03350003
  i = 0                                                                 03360003
  getp=0                                                                03370003
  syncio=0                                                              03380003
  syncwr=0                                                              03390003
  sio    =0                                                             03400003
  /* say 'buffer manager for plan' QWHCPLAN */                          03410003
  do until i= nb_pools                                                  03420003
     i = i+1                                                            03430003
     QBACPID   = C2D(SUBSTR(INPUT_REC,OFFSET,4))                        03440003
     offset=offset + 4                                                  03450003
     QBACGET   = C2D(SUBSTR(INPUT_REC,OFFSET,4))                        03460003
     getp = getp+QBACGET                                                03470003
     offset = offset + 12                                               03480003
     QBACRIO   = C2D(SUBSTR(INPUT_REC,OFFSET,4))                        03490003
     syncio = syncio+QBACRIO                                            03500003
     offset = offset + 4                                                03510003
     offset = offset + 4                                                03520003
     QBACIMW   = C2D(SUBSTR(INPUT_REC,OFFSET,4))                        03530003
     syncwr  = syncwr + QBACIMW                                         03540003
     offset = offset + 4                                                03550003
     offset = offset + 4                                                03560003
     offset = offset + 24                                               03570003
     QBACSIO   = C2D(SUBSTR(INPUT_REC,OFFSET,4))                        03580003
     sio     = sio    +QBACSIO                                          03590003
     offset = offset + 8                                                03600003
  /* say '      ',                                          */          03610003
  /*     'buffer id' QBACPID 'gp:' QBACGET 'syncio' QBACRIO,*/          03620003
  /*     'syncwr' QBACIMW  'SIO' QBACSIO                    */          03630003
  end                                                                   03640003
                                                                        03650003
  return                                                                03660003
/* sql statements  */                                                   03670003
DSNDQXST:                                                               03680003
numeric digits 15                                                       03681010
   selects   =0                                                         03690003
   inserts   =0                                                         03700003
   updates   =0                                                         03710003
   deletes   =0                                                         03720003
   opens     =0                                                         03730003
   fetchs    =0                                                         03740003
   offset=offset + 4                                                    03750003
   eye_catch = SUBSTR(INPUT_REC,OFFSET,4)                               03760003
   if eye_catch <> 'QXST' then                                          03770003
           do                                                           03780003
              say 'QXST eye catcher not found at record' reci,          03790003
                  ' offset' offset                                      03800003
              exit 8                                                    03810003
           end                                                          03820003
   offset=offset + 4                                                    03830003
   selects   = C2D(SUBSTR(INPUT_REC,OFFSET,8))                          03840003
   offset=offset + 8                                                    03850003
   inserts   = C2D(SUBSTR(INPUT_REC,OFFSET,8))                          03860003
   offset=offset + 8                                                    03870003
   updates   = C2D(SUBSTR(INPUT_REC,OFFSET,8))                          03880003
   offset=offset + 8                                                    03890003
   deletes   = C2D(SUBSTR(INPUT_REC,OFFSET,8))                          03900003
   offset=offset + 24                                                   03910003
   opens     = C2D(SUBSTR(INPUT_REC,OFFSET,8))                          03920003
   offset=offset + 136 /* 17*8*/                                        03930003
   fetchs    = C2D(SUBSTR(INPUT_REC,OFFSET,8))                          03940003
  return                                                                03950003
                                                                        03960003
GET_FMT_TIME:                                                           03970003
  RUN_HH = SM101TME % 360000                                            03980003
  RUN_HH = RIGHT(RUN_HH,2,'0')                                          03990003
  RUN_MIN = SM101TME % 6000 - RUN_HH*60                                 04000003
  RUN_MIN = RIGHT(RUN_MIN,2,'0')                                        04010003
  RUN_SEC = SM101TME % 100 - RUN_HH *3600 - RUN_MIN*60                  04020003
  RUN_SEC = RIGHT(RUN_SEC,2,'0')                                        04030003
  RUN_FMT_TIME = RUN_HH!!':'!!RUN_MIN!!':'!!RUN_SEC                     04040003
RETURN                                                                  04050003
                                                                        04060003
write_header:                                                           04070003
    say 'file ' oufs     ' will be produced'                            04080003
    queue "Lpar,Ssid,Date,Hour,Conntype,",                              04090003
           "Cl1Cpu,Cl2Cpu,",                                            04100003
           "Getp,SyncIo,SyncWr,Sio,",                                   04110003
           "Selects,Inserts,Updates,Deletes,Opens,Fetchs,",             04120003
           "WaitIO,",                                                   04130003
           "WaitWrLog," ,                                               04140003
           "WaitGlLock,",                                               04150003
           "Logrec," ,                                                  04160003
           "Logbytes"                                                   04170003
                                                                        04180003
    "EXECIO" queued() "DISKW OUFs"                                      04190003
    reco=reco+1                                                         04200003
  return                                                                04210003
                                                                        04220003
process_summary:                                                        04230003
   hour = left(run_fmt_time,2)                                          04241016
   /* pas de rupture pour le 1er record lu */                           04250003
   if rupture = 0                                                       04260003
   then do                                                              04270003
       rupture=1                                                        04280003
       s_hour=hour                                                      04290003
   end                                                                  04300003
   /* detection rupture,declenche ecriture*/                            04310003
   if   hour <>  s_hour                                                 04320003
   then do                                                              04330003
       call write_summary                                               04340003
       do i=1 to nbr_conntype                                           04350003
             conntmp = lst_conntype.i                                   04360003
             if conntmp = conntype then                                 04370003
             do                                                         04380003
                 /* summary counters of the current conntype */         04390003
                 sm_tcb_time.conntype  =  tcb_time                      04400003
                 sm_DB2_cpu.conntype   =  DB2_cpu  /* DB2 CPU */        04410003
                 sm_getp.conntype      =  getp                          04420003
                 sm_syncio.conntype    =  syncio                        04430003
                 sm_syncwr.conntype    =  syncwr                        04440003
                 sm_sio.conntype       =  sio                           04450003
                 sm_selects.conntype   =  selects                       04460003
                 sm_inserts.conntype   =  inserts                       04470003
                 sm_updates.conntype   =  updates                       04480003
                 sm_deletes.conntype   =  deletes                       04490003
                 sm_opens.conntype     =  opens                         04500003
                 sm_fetchs.conntype    =  fetchs                        04510003
                 sm_WaitIO.conntype    =  WaitIO                        04520003
                 sm_WaitWrLog.conntype =  WaitWrLog                     04530003
                 sm_WaitGlLock.conntype=  WaitGlLock                    04540003
                 sm_logrec.conntype    =  logrec                        04550003
                 sm_logbytes.conntype  =  logbytes                      04560003
             end                                                        04570003
             else do                                                    04580003
                 sm_tcb_time.conntmp   =  0                             04590003
                 sm_DB2_cpu.conntmp    =  0                             04600003
                 sm_getp.conntmp       =  0                             04610003
                 sm_syncio.conntmp     =  0                             04620003
                 sm_syncwr.conntmp     =  0                             04630003
                 sm_sio.conntmp        =  0                             04640003
                 sm_selects.conntmp    =  0                             04650003
                 sm_inserts.conntmp    =  0                             04660003
                 sm_updates.conntmp    =  0                             04670003
                 sm_deletes.conntmp    =  0                             04680003
                 sm_opens.conntmp      =  0                             04690003
                 sm_fetchs.conntmp     =  0                             04700003
                 sm_WaitIO.conntmp     =  0                             04710003
                 sm_WaitWrLog.conntmp  =  0                             04720003
                 sm_WaitGlLock.conntmp =  0                             04730003
                 sm_logrec.conntmp     =  0                             04740003
                 sm_logbytes.conntmp   =  0                             04750003
             end                                                        04760003
       end  /* end do for */                                            04770003
                                                                        04780003
       s_hour=hour                                                      04790003
                                                                        04800003
   end                                                                  04810003
   /*pas de rupture , on accumule les valeurs */                        04820003
   else do                                                              04830003
       sm_tcb_time.conntype  =  tcb_time  + sm_tcb_time.conntype        04840003
       sm_DB2_cpu.conntype   =  DB2_cpu   + sm_DB2_cpu.conntype         04850003
       sm_getp.conntype      =  getp      + sm_getp.conntype            04860003
       sm_syncio.conntype    =  syncio    + sm_syncio.conntype          04870003
       sm_syncwr.conntype    =  syncwr    + sm_syncwr.conntype          04880003
       sm_sio.conntype       =  sio       + sm_sio.conntype             04890003
       sm_selects.conntype   =  selects   + sm_selects.conntype         04900003
       sm_inserts.conntype   =  inserts   + sm_inserts.conntype         04910003
       sm_updates.conntype   =  updates   + sm_updates.conntype         04920003
       sm_deletes.conntype   =  deletes   + sm_deletes.conntype         04930003
       sm_opens.conntype     =  opens     + sm_opens.conntype           04940003
       sm_fetchs.conntype    =  fetchs    + sm_fetchs.conntype          04950003
       sm_WaitIO.conntype    =  WaitIO    + sm_WaitIO.conntype          04960003
       sm_WaitWrLog.conntype =  WaitWrLog + sm_WaitWrLog.conntype       04970003
       sm_WaitGlLock.conntype=  WaitGlLock+ sm_WaitGlLock.conntype      04980003
       sm_logrec.conntype    =  logrec    + sm_logrec.conntype          04990003
       sm_logbytes.conntype  =  logbytes  + sm_logbytes.conntype        05000003
                                                                        05010003
   end/*pas de rupture , on accumule les valeurs */                     05020003
                                                                        05030003
   return                                                               05040003
                                                                        05050003
write_summary:                                                          05060003
   if reco = 0 then call croutput                                       05070020
                                                                        05080003
     /* loop to write all connectype */                                 05090003
     do i=1 to nbr_conntype                                             05100003
         ConnTmp = Lst_Conntype.i                                       05110003
         sm_logbytes.ConnTmp=sm_logbytes.ConnTmp/1048576                05120003
         sm_logbytes.ConnTmp=format(sm_logbytes.ConnTmp,,0)             05130003
         reco=reco+1                                                    05131004
         queue sm101sid !! ',' !! sm101ssi !! ','  ,                    05140003
         !! sm101dte !! ','   ,                                         05150003
         !! s_hour !! ','   ,                                           05160003
         !! '"' !! ConnTmp !! '"' !! ','   ,                            05170003
         !! sm_tcb_time.ConnTmp   !! ','   ,                            05180003
         !! sm_DB2_cpu.ConnTmp    !! ','   ,                            05190003
         !! format(sm_getp.ConnTmp,,0,0)     !! ','   ,                 05200013
         !! sm_syncio.ConnTmp     !! ','   ,                            05210003
         !! sm_syncwr.ConnTmp     !! ','   ,                            05220003
         !! sm_sio.ConnTmp        !! ','   ,                            05230003
         !! format(sm_selects.ConnTmp,,0,0)    !! ','   ,               05240013
         !! sm_inserts.ConnTmp    !! ','   ,                            05250003
         !! sm_updates.ConnTmp    !! ','   ,                            05260003
         !! sm_deletes.ConnTmp    !! ','   ,                            05270003
         !! sm_opens.ConnTmp      !! ','   ,                            05280003
         !! sm_fetchs.ConnTmp     !! ','   ,                            05290003
         !! sm_WaitIO.ConnTmp     !! ','   ,                            05300003
         !! sm_WaitWrLog.ConnTmp !! ','    ,                            05310003
         !! sm_WaitGlLock.ConnTmp!! ','    ,                            05320003
         !! sm_logrec.ConnTmp     !! ','   ,                            05330003
         !! sm_logbytes.ConnTmp   !! ','                                05340003
     end                                                                05350003
                                                                        05360003
    "EXECIO" queued() "DISKW OUFS"                                      05370003
   return                                                               05380003
                                                                        05390003
x_time:                                                                 05400003
  arg time8                                                             05410003
  time8    = X2D(SUBSTR(time8,1,13))                                    05420003
  time8     = time8/1000000                                             05430003
  return time8                                                          05440003
                                                                        05450003
record_conntype:                                                        05460003
   found=0                                                              05470003
   do i = 1 to nbr_conntype                                             05480003
      if lst_conntype.i = conntype then                                 05490003
         do                                                             05500003
            found=1                                                     05510003
            leave                                                       05520003
         end                                                            05530003
   end                                                                  05540003
   /* not found : add new conntype to list*/                            05550003
   if found=0 then                                                      05560003
      do                                                                05570003
         nbr_conntype = nbr_conntype + 1                                05580003
         lst_conntype.nbr_conntype = conntype                           05590003
            /* Initialize variables */                                  05600003
            sm_tcb_time.conntype  =    0                                05610003
            sm_DB2_cpu.conntype   =    0                                05620003
            sm_getp.conntype      =    0                                05630003
            sm_syncio.conntype    =    0                                05640003
            sm_syncwr.conntype    =    0                                05650003
            sm_sio.conntype       =    0                                05660003
            sm_selects.conntype   =    0                                05670003
            sm_inserts.conntype   =    0                                05680003
            sm_updates.conntype   =    0                                05690003
            sm_deletes.conntype   =    0                                05700003
            sm_opens.conntype     =    0                                05710003
            sm_fetchs.conntype    =    0                                05720003
            sm_WaitIO.conntype    =    0                                05730003
            sm_WaitWrLog.conntype =    0                                05740003
            sm_WaitGlLock.conntype=    0                                05750003
            sm_logrec.conntype    =    0                                05760003
            sm_logbytes.conntype  =    0                                05770003
                                                                        05780003
      end                                                               05790003
  return                                                                05800003
/*========================================== */                         05810003
/* Set SMF data set name , depending on lpar */                         05820003
/*========================================== */                         05830003
SetSmfDs:                                                               05840003
  oufl = 'systmp.wsyngud.smfexta'                                       05850003
  Select                                                                05860003
       When lpar  = 'XX10' then                                         05870003
            do                                                          05880003
                oufl='systmp.wsyngud.smfexta'                           05890003
                ssid='DB2B'                                             05900003
            end                                                         05910003
       When lpar  = 'LIM'   then                                        05920003
            do                                                          05930003
                call GetDate                                            05940003
                oufl="GEB.BSMF"!!Lpar!!".DB2.D"!!dd!!"J"!!yy1           05950003
                ssid='DBP1'                                             05960003
            end                                                         05970003
       When lpar  = 'LIM2' then                                         05980003
            do                                                          05990003
                call GetDate                                            06000003
                oufl="GEB.BSMF"!!Lpar!!".DB2.D"!!dd!!"J"!!yy1           06010003
                ssid='DBP2'                                             06020003
            end /* end Lpar XX10 Sofinco */                             06030003
       When lpar  = 'LIM3' then                                         06040003
            do                                                          06050003
                call GetDate                                            06060003
                oufl="GEB.BSMF"!!Lpar!!".DB2.D"!!dd!!"J"!!yy1           06070003
                ssid='DBP3'                                             06080003
            end /* end Lpar XX10 Sofinco */                             06090003
       When lpar  = 'LIM4' then                                         06100003
            do                                                          06110003
                call GetDate                                            06120003
                oufl="GEB.BSMF"!!Lpar!!".DB2.D"!!dd!!"J"!!yy1           06130003
                ssid='DBP8'                                             06140003
            end /* end Lpar XX10 Sofinco */                             06150003
       When lpar  = 'IPO4' then                                         06160003
            do                                                          06170003
                oufl='NotUsed'                                          06180003
                ssid='DSN2'                                             06190003
            end /* end Lpar IPO4 CACIB */                               06200005
       When lpar  = 'MVSA' then                                         06201005
            do                                                          06202005
                oufl='NotUsed'                                          06203005
                ssid='DB2P'                                             06204005
            end /* end Lpar MVSA CARIPARMA*/                            06205005
       When lpar  = 'ZPR1' then                                         06206006
            do                                                          06207006
                oufl='NotUsed'                                          06208006
                ssid='DB2E'                                             06209006
            end /* end Lpar MVSA CARIPARMA*/                            06209106
       When lpar  = 'PROD' then                                         06209216
            do                                                          06209315
                clnt='CAAGIS'                                           06209418
                oufl='NotUsed'                                          06209518
                ssid='XXXX'                                             06209618
            end /* end Lpar caagis */                                   06209716
       Otherwise                                                        06211015
            do                                                          06220003
               say 'Lpar not processed - End of program'                06230003
               exit(0)                                                  06240003
            end                                                         06250003
  end   /* End select */                                                06260003
  return                                                                06270003
GetDate:                                                                06280003
  hier=DATE('E',DATE(B)-1,'B')                                          06290003
  dd=substr(hier,1,2)                                                   06300003
  yy1=substr(hier,8,1)                                                  06310003
  return                                                                06320003
/* Report dataset on output */                                          06330016
Croutput:                                                               06331016
    /* caagis ssid = celui qui est en entree */                         06340016
    if clnt = 'CAAGIS' then                                             06340119
    do                                                                  06340216
          ssidx = sm101ssi                                              06340316
          if ssidx = 'DBPR' then lpar='SUDM'                            06340416
          if ssidx = 'DB2I' then lpar='SUDB'                            06340616
    end                                                                 06340716
    else ssidx = ssid                                                   06340816
    oufs = "'" !! hlq !! '.reportA.' !! lpar !! '.' !! ssidx !! "'"     06341016
    "DELETE" oufs "PURGE"                                               06350016
    "ALLOC FI(OUFs) DA("oufs") NEW CATALOG REUSE" ,                     06360016
    "LRECL(320) RECFM(V B) TRACKS SPACE(15,15)"                         06370016
    rcalloc = rc                                                        06380016
    if rcalloc <> 0 then Do                                             06390016
         say "**********************************************"           06400016
         say "   Error allocating report file" rcalloc                  06410016
         say "   Abnormal end  "                                        06420016
         say "**********************************************"           06430016
         Exit 8                                                         06440016
    end                                                                 06450016
return                                                                  06460016