2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								subroutine fano232(symbol,nbits,mettab,ndelta,maxcycles,dat,     &
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     ncycles,metric,ierr)
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								! Sequential decoder for K=32, r=1/2 convolutional code using 
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								! the Fano algorithm.  Translated from C routine for same purpose
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								! written by Phil Karn, KA9Q.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  parameter (MAXBITS=103)
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  parameter (MAXBYTES=(MAXBITS+7)/8)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  integer*1 symbol(0:2*MAXBITS-1)  !Soft symbols (as unsigned i*1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  integer*1 dat(MAXBYTES)          !Decoded user data, 8 bits per byte
							 | 
						
					
						
							
								
									
										
										
										
											2015-11-18 01:28:12 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  integer mettab(-128:127,0:1)     !Metric table
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								! These were the "node" structure in Karn's C code:
							 | 
						
					
						
							
								
									
										
										
										
											2015-11-18 01:28:12 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  integer nstate(0:MAXBITS)        !Encoder state of next node
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  integer gamma(0:MAXBITS)         !Cumulative metric to this node
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  integer metrics(0:3,0:MAXBITS)   !Metrics indexed by all possible Tx syms
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  integer tm(0:1,0:MAXBITS)        !Sorted metrics for current hypotheses
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  integer ii(0:MAXBITS)            !Current branch being tested
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  logical noback
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  include 'conv232.f90'            !Polynomials defined here
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  ntail=nbits-31
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								! Compute all possible branch metrics for each symbol pair.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								! This is the only place we actually look at the raw input symbols
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  i4a=0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  i4b=0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  do np=0,nbits-1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     j=2*np
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     i4a=symbol(j)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     i4b=symbol(j+1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     metrics(0,np) = mettab(i4a,0) + mettab(i4b,0)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     metrics(1,np) = mettab(i4a,0) + mettab(i4b,1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     metrics(2,np) = mettab(i4a,1) + mettab(i4b,0)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     metrics(3,np) = mettab(i4a,1) + mettab(i4b,1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  enddo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  np=0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  nstate(np)=0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  n=iand(nstate(np),npoly1)                  !Compute and sort branch metrics 
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  n=ieor(n,ishft(n,-16))                     !from the root node
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  lsym=partab(iand(ieor(n,ishft(n,-8)),255))
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  n=iand(nstate(np),npoly2)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  n=ieor(n,ishft(n,-16))
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  lsym=lsym+lsym+partab(iand(ieor(n,ishft(n,-8)),255))
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  m0=metrics(lsym,np)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  m1=metrics(ieor(3,lsym),np)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  if(m0.gt.m1) then
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     tm(0,np)=m0                             !0-branch has better metric
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     tm(1,np)=m1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  else
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     tm(0,np)=m1                             !1-branch is better
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     tm(1,np)=m0
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     nstate(np)=nstate(np) + 1               !Set low bit
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  endif
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  ii(np)=0                                   !Start with best branch
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  gamma(np)=0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  nt=0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  do i=1,nbits*maxcycles                     !Start the Fano decoder
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     ngamma=gamma(np) + tm(ii(np),np)        !Look forward
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     if(ngamma.ge.nt) then
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								! Node is acceptable.  If first time visiting this node, tighten threshold:
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        if(gamma(np).lt.(nt+ndelta)) nt=nt + ndelta * ((ngamma-nt)/ndelta)
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        gamma(np+1)=ngamma                   !Move forward
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        nstate(np+1)=ishft(nstate(np),1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        np=np+1
							 | 
						
					
						
							
								
									
										
										
										
											2015-11-18 01:28:12 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								        if(np.eq.nbits) go to 100          !We're done!
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        n=iand(nstate(np),npoly1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        n=ieor(n,ishft(n,-16))
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        lsym=partab(iand(ieor(n,ishft(n,-8)),255))
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        n=iand(nstate(np),npoly2)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        n=ieor(n,ishft(n,-16))
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        lsym=lsym+lsym+partab(iand(ieor(n,ishft(n,-8)),255))
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								            
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        if(np.ge.ntail) then
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								           tm(0,np)=metrics(lsym,np)      !We're in the tail, now all zeros
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        else
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           m0=metrics(lsym,np)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           m1=metrics(ieor(3,lsym),np)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           if(m0.gt.m1) then
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              tm(0,np)=m0                 !0-branch has better metric
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              tm(1,np)=m1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           else
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              tm(0,np)=m1                 !1-branch is better
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              tm(1,np)=m0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              nstate(np)=nstate(np) + 1   !Set low bit
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           endif
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        endif
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        ii(np)=0                          !Start with best branch
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								     else
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        do while(.true.)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           noback=.false.                 !Threshold violated, can't go forward
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           if(np.eq.0) noback=.true.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           if(np.gt.0) then
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              if(gamma(np-1).lt.nt) noback=.true.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           endif
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								           if(noback) then               !Can't back up, either
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              nt=nt-ndelta               !Relax threshold and look forward again
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              if(ii(np).ne.0) then
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								                 ii(np)=0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								                 nstate(np)=ieor(nstate(np),1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              endif
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              exit
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           endif
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								           np=np-1                       !Back up
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           if(np.lt.ntail .and. ii(np).ne.1) then
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              ii(np)=ii(np)+1            !Search the next best branch
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              nstate(np)=ieor(nstate(np),1)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								              exit
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								           endif
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        enddo
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     endif
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  enddo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  i=nbits*maxcycles
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								100 metric=gamma(np)                       !Final path metric
							 | 
						
					
						
							
								
									
										
										
										
											2012-10-20 16:37:01 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								  nbytes=(nbits+7)/8                       !Copy decoded data to user's buffer
							 | 
						
					
						
							
								
									
										
										
										
											2012-07-10 13:43:16 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  np=7
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  do j=1,nbytes-1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     i4a=nstate(np)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     dat(j)=i4a
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								     np=np+8
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  enddo
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  dat(nbytes)=0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  ncycles=i+1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  ierr=0
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  if(i.ge.maxcycles*nbits) ierr=-1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								  return
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								end subroutine fano232
							 |