mirror of
https://github.com/saitohirga/WSJT-X.git
synced 2024-11-25 05:38:46 -05:00
Modifications to give QRA64 use of longer TR periods and tone-spacing submodes. Noy yet finished, or tested!
This commit is contained in:
parent
2de2874672
commit
bf38f4416c
@ -11,6 +11,7 @@ JT9+JT65 1110100000011110000100000000000010
|
||||
JT65 1110100000001110000100000000000010
|
||||
JT65/VHF 1111100100001101101011000100000000
|
||||
QRA64 1111100101101101100000000010000000
|
||||
QRA66 1111110101101101000100000011000000
|
||||
ISCAT 1001110000000001100000000000000000
|
||||
MSK144 1011111101000000000100010000000000
|
||||
WSPR 0000000000000000010100000000000000
|
||||
|
@ -197,7 +197,7 @@ subroutine multimode_decoder(ss,id2,params,nfsample)
|
||||
if(params%nmode.eq.66) then
|
||||
! We're in QRA66 mode
|
||||
call timer('decqra66',0)
|
||||
call my_qra66%decode(qra66_decoded,id2,params%nutc,params%nfqso, &
|
||||
call my_qra66%decode(qra66_decoded,id2,params%nutc,params%ntr,params%nfqso, &
|
||||
params%ntol,params%ndepth,mycall,hiscall,hisgrid)
|
||||
call timer('decqra66',1)
|
||||
go to 800
|
||||
@ -793,9 +793,11 @@ contains
|
||||
integer, intent(in) :: ntrperiod
|
||||
real, intent(in) :: fmid
|
||||
real, intent(in) :: w50
|
||||
integer navg
|
||||
|
||||
write(*,1001) nutc,nsnr,dt,nint(freq),decoded,irc
|
||||
1001 format(i6.6,i4,f5.1,i5,' + ',1x,a37,1x,i4)
|
||||
navg=irc/100
|
||||
write(*,1001) nutc,nsnr,dt,nint(freq),decoded,mod(irc,100),navg
|
||||
1001 format(i6.6,i4,f5.1,i5,' + ',1x,a37,1x,i2,i4)
|
||||
write(13,1002) nutc,nint(sync),nsnr,dt,freq,0,decoded
|
||||
1002 format(i6.6,i4,i5,f6.1,f8.0,i4,3x,a37,' QRA66')
|
||||
|
||||
|
@ -226,7 +226,7 @@ program jt9
|
||||
endif
|
||||
shared_data%id2=0 !??? Why is this necessary ???
|
||||
if(mode.eq.5) npts=21*3456
|
||||
if(mode.eq.66) npts=15*12000
|
||||
if(mode.eq.66) npts=TRperiod*12000
|
||||
do iblk=1,npts/kstep
|
||||
k=iblk*kstep
|
||||
if(mode.eq.8 .and. k.gt.179712) exit
|
||||
|
@ -4,24 +4,23 @@ program qra66sim
|
||||
|
||||
use wavhdr
|
||||
use packjt
|
||||
parameter (NMAX=15*12000) !180,000
|
||||
parameter (NFFT=NMAX,NH=NFFT/2)
|
||||
parameter (NMAX=300*12000) !Total samples in .wav file
|
||||
type(hdr) h !Header for .wav file
|
||||
integer*2 iwave(NMAX) !Generated waveform
|
||||
integer*4 itone(85) !Channel symbols (values 0-65)
|
||||
real*4 xnoise(NMAX) !Generated random noise
|
||||
real*4 dat(NMAX) !Generated real data
|
||||
complex cdat(NMAX) !Generated complex waveform
|
||||
complex cspread(0:NFFT-1) !Complex amplitude for Rayleigh fading
|
||||
complex cspread(0:NMAX-1) !Complex amplitude for Rayleigh fading
|
||||
complex z
|
||||
real*8 f0,dt,twopi,phi,dphi,baud,fsample,freq
|
||||
character msg*22,fname*13,csubmode*1,arg*12
|
||||
character msgsent*22
|
||||
|
||||
nargs=iargc()
|
||||
if(nargs.ne.7) then
|
||||
print *, 'Usage: qra66sim "msg" A|B freq fDop DT Nfiles SNR'
|
||||
print *, 'Example: qra66sim "K1ABC W9XYZ EN37" A 1500 0.2 0.0 1 -10'
|
||||
if(nargs.ne.8) then
|
||||
print *, 'Usage: qra66sim "msg" A-E freq fDop DT TRp Nfiles SNR'
|
||||
print *, 'Example: qra66sim "K1ABC W9XYZ EN37" A 1500 0.2 0.0 15 1 -10'
|
||||
go to 999
|
||||
endif
|
||||
call getarg(1,msg)
|
||||
@ -34,32 +33,48 @@ program qra66sim
|
||||
call getarg(5,arg)
|
||||
read(arg,*) xdt
|
||||
call getarg(6,arg)
|
||||
read(arg,*) nfiles
|
||||
read(arg,*) ntrperiod
|
||||
call getarg(7,arg)
|
||||
read(arg,*) nfiles
|
||||
call getarg(8,arg)
|
||||
read(arg,*) snrdb
|
||||
|
||||
|
||||
if(ntrperiod.eq.15) then
|
||||
nsps=1800
|
||||
else if(ntrperiod.eq.30) then
|
||||
nsps=3600
|
||||
else if(ntrperiod.eq.60) then
|
||||
nsps=7680
|
||||
else if(ntrperiod.eq.120) then
|
||||
nsps=16000
|
||||
else if(ntrperiod.eq.300) then
|
||||
nsps=41472
|
||||
else
|
||||
print*,'Invalid TR period'
|
||||
go to 999
|
||||
endif
|
||||
|
||||
rms=100.
|
||||
fsample=12000.d0 !Sample rate (Hz)
|
||||
npts=fsample*ntrperiod !Total samples in .wav file
|
||||
nfft=npts
|
||||
nh=nfft/2
|
||||
dt=1.d0/fsample !Sample interval (s)
|
||||
twopi=8.d0*atan(1.d0)
|
||||
npts=NMAX !Total samples in .wav file
|
||||
nsps=1800
|
||||
nsym=85 !Number of channel symbols
|
||||
if(csubmode.eq.'B') then
|
||||
nsps=nsps/2
|
||||
nsym=2*nsym-1
|
||||
endif
|
||||
mode66=2**(ichar(csubmode) - ichar('A'))
|
||||
print*,csubmode,mode66
|
||||
|
||||
ichk=66 !Flag sent to genqra64
|
||||
call genqra64(msg,ichk,msgsent,itone,itype)
|
||||
write(*,1001) itone
|
||||
1001 format('Channel symbols:'/(20i3))
|
||||
|
||||
baud=12000.d0/nsps !Keying rate = 6.25 baud
|
||||
baud=12000.d0/nsps !Keying rate (6.67 baud fot 15-s sequences)
|
||||
h=default_header(12000,npts)
|
||||
|
||||
write(*,1000)
|
||||
1000 format('File Freq A|B S/N DT Dop Message'/60('-'))
|
||||
1000 format('File Freq A-E S/N DT Dop Message'/60('-'))
|
||||
|
||||
do ifile=1,nfiles !Loop over requested number of files
|
||||
write(fname,1002) ifile !Output filename
|
||||
@ -85,9 +100,8 @@ program qra66sim
|
||||
do i=1,npts !Add this signal into cdat()
|
||||
isym=i/nsps + 1
|
||||
if(isym.gt.nsym) exit
|
||||
if(csubmode.eq.'B' .and. isym.gt.84) isym=isym-84
|
||||
if(isym.ne.isym0) then
|
||||
freq=f0 + itone(isym)*baud
|
||||
freq=f0 + itone(isym)*baud*mode66
|
||||
dphi=twopi*freq*dt
|
||||
isym0=isym
|
||||
endif
|
||||
@ -102,9 +116,9 @@ program qra66sim
|
||||
if(fspread.ne.0) then !Apply specified Doppler spread
|
||||
df=12000.0/nfft
|
||||
cspread(0)=1.0
|
||||
cspread(NH)=0.
|
||||
cspread(nh)=0.
|
||||
b=6.0 !Use truncated Lorenzian shape for fspread
|
||||
do i=1,NH
|
||||
do i=1,nh
|
||||
f=i*df
|
||||
x=b*f/fspread
|
||||
z=0.
|
||||
@ -120,12 +134,12 @@ program qra66sim
|
||||
phi2=twopi*rran()
|
||||
z=a*cmplx(cos(phi2),sin(phi2))
|
||||
endif
|
||||
cspread(NFFT-i)=z
|
||||
cspread(nfft-i)=z
|
||||
enddo
|
||||
|
||||
! do i=0,NFFT-1
|
||||
! do i=0,nfft-1
|
||||
! f=i*df
|
||||
! if(i.gt.NH) f=(i-nfft)*df
|
||||
! if(i.gt.nh) f=(i-nfft)*df
|
||||
! s=real(cspread(i))**2 + aimag(cspread(i))**2
|
||||
! write(13,3000) i,f,s,cspread(i)
|
||||
!3000 format(i5,f10.3,3f12.6)
|
||||
@ -133,19 +147,19 @@ program qra66sim
|
||||
! s=real(cspread(0))**2 + aimag(cspread(0))**2
|
||||
! write(13,3000) 1024,0.0,s,cspread(0)
|
||||
|
||||
call four2a(cspread,NFFT,1,1,1) !Transform to time domain
|
||||
call four2a(cspread,nfft,1,1,1) !Transform to time domain
|
||||
|
||||
sum=0.
|
||||
do i=0,NFFT-1
|
||||
do i=0,nfft-1
|
||||
p=real(cspread(i))**2 + aimag(cspread(i))**2
|
||||
sum=sum+p
|
||||
enddo
|
||||
avep=sum/NFFT
|
||||
avep=sum/nfft
|
||||
fac=sqrt(1.0/avep)
|
||||
cspread=fac*cspread !Normalize to constant avg power
|
||||
cdat=cspread*cdat !Apply Rayleigh fading
|
||||
|
||||
! do i=0,NFFT-1
|
||||
! do i=0,nfft-1
|
||||
! p=real(cspread(i))**2 + aimag(cspread(i))**2
|
||||
! write(14,3010) i,p,cspread(i)
|
||||
!3010 format(i8,3f12.6)
|
||||
|
@ -28,32 +28,51 @@ module qra66_decode
|
||||
|
||||
contains
|
||||
|
||||
subroutine decode(this,callback,iwave,nutc,nfqso,ntol,ndepth, &
|
||||
subroutine decode(this,callback,iwave,nutc,ntrperiod,nfqso,ntol,ndepth, &
|
||||
mycall,hiscall,hisgrid)
|
||||
|
||||
use timer_module, only: timer
|
||||
use packjt
|
||||
use, intrinsic :: iso_c_binding
|
||||
parameter (NFFT1=15*12000,NFFT2=15*6000)
|
||||
parameter (NMAX=60*12000) !### Needs to be 300*12000 ###
|
||||
class(qra66_decoder), intent(inout) :: this
|
||||
procedure(qra66_decode_callback) :: callback
|
||||
character(len=12) :: mycall, hiscall
|
||||
character(len=6) :: hisgrid
|
||||
character*37 decoded
|
||||
integer*2 iwave(NFFT1) !Raw data
|
||||
integer*2 iwave(NMAX) !Raw data
|
||||
integer dat4(12)
|
||||
logical lapdx,ltext
|
||||
complex c0(0:NFFT1-1) !Analytic signal, 6000 S/s
|
||||
complex c0(0:NMAX-1) !Analytic signal, 6000 S/s
|
||||
real s3(-64:127,63)
|
||||
real s3a(-64:127,63)
|
||||
real a(5)
|
||||
data nc1z/-1/,nc2z/-1/,ng2z/-1/,maxaptypez/-1/
|
||||
save nc1z,nc2z,ng2z,maxaptypez,nsave,s3a
|
||||
|
||||
this%callback => callback
|
||||
nsps=1800
|
||||
nfft1=ntrperiod*12000
|
||||
nfft2=ntrperiod*6000
|
||||
if(ntrperiod.eq.15) then
|
||||
nsps=1800
|
||||
else if(ntrperiod.eq.30) then
|
||||
nsps=3600
|
||||
else if(ntrperiod.eq.60) then
|
||||
nsps=7680
|
||||
else if(ntrperiod.eq.120) then
|
||||
nsps=16000
|
||||
else if(ntrperiod.eq.300) then
|
||||
nsps=41472
|
||||
else
|
||||
stop 'Invalid TR period'
|
||||
endif
|
||||
baud=12000.0/nsps
|
||||
df1=12000.0/NFFT1
|
||||
df1=12000.0/nfft1
|
||||
print*,'aaa',ntrperiod,hisgrid,nsps,baud
|
||||
do i=1,NMAX
|
||||
write(61,3061) i/12000.0,iwave(i)/32767.0
|
||||
3061 format(2f12.6)
|
||||
enddo
|
||||
this%callback => callback
|
||||
|
||||
if(nutc.eq.-999) print*,lapdx,nfa,nfb,nfqso !Silence warning
|
||||
|
||||
@ -87,15 +106,14 @@ contains
|
||||
naptype=maxaptype
|
||||
|
||||
! Downsample to give complex data at 6000 S/s
|
||||
fac=2.0/NFFT1
|
||||
fac=2.0/nfft1
|
||||
c0=fac*iwave
|
||||
call four2a(c0,NFFT1,1,-1,1) !Forward c2c FFT
|
||||
c0(NFFT2/2+1:NFFT2)=0. !Zero the top half
|
||||
call four2a(c0,nfft1,1,-1,1) !Forward c2c FFT
|
||||
c0(nfft2/2+1:nfft2)=0. !Zero the top half
|
||||
c0(0)=0.5*c0(0)
|
||||
call four2a(c0,nfft2,1,1,1) !Inverse c2c FFT
|
||||
|
||||
call timer('sync66 ',0)
|
||||
call sync66(iwave,15*12000,nsps,nfqso,ntol,xdt,f0,snr1)
|
||||
call sync66(iwave,60*12000,nsps,nfqso,ntol,xdt,f0,snr1) !### 300*12000 ###
|
||||
call timer('sync66 ',1)
|
||||
jpk=(xdt+0.5)*6000 - 384 !### Empirical ###
|
||||
if(jpk.lt.0) jpk=0
|
||||
@ -132,11 +150,11 @@ contains
|
||||
if(nsave.ge.2) then
|
||||
call qra64_dec(s3a,nc1,nc2,ng2,naptype,0,nSubmode,b90, &
|
||||
nFadingModel,dat4,snr2,irc)
|
||||
if(irc.ge.0) irc=10*nsave + irc
|
||||
if(irc.ge.0) irc=100*nsave + irc
|
||||
endif
|
||||
call timer('qra64_av',1)
|
||||
endif
|
||||
snr2=snr2 + 5.563 !10*log(6912/1920)
|
||||
snr2=snr2 + db(6912.0/nsps)
|
||||
if(irc.gt.0) call badmsg(irc,dat4,nc1,nc2,ng2)
|
||||
|
||||
decoded=' '
|
||||
|
@ -1,19 +1,27 @@
|
||||
subroutine sync66(iwave,nmax,nsps,nfqso,ntol,xdt,f0,snr1)
|
||||
|
||||
parameter (NSTEP=4) !Quarter-symbol steps
|
||||
parameter (IZ=1600,JZ=352,NSPSMAX=1920)
|
||||
integer*2 iwave(0:nmax-1) !Raw data
|
||||
integer b11(11) !Barker 11 code
|
||||
integer ijpk(2) !Indices i and j at peak of sync_sig
|
||||
real s1(IZ,JZ) !Symbol spectra
|
||||
real x(JZ) !Work array; 2FSK sync modulation
|
||||
real, allocatable :: s1(:,:) !Symbol spectra
|
||||
real, allocatable :: x(:) !Work array; 2FSK sync modulation
|
||||
real sync(4*85) !sync vector
|
||||
real sync_sig(-64:64,-15:15)
|
||||
complex c0(0:NSPSMAX) !Complex spectrum of symbol
|
||||
complex, allocatable :: c0(:) !Complex spectrum of symbol
|
||||
data b11/1,1,1,0,0,0,1,0,0,1,0/ !Barker 11 code
|
||||
data sync(1)/99.0/
|
||||
save sync
|
||||
|
||||
nfft=2*NSPS
|
||||
df=12000.0/nfft
|
||||
istep=nsps/NSTEP
|
||||
iz=5000.0/df
|
||||
jz=352
|
||||
allocate(s1(iz,jz))
|
||||
allocate(x(jz))
|
||||
allocate(c0(0:nsps))
|
||||
|
||||
if(sync(1).eq.99.0) then
|
||||
sync=0.
|
||||
do k=1,22
|
||||
@ -23,9 +31,6 @@ subroutine sync66(iwave,nmax,nsps,nfqso,ntol,xdt,f0,snr1)
|
||||
enddo
|
||||
endif
|
||||
|
||||
nfft=2*NSPS
|
||||
df=12000.0/nfft !3.125 Hz
|
||||
istep=nsps/NSTEP
|
||||
fac=1/32767.0
|
||||
do j=1,JZ !Compute symbol spectra
|
||||
ia=(j-1)*istep
|
||||
|
@ -70,7 +70,7 @@ program test_qra66
|
||||
if(len(trim(line)).lt.60) cycle
|
||||
read(line(11:20),*) xdt,nf
|
||||
if(abs(xdt-dt).lt.0.15 .and. abs(nf-nf0).lt.4) nsync=nsync+1
|
||||
read(line(60:),*) irc
|
||||
read(line(60:),*) irc,iavg
|
||||
if(irc.lt.0) cycle
|
||||
decok=index(line,'W9XYZ').gt.0
|
||||
if(decok) then
|
||||
@ -92,6 +92,8 @@ program test_qra66
|
||||
write(*,1100) nsnr,ndepth,fDop,nsync,ndecodes,navg,nfalse,nretcode,tdec/nfiles
|
||||
write(12,1100) nsnr,ndepth,fDop,nsync,ndecodes,navg,nfalse,nretcode,tdec/nfiles
|
||||
1100 format(i3,i2,i3,3i5,i4,i6,11i4,f6.2)
|
||||
flush(6)
|
||||
flush(12)
|
||||
enddo
|
||||
|
||||
999 end program test_qra66
|
||||
|
@ -6428,7 +6428,8 @@ void MainWindow::on_actionQRA66_triggered()
|
||||
m_wideGraph->setModeTx(m_modeTx);
|
||||
m_wideGraph->setPeriod(m_TRperiod,6912);
|
||||
// 0123456789012345678901234567890123
|
||||
displayWidgets(nWidgets("1111100001001100000100000001000000"));
|
||||
//displayWidgets(nWidgets("1111100001001100000100000001000000"));
|
||||
displayWidgets(nWidgets("1111110101101101000100000011000000"));
|
||||
statusChanged();}
|
||||
|
||||
void MainWindow::on_actionISCAT_triggered()
|
||||
|
@ -472,7 +472,7 @@ void CPlotter::DrawOverlay() //DrawOverlay()
|
||||
}
|
||||
|
||||
if(m_mode=="QRA66") { //QRA66
|
||||
bw=65.0*12000.0/1920.0;
|
||||
bw=65.0*12000.0/1800.0;
|
||||
}
|
||||
if(m_modeTx=="JT65") { //JT65
|
||||
bw=65.0*11025.0/4096.0;
|
||||
|
Loading…
Reference in New Issue
Block a user