mirror of
https://github.com/saitohirga/WSJT-X.git
synced 2024-11-15 08:31:57 -05:00
d431e2cecd
Re-factor the JT4, JT65 and JT9 decoders as Fortran modules using type bound procedures, the decoder types implement a callback procedure such that he client of the decoder can interpret the decode results as they need. The JT4 decoder has a second callback that delivers message averaging status. Also the previously separate source files lib/jt4a.f90 and lib/avg4.f90 have been merged into lib/jt4_decode.f90 as private type bound procedures of the new jt4_decoder type. Re-factored the lib/decoder.f90 subroutine to utilize the new decoder types. Added local procedures to process decodes and averaging results including the necessary OpenMP synchronization directives for parallel JT9+JT65 decoding. Added the jt65_test module which is a basic test harness for JT65 decoding. Re-factored the jt65 utility to utilize the new jt65_test module. Changed a few integers to logical variables where their meaning is clearly binary. git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@6324 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
53 lines
1.3 KiB
Fortran
53 lines
1.3 KiB
Fortran
subroutine softsym(id2,npts8,nsps8,newdat,fpk,syncpk,snrdb,xdt, &
|
|
freq,drift,a3,schk,i1SoftSymbols)
|
|
|
|
! Compute the soft symbols
|
|
|
|
use timer_module, only: timer
|
|
|
|
parameter (NZ2=1512,NZ3=1360)
|
|
logical, intent(inout) :: newdat
|
|
complex c2(0:NZ2-1)
|
|
complex c3(0:NZ3-1)
|
|
complex c5(0:NZ3-1)
|
|
real a(3)
|
|
integer*1 i1SoftSymbolsScrambled(207)
|
|
integer*1 i1SoftSymbols(207)
|
|
include 'jt9sync.f90'
|
|
|
|
nspsd=16
|
|
ndown=nsps8/nspsd
|
|
|
|
! Mix, low-pass filter, and downsample to 16 samples per symbol
|
|
call timer('downsam9',0)
|
|
call downsam9(id2,npts8,nsps8,newdat,nspsd,fpk,c2)
|
|
call timer('downsam9',1)
|
|
|
|
call peakdt9(c2,nsps8,nspsd,c3,xdt) !Find DT
|
|
|
|
fsample=1500.0/ndown
|
|
a=0.
|
|
call timer('afc9 ',0)
|
|
call afc9(c3,nz3,fsample,a,syncpk) !Find deltaF, fDot, fDDot
|
|
call timer('afc9 ',1)
|
|
freq=fpk - a(1)
|
|
drift=-2.0*a(2)
|
|
a3=a(3)
|
|
a(3)=0.
|
|
|
|
call timer('twkfreq ',0)
|
|
call twkfreq(c3,c5,nz3,fsample,a) !Correct for delta f, f1, f2 ==> a(1:3)
|
|
call timer('twkfreq ',1)
|
|
|
|
! Compute soft symbols (in scrambled order)
|
|
call timer('symspec2',0)
|
|
call symspec2(c5,nz3,nsps8,nspsd,fsample,freq,drift,snrdb,schk, &
|
|
i1SoftSymbolsScrambled)
|
|
call timer('symspec2',1)
|
|
|
|
! Remove interleaving
|
|
call interleave9(i1SoftSymbolsScrambled,-1,i1SoftSymbols)
|
|
|
|
return
|
|
end subroutine softsym
|