SUBROUTINE FPCPLN
*-- Author :  R. Henderson
      SUBROUTINE FPCPLN
C-------------------------------------------------------------                                                
C                                                                                                             
C---  routine calculates plane normal and constant                                                            
C---  for each cluster found by FPDIG4                                                                        
C                                                                                                             
C-------------------------------------------------------------                                                
C---                                                                                                          
*KEEP,FPPRAM.                                                                                                 
C                                                                                                             
C---  MAXSEG is maximum number of segments per supermodule                                                    
C---  MAXCON is maximum number of amibiguous segments associatable with                                       
C---         one segment                                                                                      
C---  LIMSTO is maximum number of 2 cluster planes intersections to be                                        
C---         stored per supermodule                                                                           
C---  MSEGLM is maximum number of clusters that can be found before                                           
C---         connectivity considered                                                                          
C---  MAXCLU is maximum number of clusters that can be found after                                            
C---         forming non-connected set    MUST BE 50 IF RUN WITH OLD RCW                                      
C---         (cluster = 3/4 digits found in a straight line in one                                            
C---          4-wire orientation)                                                                             
C                                                                                                             
      PARAMETER (MAXSEG = 200)                                          
      PARAMETER (MAXCON = 100)                                          
      PARAMETER (LIMSTO = 5000)                                         
      PARAMETER (MSEGLM = 150)                                          
      PARAMETER (MAXCLU = 50)                                           
C---                                                                                                          
*KEND.                                                                                                        
C---                                                                                                          
*KEEP,FPH1WRK.                                                                                                
      PARAMETER (MAXHTS=200)                                            
      PARAMETER (NUMWPL=36)                                             
      PARAMETER (MAXTRK=200)                                            
      PARAMETER (MXTTRK=900)                                            
      PARAMETER (MAXTR3=200)                                            
      PARAMETER (MAXHPW=2)                                              
      PARAMETER (MAXDIG=2000)                                           
      PARAMETER (NUMRWR=1727)                                           
      PARAMETER (NUMPWR=1151)                                           
      LOGICAL DRMASK                                                    
      COMMON /H1WORK/                                                   
C--    *KEEP,FPCSEG.                                                                                          
C---                                                                                                          
     3                  TPNORM(3,9,MAXCLU), PCONST(9,MAXCLU)     ,      
     4                 SMLS(4,2,LIMSTO,3) ,                             
C---                                                                                                          
C--    *KEEP,FPDIGI.                                                                                          
     5                 DRSTO(MSEGLM,4),NDRSTO(4),                       
     6               IDIGST(4,MSEGLM),                                  
     7               SEGTAB(MSEGLM,MSEGLM),DRMASK(MSEGLM,4),            
     8               IDCELL(MSEGLM,4),                                  
     9               NSGTAB(MSEGLM),ASGTAB(MSEGLM),                     
     A               RESSTO(MSEGLM,4) ,                                 
C---                                                                                                          
C--    *KEEP,FPDGI.                                                                                           
     B               IDGIST(MSEGLM,4),IDGISM(4,9,MAXCLU)                
     C               ,RCHI(MAXSEG,3) ,                                  
C---                                                                                                          
C--    *KEEP,FPSTID.                                                                                          
     D               IDRSTO(MSEGLM,4),IDYUV(4,9,MSEGLM),                
     E               IDYUVS(12,MAXSEG,3),FREQ(MSEGLM+1) ,               
C---                                                                                                          
C--    *interface to real data                                                                                
     F             NDPW(NUMWPL),DW(MAXHTS,NUMWPL),DWG(MAXHTS,NUMWPL),   
     G             DRIWP(MAXHTS,NUMWPL),DRIWM(MAXHTS,NUMWPL),           
     G             DRIW(MAXHTS,NUMWPL),IPHOLE(MAXHTS,NUMWPL),           
     H             IPFRPE(MAXHTS,36), IPPIOS(MAXDIG,2)                  
C---.                                                                                                         
*KEND.                                                                                                        
C---                                                                                                          
*KEEP,FPCLUS.                                                                                                 
      COMMON /FPCLUS/   TC(3,9,MAXCLU) , NTC(9) , TOC(3,9,MAXCLU) ,     
     2                 TCYUV(4,9,MAXCLU), TCYUVW(4,9,MAXCLU)            
C---                                                                                                          
*KEND.                                                                                                        
C---                                                                                                          
*KEEP,FPLGEO.                                                                                                 
C---                                                                                                          
      COMMON /FPLGEO/   ZPLAN(36)   , TP(9)   , YP(26)    , PLANE(3,9), 
     1                 RMAX    , RMIN    , YSTART    , YSPACE    ,      
     2                 X0      , Y0      , PZSTRU (8), STAGER   ,       
     3                 RESOL   , ACUT    , CTP(9)    , STP(9)           
C---                                                                                                          
*KEND.                                                                                                        
C---                                                                                                          
C                                                                                                             
C---  Calculate the normals to the planes formed by the tracks                                                
C---  and four wires in the same orientation for each cluster in each                                         
C---  plane                                                                                                   
C                                                                                                             
      DO 10 IPLANE = 1,9                                                
      DO 20 ITC    = 1,NTC(IPLANE)                                      
C                                                                                                             
C---  calculate normals                                                                                       
C                                                                                                             
      TPNORM(1,IPLANE,ITC) =                                            
     1         (   PLANE(3,IPLANE) * TC(2,IPLANE,ITC)                   
     2           - PLANE(2,IPLANE) * TC(3,IPLANE,ITC) )                 
      TPNORM(2,IPLANE,ITC) =                                            
     1       - (   PLANE(3,IPLANE) * TC(1,IPLANE,ITC)                   
     2           - PLANE(1,IPLANE) * TC(3,IPLANE,ITC) )                 
      TPNORM(3,IPLANE,ITC) =                                            
     1         (   PLANE(2,IPLANE) * TC(1,IPLANE,ITC)                   
     2           - PLANE(1,IPLANE) * TC(2,IPLANE,ITC) )                 
C                                                                                                             
C---  Normalize TPNORM                                                                                        
C                                                                                                             
          ALEN = SQRT ( TPNORM(1,IPLANE,ITC)**2 +                       
     1                  TPNORM(2,IPLANE,ITC)**2 +                       
     2                  TPNORM(3,IPLANE,ITC)**2 )                       
          DO 60 I=1,3                                                   
          TPNORM(I,IPLANE,ITC) = TPNORM (I,IPLANE,ITC) / ALEN           
   60     CONTINUE                                                      
C                                                                                                             
C---  Calculate the characteristic constant for this plane                                                    
C                                                                                                             
          PCONST(IPLANE,ITC) =                                          
     1                   TOC(1,IPLANE,ITC) * TPNORM(1,IPLANE,ITC)       
     2                 + TOC(2,IPLANE,ITC) * TPNORM(2,IPLANE,ITC)       
     3                 + TOC(3,IPLANE,ITC) * TPNORM(3,IPLANE,ITC)       
   20 CONTINUE                                                          
   10 CONTINUE                                                          
      END                                                               
*