/[PAMELA software]/yoda/techmodel/forroutines/calorimeter/riempi.for
ViewVC logotype

Annotation of /yoda/techmodel/forroutines/calorimeter/riempi.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.1 - (hide annotations) (download)
Thu Aug 19 15:24:48 2004 UTC (20 years, 4 months ago) by kusanagi
Branch: MAIN
*** empty log message ***

1 kusanagi 1.1
2     C-----------------------------------------------------
3     SUBROUTINE RIEMPI(m,lunga,lleng,lung,pari,vect,vecta)
4     C-----------------------------------------------------
5    
6     IMPLICIT NONE
7     C
8     integer m, lunga ,lleng, lung, i, bi, bit,pari
9     INTEGER*2 VECT(30000)
10     INTEGER*1 VECTA(lung)
11     C
12     INTEGER iev,iev2
13     C
14     INTEGER NPLA, NCHA, LENSEV
15     PARAMETER (NPLA=22,NCHA=96,LENSEV=NPLA*NCHA)
16     INTEGER merror(4)
17     integer*2 e2(4)
18     INTEGER contr
19     REAL DEXY(2,NPLA,NCHA), dexyc(2,npla,ncha), base(2,npla,6)
20    
21    
22     real calselftrig(4,7), calIItrig(4), calstripshit(4),
23     & calDSPtaberr(4), calevnum(4)
24    
25    
26     REAL calped(4,11,96), calgood(4,11,96), calthr(4,11,6)
27     REAL calrms(4,11,96), calbase(4,11,6), calvar(4,11,6)
28     REAL calpuls(4,11,96)
29     real perror(4)
30     integer stwerr(4)
31    
32     COMMON / evento / IEV, stwerr,perror,
33     & dexy,dexyc,base,
34     & calselftrig,calIItrig,
35     & calstripshit,calDSPtaberr,calevnum
36    
37     save / evento /
38    
39     COMMON / calib / IEV2, calped, calgood, calthr, calrms,
40     & calbase,
41     & calvar,
42     & calpuls
43    
44     save / calib /
45     c
46     COMMON / VARIE / merror, CONTR, e2
47     SAVE / VARIE /
48     C
49     do i = 1, (lunga - lleng)
50     vect(i) = 0
51     if (m.le.lung) then
52     do bit=0, 7
53     if (pari.eq.1.and.m.eq.lung) then
54     bi = ibits(vecta(m+1),bit,1)
55     if (bi.eq.1) vect(i) = ibset(vect(i),bit)
56     endif
57     if (m.lt.lung) then
58     bi = ibits(vecta(m+1),bit,1)
59     if (bi.eq.1) vect(i) = ibset(vect(i),bit)
60     endif
61     bi = ibits(vecta(m),bit,1)
62     if (bi.eq.1) vect(i) = ibset(vect(i),bit+8)
63     enddo
64     endif
65     m = m + 2
66     enddo
67     c
68     17 FORMAT(2X,'Elemento:',2X,I4,2X,' word:',2X,Z8)
69     return
70     end

  ViewVC Help
Powered by ViewVC 1.1.23