1subroutine fano232(symbol,nbits,mettab,ndelta,maxcycles,dat,     &
2     ncycles,metric,ierr)
3
4! Sequential decoder for K=32, r=1/2 convolutional code using
5! the Fano algorithm.  Translated from C routine for same purpose
6! written by Phil Karn, KA9Q.
7
8  parameter (MAXBITS=103)
9  parameter (MAXBYTES=13)          !(MAXBITS+7)/8
10  integer*1 symbol(0:2*MAXBITS-1)  !Soft symbols (as unsigned i*1)
11  integer*1 dat(MAXBYTES)          !Decoded user data, 8 bits per byte
12  integer mettab(-128:127,0:1)     !Metric table
13
14! These were the "node" structure in Karn's C code:
15  integer nstate(0:MAXBITS)        !Encoder state of next node
16  integer gamma(0:MAXBITS)         !Cumulative metric to this node
17  integer metrics(0:3,0:MAXBITS)   !Metrics indexed by all possible Tx syms
18  integer tm(0:1,0:MAXBITS)        !Sorted metrics for current hypotheses
19  integer ii(0:MAXBITS)            !Current branch being tested
20
21  logical noback
22  include 'conv232.f90'            !Polynomials defined here
23
24  ntail=nbits-31
25
26! Compute all possible branch metrics for each symbol pair.
27! This is the only place we actually look at the raw input symbols
28  i4a=0
29  i4b=0
30  do np=0,nbits-1
31     j=2*np
32     i4a=symbol(j)
33     i4b=symbol(j+1)
34     metrics(0,np) = mettab(i4a,0) + mettab(i4b,0)
35     metrics(1,np) = mettab(i4a,0) + mettab(i4b,1)
36     metrics(2,np) = mettab(i4a,1) + mettab(i4b,0)
37     metrics(3,np) = mettab(i4a,1) + mettab(i4b,1)
38  enddo
39
40  np=0
41  nstate(np)=0
42
43  n=iand(nstate(np),npoly1)                  !Compute and sort branch metrics
44  n=ieor(n,ishft(n,-16))                     !from the root node
45  lsym=partab(iand(ieor(n,ishft(n,-8)),255))
46  n=iand(nstate(np),npoly2)
47  n=ieor(n,ishft(n,-16))
48  lsym=lsym+lsym+partab(iand(ieor(n,ishft(n,-8)),255))
49  m0=metrics(lsym,np)
50  m1=metrics(ieor(3,lsym),np)
51  if(m0.gt.m1) then
52     tm(0,np)=m0                             !0-branch has better metric
53     tm(1,np)=m1
54  else
55     tm(0,np)=m1                             !1-branch is better
56     tm(1,np)=m0
57     nstate(np)=nstate(np) + 1               !Set low bit
58  endif
59
60  ii(np)=0                                   !Start with best branch
61  gamma(np)=0
62  nt=0
63
64  do i=1,nbits*maxcycles                     !Start the Fano decoder
65     ngamma=gamma(np) + tm(ii(np),np)        !Look forward
66     if(ngamma.ge.nt) then
67! Node is acceptable.  If first time visiting this node, tighten threshold:
68        if(gamma(np).lt.(nt+ndelta)) nt=nt + ndelta * ((ngamma-nt)/ndelta)
69        gamma(np+1)=ngamma                   !Move forward
70        nstate(np+1)=ishft(nstate(np),1)
71        np=np+1
72        if(np.eq.nbits) go to 100          !We're done!
73
74        n=iand(nstate(np),npoly1)
75        n=ieor(n,ishft(n,-16))
76        lsym=partab(iand(ieor(n,ishft(n,-8)),255))
77        n=iand(nstate(np),npoly2)
78        n=ieor(n,ishft(n,-16))
79        lsym=lsym+lsym+partab(iand(ieor(n,ishft(n,-8)),255))
80
81        if(np.ge.ntail) then
82           tm(0,np)=metrics(lsym,np)      !We're in the tail, now all zeros
83        else
84           m0=metrics(lsym,np)
85           m1=metrics(ieor(3,lsym),np)
86           if(m0.gt.m1) then
87              tm(0,np)=m0                 !0-branch has better metric
88              tm(1,np)=m1
89           else
90              tm(0,np)=m1                 !1-branch is better
91              tm(1,np)=m0
92              nstate(np)=nstate(np) + 1   !Set low bit
93           endif
94        endif
95        ii(np)=0                          !Start with best branch
96     else
97        do while(.true.)
98           noback=.false.                 !Threshold violated, can't go forward
99           if(np.eq.0) noback=.true.
100           if(np.gt.0) then
101              if(gamma(np-1).lt.nt) noback=.true.
102           endif
103
104           if(noback) then               !Can't back up, either
105              nt=nt-ndelta               !Relax threshold and look forward again
106              if(ii(np).ne.0) then
107                 ii(np)=0
108                 nstate(np)=ieor(nstate(np),1)
109              endif
110              exit
111           endif
112
113           np=np-1                       !Back up
114           if(np.lt.ntail .and. ii(np).ne.1) then
115              ii(np)=ii(np)+1            !Search the next best branch
116              nstate(np)=ieor(nstate(np),1)
117              exit
118           endif
119        enddo
120     endif
121  enddo
122  i=nbits*maxcycles
123
124100 metric=gamma(np)                       !Final path metric
125  nbytes=(nbits+7)/8                       !Copy decoded data to user's buffer
126  np=7
127  do j=1,nbytes-1
128     i4a=nstate(np)
129     dat(j)=int(i4a,1)
130     np=np+8
131  enddo
132  dat(nbytes)=0
133  ncycles=i+1
134  ierr=0
135  if(i.ge.maxcycles*nbits) ierr=-1
136
137  return
138end subroutine fano232
139