Google
 

Trailing-Edge - PDP-10 Archives - BB-FB49A-RM - sources/sntfil.b36
There are no other files named sntfil.b36 in the archive.
%title 'SNT Trace File Processor'

module SNTFIL (ident = 'Version 1.02') =
begin

! Copyright (c) 1984, 1985 by
! DIGITAL EQUIPMENT CORPORATION, Maynard, Massachusetts
!
! This software is furnished under a license and may be used and  copied
! only  in  accordance  with  the  terms  of  such  license and with the
! inclusion of the above copyright notice.  This software or  any  other
! copies  thereof may not be provided or otherwise made available to any
! other person.  No title to and ownership of  the  software  is  hereby
! transferred.
!
! The information in this software is subject to change  without  notice
! and  should  not  be  construed  as  a commitment by Digital Equipment
! Corporation.
!
! Digital assumes no responsibility for the use or  reliability  of  its
! software on equipment which is not supplied by Digital.
!++
! FACILITY:	DECnet/SNA TOPS-20 SNA Trace Utility file handler
!
! ABSTRACT:	This module provides the facility to manage the files
!               for both the Trace Collector and Analyzer.
!
! ENVIRONMENT:	TOPS-20 Operating Systems, user mode.
!
! AUTHOR:	Dennis Brannon,               CREATION DATE: July 26, 1983.
!
! MODIFIED BY:
!
! 	D. Brannon, : VERSION 1.00
!
! 1.01  D. Brannon, 29-Oct-84
!       Added routine FIL$PURGE.
!
! 1.02  D. Brannon, 31-Jan-85
!       fixed bug of a byte pointer pointing to a byte pointer and made
!       ST[ST_CIRCUIT_ID] and ST[ST_GATEWAY] be byte pointers to the ASCIZ
!       strings of the circuit id and the gateway node name.
!--

!
! REQUIRED FILES
!

library 'MONSYM';                       ! Monitor symbols
library 'SYS:TXTLIB';                   ! Text Processing Library
library 'SNTLIB';
library 'SNTDEF';
require 'JSYS';                         ! TOPS-20 JSYS declarations

!
! FORWARD ROUTINE
!

forward routine
    FIL$BUILD_HEADER_RECORD,
    FIL$OPEN_TRACE_FILE,
    FIL$CLOSE_TRACE_FILE,
    FIL$OPEN_OUTPUT_FILE,
    FIL$CLOSE_OUTPUT_FILE,
    FIL$OPEN_ANALYZE_FILE,
    FIL$CLOSE_ANALYZE_FILE,
    FIL$CLOSE_NETWORK,
    FIL$GET_RECORD,
    FIL$GET_COUNT,
    FIL$PURGE,
    FIL$TERMINATE_TRACE,
    FIL$WRITE_END_RECORD,
    FIL$WRITE_HEADER_RECORD,
    FIL$WRITE_RECORD;

!
! EXTERNAL REFERENCES
!
external
    ST: SNTBLOCK;

external routine
    GAD$DISCONNECT_LINK,
    MEM$GET,
    MEM$RETURN: novalue,
    TXT$WRITE,
    USP$PUT_TIME_STAMP: novalue,
    USP$TIME_ZONE: novalue,
    USP$ERROR_MESSAGE: novalue;
%global_routine ('FIL$OPEN_ANALYZE_FILE') =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Open analyze file and verify the header record to avoid illegal
!       file format.
!
! FORMAL PARAMETERS:
!
!       none
!
! ROUTINE VALUE:
!
!       $TRUE   Analyze file is opened successfully and ready.
!       $FALSE  Otherwise.
!
! SIDE EFFECTS:
!
!       none
!
!--

    begin

    local
        JFN;

    if (JFN = .ST[ST_ANALYZE_JFN]) neq 0     ! This should not happen
    then jsys_haltf ();

    if not jsys_gtjfn (gj_sht+gj_fou, .ST[ST_ANALYZE_FILE]; JFN)
    then return $FALSE;

    if not jsys_openf (.JFN, of_rd+$$(8,of_bsz))
    then begin                          ! Could not open file
         jsys_rljfn (.JFN);             ! Release file JFN
         ST[ST_ANALYZE_JFN] = 0;        ! Zero out the JFN field
         return $FALSE;
         end;

    ST[ST_ANALYZE_JFN] = .JFN;
    return $TRUE;

    end;                                ! End of FIL$OPEN_ANALYZE_FILE
%global_routine ('FIL$CLOSE_ANALYZE_FILE') =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Close analyze file.
!
! FORMAL PARAMETERS:
!
!       none
!
! ROUTINE VALUE:
!
!       $TRUE   Analyzed file is closed successfully.
!       $FALSE  Otherwise.
!
! SIDE EFFECTS:
!
!       none
!
!--

    begin
    local
      JFN;

    JFN = .ST[ST_ANALYZE_JFN];
    if .JFN eql 0
    then return $FALSE;

    jsys_closf (.JFN);           ! Close file
    jsys_rljfn (.JFN);
    ST[ST_ANALYZE_JFN] = 0;      ! Remove JFN definition
    return $TRUE;

    end;                                ! End of FIL$CLOSE_ANALYZE_FILE
%global_routine ('FIL$BUILD_HEADER_RECORD') =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Build header record for the trace file.
!
! FORMAL PARAMETERS:
!
!
! ROUTINE VALUE:
!
!       none
!
! SIDE EFFECTS:
!
!       none
!
!--

    begin

    local
        FLDPTR,
        TIMBUF,
        BUFFER,
        POINTER,
        LENGTH,
        MARK,
        MARKTEMP;

    bind
        UPPERCASE = ch$asciz ('%A%N');  ! Pattern to uppercase & suppress null

    BUFFER = MEM$GET (1);               ! Temporary buffer for header record
    POINTER = ch$ptr (.BUFFER,,8);
    MARK = .POINTER;                    ! Save starting point of pointer

    ch$wchar_a (INIT_MSG_K$TRAPRO, POINTER);    ! Header message type
                                                ! (initiate trace)
    ch$wchar_a (VERSION_VER_K$TRAPRO, POINTER); ! Version number
    ch$wchar_a (DECECO_VER_K$TRAPRO, POINTER);  ! ECO number
    ch$wchar_a (CUSECO_VER_K$TRAPRO, POINTER);  ! User ECO number

    ch$wchar_a (.ST[ST_BUFFERS], POINTER);      ! Buffering level
    ch$wchar_a (.ST[ST_TYPE], POINTER);         ! Type of trace
    ch$wchar_a (.ST[ST_FILES], POINTER);
    ch$wchar_a (.ST[ST_FILENUM], POINTER);
    ch$wchar_a (.ST[ST_FILESIZE], POINTER);
    ch$wchar_a (.ST[ST_ENTRIES], POINTER);
    ch$wWord_a (.ST[ST_SIZE], POINTER);
    ch$wWord_a (.ST[ST_SESSION], POINTER);

    FLDPTR = .ST[ST_CIRCUIT_ID];
    LENGTH = CH$LEN (.FLDPTR);
    ch$wchar_a (.LENGTH, POINTER);
    TXT_WRITE (POINTER, .LENGTH, UPPERCASE, .FLDPTR);
    POINTER = ch$fill (%C' ', 15-.LENGTH, .POINTER);
!    POINTER = CH$COPY (.LENGTH, .FLDPTR, %C' ', 15, .POINTER);

    MARKTEMP = ch$plus (.POINTER, 16);
    USP$PUT_TIME_STAMP (POINTER);
    USP$TIME_ZONE  (POINTER);
    POINTER = ch$fill ( %C' ', ch$diff (.MARKTEMP, .POINTER), .POINTER);

    FLDPTR = .ST[ST_GATEWAY];
    LENGTH = CH$LEN (.FLDPTR);
    ch$wchar_a (.LENGTH, POINTER);
    TXT_WRITE (POINTER, .LENGTH, UPPERCASE, .FLDPTR);
!    POINTER = ch$move (.LENGTH, .FLDPTR, .POINTER);

    LENGTH = ch$diff (.POINTER, .MARK);      ! Get the length of the
                                             !  header record

    ST[ST_HLEN] = .LENGTH;
    ST[ST_HEADER] = .BUFFER;

    return $TRUE;
    end;                                ! End of FIL$BUILD_HEADER_RECORD
%global_routine ('FIL$CLOSE_OUTPUT_FILE', NUMBER) =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Close output file.
!
! FORMAL PARAMETERS:
!
!       NUMBER          File generation number
!
! ROUTINE VALUE:
!
!       $TRUE   Output file is closed successfully.
!       $FALSE  Otherwise.
!
! SIDE EFFECTS:
!
!       none
!
!--

    begin

    local
        JFN;

    JFN = .ST[ST_OUTPUT_JFN];
    if .JFN eql 0
    then return $FALSE;

    jsys_closf (.JFN);           ! Close file
    ST[ST_OUTPUT_JFN] = 0;       ! Zero out the JFN field

    return $TRUE;

    end;                                ! End of FIL$CLOSE_OUTPUT_FILE
%global_routine ('FIL$CLOSE_NETWORK') =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Close network link.
!
! FORMAL PARAMETERS:
!
!       None
!
! ROUTINE VALUE:
!
!       $TRUE   Output file is closed successfully.
!       $FALSE  Otherwise.
!
! SIDE EFFECTS:
!
!       none
!
!--

    begin

    local
        STATUS,
        JFN;

    JFN = .ST[ST_JFN];
    if .JFN eql 0
    then return $FALSE;

    if not (STATUS = GAD$DISCONNECT_LINK(.ST[ST_JFN])) then return .STATUS;

    jsys_rljfn (.JFN);             ! Release file JFN
    ST[ST_JFN] = 0;                ! Zero out the JFN field
    return $TRUE;

    end;                                ! End of FIL$CLOSE_NETWORK
%global_routine ('FIL$CLOSE_TRACE_FILE', NUMBER) =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Close output file.
!
! FORMAL PARAMETERS:
!
!       NUMBER          File generation number
!
! ROUTINE VALUE:
!
!       $TRUE   Output file is closed successfully.
!       $FALSE  Otherwise.
!
! SIDE EFFECTS:
!
!       none
!
!--

    begin

    local
      JFN;

    JFN = .ST[ST_OUTPUT_JFN];
    if .JFN gtr 0
    then begin
         local STATUS;

         jsys_gtsts (.JFN; , STATUS);
         if .STATUS<$(gs_opn)>          ! Check if file is still open
         then begin
              FIL$WRITE_END_RECORD (.JFN);
              jsys_closf (.JFN);        ! Close file

              ST[ST_OUTPUT_JFN] = 0;       ! Zero out the JFN field

              return $TRUE;
              end;
         end;

    return $FALSE;
    end;                                ! End of FIL$CLOSE_TRACE_FILE
%routine ('FIL$GET_COUNT', JFN) =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Read two bytes (in PDP-11 fashion) from file and return the value.
!
! FORMAL PARAMETERS:
!
!       JFN             File JFN.
!
! ROUTINE VALUE:
!
!       Binary value of the two bytes, first byte is the low-order byte and
!       second byte is high-order byte.
!
! SIDE EFFECTS:
!
!       none
!
!--

    begin

    local
        COUNT;

    COUNT = 0;                          ! Reset returned value
    if jsys_bin (.JFN; , COUNT<0,8>)    ! Get low-order byte
    and jsys_bin (.JFN; , COUNT<8,8>)   ! Get high-order byte
    then return .COUNT;

    return 0;
    end;                                ! End of FIL$GET_COUNT
%global_routine ('FIL$GET_RECORD', JFN, BUFFER) =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Retrieve a data record from the trace file.
!
! FORMAL PARAMETERS:
!
!       JFN             File JFN.
!       BUFFER          Address of the data buffer where record is returned.
!
! ROUTINE VALUE:
!
!       Length of the record.
!       0 if failed to get the record.
!
! SIDE EFFECTS:
!
!       none
!
!--

    begin

    local
        COUNT;

    if ((COUNT = FIL$GET_COUNT (.JFN)) gtr 0) ! Get 2-byte count
    then 
       begin
       jsys_sin (.JFN, ch$ptr (.BUFFER,,8), -.COUNT); ! Get the record
       return .COUNT;                 ! Return length of record
       end;
    return 0;
    end;                                ! End of FIL$GET_RECORD
%global_routine ('FIL$OPEN_OUTPUT_FILE', NUMBER) =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Open output file for analyzed information.  If output file
!       is not defined, assign the default file name.
!
! FORMAL PARAMETERS:
!
!
! ROUTINE VALUE:
!
!       $TRUE   Output file is opened successfully and ready to record.
!       $FALSE  Otherwise.
!
! SIDE EFFECTS:
!
!       none
!
!--

    begin

    local
        STATUS,
        JFN;

    if (.ST[ST_OUTPUT_JFN] eql 0)
    then begin                          ! If output file is not defined
         local BUFFER, POINTER, LENGTH;

         BUFFER = MEM$GET (1);          ! Get temporary buffer for file name
         POINTER = ch$ptr (.BUFFER);    ! Pointer to buffer

         LENGTH = TXT_WRITE (POINTER,   ! Build default file name
                             $MEMORY_BUFFER_SIZE * 5,
                             .ST[ST_OUTPUT_FILE],
                             .NUMBER);

         if not jsys_gtjfn (gj_sht+gj_fou, ch$ptr (.BUFFER); JFN)
         then begin
              MEM$RETURN (.BUFFER);
              return $FALSE;
              end;

         MEM$RETURN (.BUFFER);      ! Return temporary buffer
         if .ST[SW_ANALYZE]
         then
             STATUS = jsys_openf (.JFN, of_wr+of_app+$$(7,of_bsz))
         else
             STATUS = jsys_openf (.JFN, of_wr+$$(8,of_bsz));

         if not .STATUS
         then begin                 ! Failed to open file
              jsys_rljfn (.JFN);    ! Release JFN
              return $FALSE;        ! Return failure
              end;

         ST[ST_OUTPUT_JFN] = .JFN;
         return $TRUE;
         end;

    return $FALSE;
    end;                                ! End of FIL$OPEN_OUTPUT_FILE
%global_routine ('FIL$OPEN_TRACE_FILE', NUMBER) =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Open trace file.  If trace file is not defined, assign the default
!       file name.
!
! FORMAL PARAMETERS:
!
!
! ROUTINE VALUE:
!
!       $TRUE   Trace file is opened successfully and ready to record.
!       $FALSE  Otherwise.
!
! SIDE EFFECTS:
!
!       none
!
!--

    begin

    local
        JFN;

    if (.ST[ST_OUTPUT_JFN] eql 0)
    then begin                          ! If trace file is not defined
         local BUFFER, POINTER, LENGTH;

         BUFFER = MEM$GET (1);          ! Get temporary buffer for file name
         POINTER = ch$ptr (.BUFFER);    ! Pointer to buffer

         LENGTH = TXT_WRITE (POINTER,   ! Build default file name
                             $MEMORY_BUFFER_SIZE * 5,
                             .ST[ST_OUTPUT_FILE],
                             .NUMBER);

         if not jsys_gtjfn (gj_sht+gj_fou, ch$ptr (.BUFFER); JFN)
         then begin
              MEM$RETURN (.BUFFER);
              return $FALSE;
              end;

         MEM$RETURN (.BUFFER);      ! Return temporary buffer

         if not jsys_openf (.JFN, of_wr+$$(8,of_bsz))
         then begin                 ! Failed to open file
              jsys_rljfn (.JFN);    ! Release JFN
              return $FALSE;        ! Return failure
              end;

         ST[ST_OUTPUT_JFN] = .JFN;
         return $TRUE;
         end;

    return $FALSE;
    end;                                ! End of FIL$OPEN_TRACE_FILE
%global_routine ('FIL$TERMINATE_TRACE', STATUS2) :  =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Terminate tracing and close and release all JFN's.
!
! FORMAL PARAMETERS:
!
!       none
!
! ROUTINE VALUE:
!
!       none
!
! SIDE EFFECTS:
!
!       none
!
!--
    begin

    local
         STATUS;
    FIL$CLOSE_TRACE_FILE ();
    FIL$CLOSE_OUTPUT_FILE ();
    GAD$DISCONNECT_LINK(.ST[ST_JFN]);
    if (.ST[SW_ANALYZE] and .ST[SW_OUTPUT]) then 
       if not (STATUS = FIL$CLOSE_ANALYZE_FILE()) then return .STATUS;

    return $TRUE;
    end;                                    ! End of FIL$TERMINATE_TRACE
%global_routine ('FIL$PURGE', JFN, NUMBER) :  =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Purge trace files until the number specified in the /VERSION-LIMIT
!       is reached.
!
! FORMAL PARAMETERS:
!
!       none
!
! ROUTINE VALUE:
!
!       none
!
! SIDE EFFECTS:
!
!       none
!
!--
    begin

    if not jsys_delnf (.JFN, .NUMBER)
    then return SNT$_BADPURGE
    else return SNT$_NORMAL;
    end;                                    ! End of FIL$PURGE
%global_routine ('FIL$WRITE_END_RECORD', JFN) =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Write end record for the trace file.
!
! FORMAL PARAMETERS:
!
!       JFN             Trace file JFN.
!
! ROUTINE VALUE:
!
!       none
!
! SIDE EFFECTS:
!
!       none
!
!--

    begin

    local
        BUFFER,
        POINTER,
        LENGTH,
        MARK;

!    BUFFER = MEM$GET (1);               ! Temporary buffer for end record
!    POINTER = ch$ptr (.BUFFER,2,8);     ! Offset the count
!    MARK = .POINTER;                    ! Save starting point of pointer

!    ch$wchar_a ($END_TRACE, POINTER);   ! End message type
!    LENGTH = ch$diff (.POINTER, .MARK); ! Get the length of the header record
!    CH$WWORD (.LENGTH, ch$ptr (.BUFFER,,8)); ! Write count to record

!    jsys_sout (.JFN, ch$ptr (.BUFFER,,8), -(.LENGTH+2)); ! Write header record

!    MEM$RETURN (.BUFFER);               ! Return temporary buffer

    return $TRUE;
    end;                                ! End of FIL$WRITE_END_RECORD
%global_routine ('FIL$WRITE_HEADER_RECORD', JFN, MSGADR) =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Write header record for the trace file.
!
! FORMAL PARAMETERS:
!
!       JFN             Trace file JFN.
!
! ROUTINE VALUE:
!
!       none
!
! SIDE EFFECTS:
!
!       none
!
!--

    begin

    local
        BUFFER,
        POINTER,
        LENGTH,
        MARK,        
        TIME,
        HEADER;

    HEADER = .MSGADR;
    BUFFER = MEM$GET (2);               ! Temporary buffer for header record
    POINTER = ch$ptr (.BUFFER,,8);
   
!    LENGTH = .ch$rword (ch$ptr (.HEADER,,8)) + 2; ! Get header record length
    LENGTH = .ST[ST_HLEN];
    ch$WWORD (.LENGTH, .POINTER);
    ch$move (.LENGTH, ch$ptr (.HEADER,,8), ch$plus(.POINTER,2));
                                        !Write record to buffer

    jsys_sout (.JFN, ch$ptr (.BUFFER,,8), -(.LENGTH + 2));

    MEM$RETURN (.BUFFER);               ! Return temporary buffer
     
    return $TRUE;
    end;                                ! End of FIL$WRITE_HEADER_RECORD
%global_routine ('FIL$WRITE_RECORD', ADDRESS, LENGTH) =

!++
! FUNCTIONAL DESCRIPTION:
!
!       Write trace records
!
! FORMAL PARAMETERS:
!
!       ADDRESS         Address of the Trace message.
!       LENGTH          Length of the Trace message.
!
! ROUTINE VALUE:
!
!       none
!
! SIDE EFFECTS:
!
!       none
!
!--

    begin

    local
        BUFFER,
        BUFPTR,
        POINTER;


    BUFFER = MEM$GET (1);               ! Temporary buffer
    BUFPTR = ch$ptr (.BUFFER,,8);       ! Pointer to record buffer
    POINTER = ch$ptr (.ADDRESS,,8);

    ch$wword_a (.LENGTH, BUFPTR);         ! Write count to record
    ch$move (.LENGTH, .POINTER, .BUFPTR); ! Append message

    ! At this point, logically, the trace file must have been opened

    ! Write to file
    jsys_sout (.ST[ST_OUTPUT_JFN], ch$ptr (.BUFFER,,8), -(.LENGTH+2));


    MEM$RETURN (.BUFFER);               ! Return temporary buffer

    return $TRUE;
    end;                                ! End of FIL$WRITE_RECORD
end                                   ! End of SNTFIL module
eludom
! Local Modes:
! Mode:BLISS
! Auto Save Mode:2
! Comment Column:40
! Comment Rounding:+1
! End: