File: decode4.f90

package info (click to toggle)
wsjtx 2.7.0%2Brepack-1
  • links: PTS, VCS
  • area: main
  • in suites: trixie
  • size: 70,440 kB
  • sloc: cpp: 75,379; f90: 46,460; python: 27,241; ansic: 13,367; fortran: 2,382; makefile: 197; sh: 133
file content (112 lines) | stat: -rwxr-xr-x 2,929 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
subroutine decode4(dat,npts,dtx,nfreq,flip,mode4,ndepth,neme,minw,           &
     mycall,hiscall,hisgrid,decoded,nfano,deepbest,qbest,ichbest)

! Decodes JT4 data, assuming that DT and DF have already been determined.
! Input dat(npts) has already been downsampled by 2: rate = 11025/2.
! ### NB: this initial downsampling should be removed in WSJT-X, since
! it restricts the useful bandwidth to < 2.7 kHz.

  use jt4
  real dat(npts)                        !Raw data
  character decoded*22,deepmsg*22,deepbest*22
  character*12 mycall,hiscall
  character*6 hisgrid
  real*8 dt,df,phi,f0,dphi,twopi,phi1,dphi1
  complex*16 cz,cz1,c0,c1
  real*4 sym(207)

  twopi=8*atan(1.d0)
  dt=2.d0/11025             !Sample interval (2x downsampled data)
  df=11025.d0/2520.d0       !Tone separation for JT4A mode
  nsym=206
  amp=15.0
  istart=nint((dtx+0.8)/dt)              !Start index for synced FFTs
  if(istart.lt.0) istart=0
  nchips=0
  qbest=0.
  qtop=0.
  deepmsg='                      '
  ichbest=-1
  c0=0.
  k=istart
  phi=0.d0
  phi1=0.d0

  ich1=minw+1
  do ich=1,7
     if(nch(ich).le.mode4) ich2=ich
  enddo

  do ich=ich1,ich2
     nchips=min(nch(ich),70)
     nspchip=1260/nchips
     k=istart
     phi=0.d0
     phi1=0.d0
     fac2=1.e-8 * sqrt(float(mode4))
     do j=1,nsym+1
        if(flip.gt.0.0) then
           f0=nfreq + (npr(j))*mode4*df
           f1=nfreq + (2+npr(j))*mode4*df
        else
           f0=nfreq + (1-npr(j))*mode4*df
           f1=nfreq + (3-npr(j))*mode4*df
        endif
        dphi=twopi*dt*f0
        dphi1=twopi*dt*f1
        sq0=0.
        sq1=0.
        do nc=1,nchips
           phi=0.d0
           phi1=0.d0
           c0=0.
           c1=0.
           do i=1,nspchip
              k=k+1
              phi=phi+dphi
              phi1=phi1+dphi1
              cz=dcmplx(cos(phi),-sin(phi))
              cz1=dcmplx(cos(phi1),-sin(phi1))
              if(k.le.npts) then
                 c0=c0 + dat(k)*cz
                 c1=c1 + dat(k)*cz1
              endif
           enddo
           sq0=sq0 + real(c0)**2 + aimag(c0)**2
           sq1=sq1 + real(c1)**2 + aimag(c1)**2
        enddo
        sq0=fac2*sq0
        sq1=fac2*sq1
        rsym=amp*(sq1-sq0)
        if(j.ge.1) then
           rsymbol(j,ich)=rsym
           sym(j)=rsym
        endif
     enddo
     
     call extract4(sym,ncount,decoded)          !Do the convolutional decode
     nfano=0
     if(ncount.ge.0) then
        nfano=1
        ichbest=ich
        exit
     endif

     qual=0.                                    !Now try deep search
!     if(ndepth.ge.1) then
     if(iand(ndepth,32).eq.32) then
        call deep4(sym(2),neme,flip,mycall,hiscall,hisgrid,deepmsg,qual)
        if(qual.gt.qbest) then
           qbest=qual
           deepbest=deepmsg
           ichbest=ich
        endif
     endif
  enddo
  if(qbest.gt.qtop) then
     qtop=qbest
  endif
  qual=qbest

  return
end subroutine decode4