(file) Return to evdisplay.f CVS log (file) (dir) Up to [HallC] / Analyzer / ONEEV

  1 cdaq  1.1 *--------------------------------------------------------------
  2           *
  3           *- standalone DISPLAY for hall C
  4           *
  5 cdaq  1.2 * $Log: evdisplay.f,v $
  6           * Revision 1.1  1995/03/14  21:25:27  cdaq
  7           * Initial revision
  8           *
  9 cdaq  1.1 *--------------------------------------------------------------
 10                 IMPLICIT NONE
 11           *
 12 cdaq  1.2       character*9 here
 13                 parameter (here= 'evdisplay')
 14 cdaq  1.1 *
 15                 INCLUDE 'gen_pawspace.cmn'
 16           *
 17                 INCLUDE 'gen_filenames.cmn'
 18           *
 19                 INCLUDE 'gen_run_info.cmn'
 20                 INCLUDE 'gen_event_info.cmn'
 21           *
 22 cdaq  1.2       INCLUDE 'gen_one_ev_info.cmn'
 23                 INCLUDE 'gen_one_ev_info.dte'
 24 cdaq  1.1 *
 25                 logical FAIL,QUIT
 26                 character*800 why
 27                 character*132 line
 28                 logical ABORT
 29                 character*800 err
 30                 integer i,j
 31           *
 32 cdaq  1.2       character*1 spect
 33 cdaq  1.1 *******************************************************************
 34           *
 35                 PRINT *
 36 cdaq  1.2       PRINT *,'       Standalone DISPLAY for hall C'
 37 cdaq  1.1       PRINT *,'     R.Ent,S.Wood, & K.Beard  Oct.1994'
 38 cdaq  1.2       PRINT *,'     und Derek von der Westrum Jul 1995'
 39 cdaq  1.1       PRINT *
 40 cdaq  1.2       PRINT *,'**************************************************'
 41                 PRINT *,'*                                                *'
 42                 PRINT *,'*       Confused?  Don''t be.  Read the file      *'
 43                 PRINT *,'*   "~cdaq/documents/evdisplay/evdisplay.help"   *'
 44                 PRINT *,'*                                                *'
 45                 PRINT *,'**************************************************'
 46           *      PRINT *,' You need to specify the process and the machine you'
 47           *      PRINT *,' with which you want to connect this display process.'
 48           *      PRINT *,' Also, if you are using an Xwindow display'
 49           *      PRINT *,' you may need to run PAW once/session to get things to '
 50           *      PRINT *,' work correctly.'
 51 cdaq  1.1       PRINT *
 52                 PRINT *
 53                 PRINT *,' Enter the name of the machine running "engine" or CODA:'
 54                 PRINT *,' [cdaq1,cdaq2,hallc1,hallc2,cebafh, number; no default]:'
 55                 READ(5,'(a)') line
 56                 IF(line.EQ.' ') THEN
 57                   why= ':machine name must be specified!'
 58                   call G_add_path(here,why)
 59                   call G_rep_err(why)
 60                   STOP
 61                 ELSE
 62                   call NO_comments(line)
 63                   gen_display_server_machine= line
 64                 ENDIF
 65           *
 66                 PRINT *,' 0: Connect to offline replay'
 67                 PRINT *,' 1: Connect online analyzer'
 68                 PRINT *,' Other: A non-default RPC Program ID and version'
 69                 READ(5,'(2i30)') i,j
 70                 if(i.eq.0) then
 71                   gen_display_server_RPCprgmID = '2c0daFF8'x   !default offline
 72 cdaq  1.1         gen_display_server_RPCversionID = 1 ! default offline
 73                 else if(i.eq.1) then
 74                   gen_display_server_RPCprgmID = '2c0da005'x   !default online
 75                   gen_display_server_RPCversionID = 0 ! default online
 76                 else
 77                   gen_display_server_RPCprgmID = i
 78                   gen_display_server_RPCversionID = j
 79                 endif
 80           *
 81                 print *,"Server Program #=",gen_display_server_RPCprgmID
 82           *
 83                 PRINT *
 84                 PRINT *,' display type? [1= Xwindow[def.], 7878=GraphOn]'
 85                 READ(5,'(i30)') graph_io_dev
 86                 if(graph_io_dev.eq.0) graph_io_dev = 1
 87           *
 88                 call G_register_variables(FAIL,why)
 89                 IF(FAIL) THEN
 90                   call G_add_path(here,why)
 91                   call G_rep_err(why)
 92                   STOP
 93 cdaq  1.1       ENDIF
 94                 PRINT *,' G_register_variables OK'
 95                 PRINT *
 96           *      CALL r_one_ev_io
 97           
 98 cdaq  1.2 *
 99           *
100            100  print *
101                 print *, 'Type "h" for the HMS, or "s" for the SOS:'
102                 read *, spect
103                 if(spect.eq.'S') spect='s'
104                 if(spect.eq.'H') spect='h'
105                 if ((spect .ne. 's') .and. (spect .ne. 'h')) then
106                   print*, 'Invalid option.  Please type "h" or "s".'
107                   goto 100
108                 endif
109           *
110           *
111                 call revdis_init(FAIL,why)  ! Build lists of variables to get
112 cdaq  1.1 
113                 IF(FAIL) THEN
114                   call G_add_path(here,why)
115                   call G_rep_err(FAIL,why)
116                   STOP
117                 ELSE IF(g_config_filename.EQ.' ') THEN
118                   PRINT *
119                   PRINT *,' rpc/CTP FAILURE TO COMMUNICATE!'
120                   PRINT *
121                   STOP
122                 ENDIF
123           
124           *
125           *
126           *     Do the initialization that g_initialize was supposed to do
127           *
128                 call GZEBRA(NGBANK)
129 cdaq  1.2       call hlimit (-NHBOOK)             ! init HBOOK memory
130                 if (spect .eq. 'h') then
131                   call h_initialize(ABORT,err)
132                 elseif (spect .eq. 's') then
133                   call s_initialize(ABORT,err)
134                 endif
135 cdaq  1.1       call c_initialize(ABORT,err)
136                 call g_reset_event(ABORT,err)
137 cdaq  1.2 *     
138                 if(graph_io_dev .ne. 0) call hplint(graph_io_dev)
139                 if (graph_io_dev .eq. 0) then
140                   call hplint(0)                  ! init graphics
141                   call igmeta(-8,-111)            ! init HIGZ meta junk
142                 endif
143           
144                 if (spect .eq. 'h') then
145                   CALL h_uginit
146                 elseif (spect .eq. 's') then
147                   CALL s_uginit
148                 endif
149 cdaq  1.1 *
150                 PRINT *,' Connected to a Hall C analyzer at '
151                $     ,gen_display_server_machine(1:30)
152                 print *,' Server analyzer has the label'
153                 print *,' '
154                 print *,g_label
155                 print *,' '
156                 PRINT *,' ............begin loop......................'
157           *
158                 QUIT= .FALSE.
159           
160                 DO WHILE (.NOT.QUIT)
161           *
162                   PRINT *,' Next CTP condition for an event (?=help,1=any)?'
163                   READ(5,'(a)',ERR=99,END=99) line
164                   IF(line.EQ.'%EXIT' .or. line.EQ.'%QUIT') THEN
165                     QUIT= .TRUE.
166                   else
167                     call revdis_define(line,FAIL,why)
168                     if(.NOT.FAIL) then
169                       call revdis_getev(FAIL,why)
170 cdaq  1.1             If(FAIL) Then
171                         call G_rep_err(FAIL,why)
172                       Else
173                         write(6,'("Run",i6,", event ID",i7," sequence",i7)')
174                $             gen_run_number,gen_event_ID_number, gen_event_sequence_N
175 cdaq  1.2               if(spect.eq.'h') then
176                           call h_one_ev_display
177                         else if(spect.eq.'s') then
178                           call s_one_ev_display
179                         endif
180 cdaq  1.1             EndIf
181                     endif
182                   endif
183 cdaq  1.2 *     
184 cdaq  1.1       ENDDO
185           *
186            99   continue
187 cdaq  1.2       call IGEND                        !properly terminate HIGZ and any&all metafiles
188 cdaq  1.1       STOP
189                 END

Analyzer/Replay: Mark Jones, Documents: Stephen Wood
Powered by
ViewCVS 0.9.2-cvsgraph-1.4.0