/[PAMELA software]/calo/unpacking/riempi.for
ViewVC logotype

Annotation of /calo/unpacking/riempi.for

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.1 - (hide annotations) (download)
Mon Dec 5 16:23:21 2005 UTC (18 years, 11 months ago) by mocchiut
Branch point for: MAIN, unpacking
Initial revision

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

  ViewVC Help
Powered by ViewVC 1.1.23