FPSSGF COMMENTS
*-- Author :    R. Henderson   24/10/94
      SUBROUTINE FPSSGF(LSECSG)
C---------------------------------------------------------------                                              
C                                                                                                             
C     Routine checks the connectivity of the found                                                            
C                                                                                                             
C              SECONDARY and TERTIARY segments                                                                
C                                                                                                             
C     and returns an optimized non-connected solution in MASKSG                                               
C     0 = accept segment , -1 = reject segment                                                                
C                                                                                                             
C     the difference between this routine and FPSGRF is that it                                               
C     cannot assume that clusters are disconnected a priori                                                   
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                                                                                                             
C---                                                                                                          
*KEND.                                                                                                        
C---                                                                                                          
*KEEP,FPLSEG.                                                                                                 
C---                                                                                                          
C---                                                                                                          
*KEND.                                                                                                        
C---                                                                                                          
*KEEP,FPCLUS.                                                                                                 
C---                                                                                                          
*KEEP,FPH1WRK.                                                                                                
C--    *KEEP,FPCSEG.                                                                                          
C---                                                                                                          
C---                                                                                                          
C--    *KEEP,FPDIGI.                                                                                          
C---                                                                                                          
C--    *KEEP,FPDGI.                                                                                           
C---                                                                                                          
C--    *KEEP,FPSTID.                                                                                          
C---                                                                                                          
C--    *interface to real data                                                                                
C---.                                                                                                         
*KEND.                                                                                                        
C---                                                                                                          
*KEEP,FPSTSG.                                                                                                 
C---                                                                                                          
*KEND.                                                                                                        
C                                                                                                             
C---                                                                                                          
C---                                                                                                          
C---                                                                                                          
C---  Local variables                                                                                         
C---                                                                                                          
C---  ISGTAB (I,J) = segment number of Jth node connected to Ith node                                         
C---  KSGTAB (I)   = number of segments connected to Ith node                                                 
C---  MXLIS        = list of nodes with maximum connectivity                                                  
C---  CHLIS        = weight asscociated with each node listed in MXLIS                                        
C                                                                                                             
C                                                                                                             
C---  input                                                                                                   
C                                                                                                             
C     ASEGIN(SEG,SUPERMODULE)   = chisquare of segment                                                        
C                                                                                                             
C     ISEGIN(1,SEG,SUPERMODULE) = 1st cluster-plane for segment                                               
C     ISEGIN(2,SEG,SUPERMODULE) = 2nd cluster-plane for segment                                               
C     ISEGIN(3,SEG,SUPERMODULE) = 3rd cluster-plane for segment                                               
C     ISEGIN(4,SEG,SUPERMODULE) = number of degree of freedom for segmen                                      
C                                                                                                             
C     NFSEG(SUPERMODULE)        = number of found segments per supermodu                                      
C                                                                                                             
C---  output                                                                                                  
C                                                                                                             
C     MASKSG(SEG,SUPERMODULE)   = 0   if allowed                                                              
C                               = -1  if lost                                                                 
C                                                                                                             
         CALL FPPBIN
C                                                                                                             
C---  loop over supermodules                                                                                  
C                                                                                                             
C                                                                                                             
C---  define where secondary segments start depending on whether                                              
C---  called from Secondary or tertiary segment finder.                                                       
C                                                                                                             
C                                                                                                             
C---  zero ksgtab                                                                                             
C                                                                                                             
C                                                                                                             
C---  construct connectivity table                                                                            
C                                                                                                             
C                                                                                                             
C---  1st loop over segments                                                                                  
C                                                                                                             
C                                                                                                             
C---  remove if segs the same                                                                                 
C                                                                                                             
C                                                                                                             
C---  search to see if any cluster planes in common                                                           
C                                                                                                             
C                                                                                                             
C---  decode cluster planes                                                                                   
C                                                                                                             
*            IP1 = MOD(ICP1,10)                                                                               
C---                                                                                                          
C                                                                                                             
C---  decode cluster planes                                                                                   
C                                                                                                             
*            IP2 = MOD(ICP2,10)                                                                               
C                                                                                                             
C---  if planes the same loop over wires to see if same digits used                                           
C                                                                                                             
C                                                                                                             
C---  if digits are the same (and not 0) then build connection                                                
C                                                                                                             
*         IF(ICL1 .EQ. 0  .OR.  ICL2 .EQ. 0)GO TO 33                                                          
C                                                                                                             
C                                                                                                             
C                                                                                                             
C---  found one in common , increment counter , store connection                                              
C                                                                                                             
C                                                                                                             
C---  trap out of bounds. has been known to happen in MC!                                                     
C                                                                                                             
C                                                                                                             
C---  connection found skip furthur search of KSEG segment                                                    
C                                                                                                             
C                                                                                                             
C                                                                                                             
C                                                                                                             
C                                                                                                             
C                                                                                                             
C---  Start to remove connectivity                                                                            
C                                                                                                             
C                                                                                                             
C---  Find the highest multiplicity                                                                           
C                                                                                                             
       CALL VFLOAT(KSGTAB,FSGTAB,NFSEG(ISM))                                                           
C                                                                                                             
C---   Loop over all segments and find those with same multiplicity                                           
C                                                                                                             
C       IF(KSGTAB(ISEG) .LT. (IVMXSG-2)                                                                       
C                                                                                                             
C---  Find which segment contributes most to chisquare                                                        
C                                                                                                             
C                                                                                                             
C---   Find probablility of link segments                                                                     
C                                                                                                             
C                                                                                                             
C---   Store probability of links less own prob                                                               
C                                                                                                             
*      Fix for v.small chisq...                                                                               
        PROB1 = FPPROB(CHISUM,NDFSUM)
C        PROB1 = PROB(CHISUM,NDFSUM)                                                                          
        PROB2 = FPPROB(ASEGIN(MXSEG,ISM),ISEGIN(4,MXSEG,ISM))
C        PROB2 = PROB(ASEGIN(MXSEG,ISM),ISEGIN(4,MXSEG,ISM))                                                  
*        CHLIS(IMX) = PROB(CHISUM,NDFSUM) -                                                                   
*    1                PROB(ASEGIN(MXSEG,ISM),ISEGIN(4,MXSEG,ISM))                                             
C                                                                                                             
C                                                                                                             
C---  Find the segment with largest positive contribution                                                     
C                                                                                                             
C                                                                                                             
C---  Remove all reference to this segment from connectivity table                                            
C                                                                                                             
*      KSGTAB(IWSEG) = -1                                                                                     
*      DO 530 IS = NSTSSG, NFSEG(ISM)                                                                         
*        IF( KSGTAB(IS) .LT. 1)GO TO 530                                                                      
*          DO 531 ILS = 1, KSGTAB(IS)                                                                         
*            IF(ISGTAB(IS,ILS) .NE. IWSEG) GO TO 531                                                          
*              ISGTAB(IS,ILS) = ISGTAB(IS,KSGTAB(IS))                                                         
*              KSGTAB(IS) = KSGTAB(IS) - 1                                                                    
*  531     CONTINUE                                                                                           
*  530 CONTINUE                                                                                               
C                                                                                                             
C                                                                                                             
C---  Repeat proceedure on remaining nodes                                                                    
C                                                                                                             
C                                                                                                             
C                                                                                                             
C                                                                                                             
C---   No connectivity remaining                                                                              
C                                                                                                             
C---                                                                                                          
C                                                                                                             
C---  Write output bank                                                                                       
C                                                                                                             
C                                                                                                             
C---  Something horrible has happened - kill event!                                                           
C                                                                                                             
      CALL ERRLOG(217,'W:FPSSGF: Too much confusion! Planar data off')                                 
*