mirror of
				https://github.com/saitohirga/WSJT-X.git
				synced 2025-10-27 11:00:32 -04:00 
			
		
		
		
	Further progress on JT65 decoding with averaging and variable smoothing.
Please note: it's far from finished! git-svn-id: svn+ssh://svn.code.sf.net/p/wsjt/wsjt/branches/wsjtx@6513 ab8295b8-cf94-4d9e-aec4-7959e3be5d79
This commit is contained in:
		
							parent
							
								
									7d477606f0
								
							
						
					
					
						commit
						1288e64137
					
				| @ -12,12 +12,12 @@ subroutine decode65a(dd,npts,newdat,nqd,f0,nflip,mode65,ntrials,     & | |||||||
|   complex cx1(NMAX/8)                !Data at 1378.125 sps, offset by 355.3 Hz |   complex cx1(NMAX/8)                !Data at 1378.125 sps, offset by 355.3 Hz | ||||||
|   complex c5x(NMAX/32)               !Data at 344.53125 Hz |   complex c5x(NMAX/32)               !Data at 344.53125 Hz | ||||||
|   complex c5a(512) |   complex c5a(512) | ||||||
|   real s1(-255:256,126) |  | ||||||
|   real s2(66,126) |   real s2(66,126) | ||||||
|   real a(5) |   real a(5) | ||||||
|   logical first |   logical first | ||||||
|   character decoded*22,decoded_best*22 |   character decoded*22,decoded_best*22 | ||||||
|   character mycall*12,hiscall*12,hisgrid*6 |   character mycall*12,hiscall*12,hisgrid*6 | ||||||
|  |   common/test002/s1(-255:256,126) | ||||||
|   data first/.true./,jjjmin/1000/,jjjmax/-1000/ |   data first/.true./,jjjmin/1000/,jjjmax/-1000/ | ||||||
|   data nhz0/-9999999/ |   data nhz0/-9999999/ | ||||||
|   save |   save | ||||||
|  | |||||||
| @ -83,10 +83,11 @@ subroutine multimode_decoder(ss,id2,params,nfsample) | |||||||
|      nf1=params%nfa |      nf1=params%nfa | ||||||
|      nf2=params%nfb |      nf2=params%nfb | ||||||
|      call timer('jt65a   ',0) |      call timer('jt65a   ',0) | ||||||
|      call my_jt65%decode(jt65_decoded,dd,npts65,newdat65,params%nutc,nf1,nf2,params%nfqso,  & |      call my_jt65%decode(jt65_decoded,dd,npts65,newdat65,params%nutc,      & | ||||||
|           ntol65,params%nsubmode,params%minsync,logical(params%nagain),params%n2pass,       & |           nf1,nf2,params%nfqso,ntol65,params%nsubmode,params%minsync,      & | ||||||
|           logical(params%nrobust),ntrials,params%naggressive,params%ndepth,params%mycall,   & |           logical(params%nagain),params%n2pass,logical(params%nrobust),    & | ||||||
|           params%hiscall,params%hisgrid,params%nexp_decode) |           ntrials,params%naggressive,params%ndepth,params%nclearave,       & | ||||||
|  |           params%mycall,params%hiscall,params%hisgrid,params%nexp_decode) | ||||||
|      call timer('jt65a   ',1) |      call timer('jt65a   ',1) | ||||||
| 
 | 
 | ||||||
|   else if(params%nmode.eq.9 .or. (params%nmode.eq.(65+9) .and. params%ntxmode.eq.9)) then |   else if(params%nmode.eq.9 .or. (params%nmode.eq.(65+9) .and. params%ntxmode.eq.9)) then | ||||||
| @ -105,9 +106,10 @@ subroutine multimode_decoder(ss,id2,params,nfsample) | |||||||
|         nf1=params%nfa |         nf1=params%nfa | ||||||
|         nf2=params%nfb |         nf2=params%nfb | ||||||
|         call timer('jt65a   ',0) |         call timer('jt65a   ',0) | ||||||
|         call my_jt65%decode(jt65_decoded,dd,npts65,newdat65,params%nutc,nf1,nf2,            & |         call my_jt65%decode(jt65_decoded,dd,npts65,newdat65,params%nutc,   & | ||||||
|              params%nfqso,ntol65,params%nsubmode,params%minsync,logical(params%nagain),     & |              nf1,nf2,params%nfqso,ntol65,params%nsubmode,params%minsync,   & | ||||||
|              params%n2pass,logical(params%nrobust),ntrials,params%naggressive,params%ndepth,& |              logical(params%nagain),params%n2pass,logical(params%nrobust), & | ||||||
|  |              ntrials,params%naggressive,params%ndepth,params%nclearave,    & | ||||||
|              params%mycall,params%hiscall,params%hisgrid,params%nexp_decode) |              params%mycall,params%hiscall,params%hisgrid,params%nexp_decode) | ||||||
|         call timer('jt65a   ',1) |         call timer('jt65a   ',1) | ||||||
|      else |      else | ||||||
| @ -133,8 +135,8 @@ subroutine multimode_decoder(ss,id2,params,nfsample) | |||||||
| 
 | 
 | ||||||
| contains | contains | ||||||
| 
 | 
 | ||||||
|   subroutine jt4_decoded (this, utc, snr, dt, freq, have_sync, sync, is_deep, decoded, qual,& |   subroutine jt4_decoded(this,utc,snr,dt,freq,have_sync,sync,is_deep,    & | ||||||
|        ich, is_average, ave) |        decoded,qual,ich,is_average,ave) | ||||||
|     implicit none |     implicit none | ||||||
|     class(jt4_decoder), intent(inout) :: this |     class(jt4_decoder), intent(inout) :: this | ||||||
|     integer, intent(in) :: utc |     integer, intent(in) :: utc | ||||||
| @ -156,13 +158,15 @@ contains | |||||||
|        if (int(qual).gt.0) then |        if (int(qual).gt.0) then | ||||||
|           write(cqual, '(i2)') int(qual) |           write(cqual, '(i2)') int(qual) | ||||||
|           if (ave.gt.0) then |           if (ave.gt.0) then | ||||||
|              write(*,1000) utc ,snr, dt, freq, sync, decoded, cqual,                        & |              write(*,1000) utc,snr,dt,freq,sync,decoded,cqual,           & | ||||||
|                   char(ichar('A')+ich-1), ave |                   char(ichar('A')+ich-1), ave | ||||||
|           else |           else | ||||||
|              write(*,1000) utc ,snr, dt, freq, sync, decoded, cqual, char(ichar('A')+ich-1) |              write(*,1000) utc,snr,dt,freq,sync,decoded,cqual,           & | ||||||
|  |                   char(ichar('A')+ich-1) | ||||||
|           end if |           end if | ||||||
|        else |        else | ||||||
|           write(*,1000) utc ,snr, dt, freq, sync, decoded, ' *', char(ichar('A')+ich-1) |           write(*,1000) utc,snr,dt,freq,sync,decoded,' *',               & | ||||||
|  |                char(ichar('A')+ich-1) | ||||||
|        end if |        end if | ||||||
|     else |     else | ||||||
|        write(*,1000) utc ,snr, dt, freq |        write(*,1000) utc ,snr, dt, freq | ||||||
| @ -194,8 +198,9 @@ contains | |||||||
| 1000 format(a1,i5.4,f6.1,f6.2,i6,1x,a1) | 1000 format(a1,i5.4,f6.1,f6.2,i6,1x,a1) | ||||||
|   end subroutine jt4_average |   end subroutine jt4_average | ||||||
| 
 | 
 | ||||||
|   subroutine jt65_decoded (this, utc, sync, snr, dt, freq, drift, decoded, ft, qual,        & |   subroutine jt65_decoded(this,utc,sync,snr,dt,freq,drift,decoded,ft,     & | ||||||
|        candidates, tries, total_min, hard_min, aggression) |        qual,nsmo,nsum,minsync,nsubmode,naggressive) | ||||||
|  | 
 | ||||||
|     use jt65_decode |     use jt65_decode | ||||||
|     implicit none |     implicit none | ||||||
| 
 | 
 | ||||||
| @ -209,36 +214,40 @@ contains | |||||||
|     character(len=22), intent(in) :: decoded |     character(len=22), intent(in) :: decoded | ||||||
|     integer, intent(in) :: ft |     integer, intent(in) :: ft | ||||||
|     integer, intent(in) :: qual |     integer, intent(in) :: qual | ||||||
|     integer, intent(in) :: candidates |     integer, intent(in) :: nsmo | ||||||
|     integer, intent(in) :: tries |     integer, intent(in) :: nsum | ||||||
|     integer, intent(in) :: total_min |     integer, intent(in) :: minsync | ||||||
|     integer, intent(in) :: hard_min |     integer, intent(in) :: nsubmode | ||||||
|     integer, intent(in) :: aggression |     integer, intent(in) :: naggressive | ||||||
| 
 | 
 | ||||||
|     integer param(0:9) |     integer nft,nsmo2,nsum2 | ||||||
|     integer nsmo |     character*3 ctail | ||||||
|     real rtt |     character*36 c | ||||||
|     common/test000/param                              !### TEST ONLY ### |     data c/'0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ'/ | ||||||
| 
 | 
 | ||||||
|     rtt=0.001*param(4) | !$omp critical(decode_results) | ||||||
|     nsmo=param(9) | !    write(*,3301) ft,qual,nsmo,nsum,minsync,naggressive,sync    !### | ||||||
|  | !3301 format('decoded.f90:',6i3,f5.1)        !### | ||||||
| 
 | 
 | ||||||
|     !$omp critical(decode_results) |     if(int(sync).lt.minsync) then | ||||||
|     if(ft.eq.2 .or. nsmo.gt.0) then |        write(*,1010) utc,snr,dt,freq | ||||||
|        write(*,1010) utc,snr,dt,freq,decoded,ft,nsmo |  | ||||||
|     else |     else | ||||||
|        write(*,1010) utc,snr,dt,freq,decoded |        ctail='   ' | ||||||
| 1010 format(i4.4,i4,f5.1,i5,1x,'#',1x,a22,i4,i2) |        if(naggressive.gt.0 .and. ft.gt.0) then | ||||||
|  |           ctail(1:1)='~' | ||||||
|  |           if(ft.eq.1) ctail(1:1)='*' | ||||||
|  |           ctail(2:2)=c(nsum+1:nsum+1) | ||||||
|  |           if(nsubmode.gt.0) ctail(3:3)=c(nsmo+1:nsmo+1) | ||||||
|        endif |        endif | ||||||
|  |        write(*,1010) utc,snr,dt,freq,'*',decoded,ctail | ||||||
|  | 1010   format(i4.4,i4,f5.1,i5,1x,a1,1x,a22,a3) | ||||||
|  |     endif | ||||||
|  | 
 | ||||||
|     write(13,1012) utc,nint(sync),snr,dt,float(freq),drift,decoded,ft,nsmo |     write(13,1012) utc,nint(sync),snr,dt,float(freq),drift,decoded,ft,nsmo | ||||||
| 1012 format(i4.4,i4,i5,f6.1,f8.0,i4,3x,a22,' JT65',i4,i2) | 1012 format(i4.4,i4,i5,f6.1,f8.0,i4,3x,a22,' JT65',i4,i2) | ||||||
|     call flush(6) |     call flush(6) | ||||||
| !    write(79,3001) utc,sync,snr,dt,freq,candidates,    & |  | ||||||
| !         hard_min,total_min,rtt,tries,ft,min(qual,99),decoded |  | ||||||
| !3001 format(i4.4,f5.1,i4,f5.1,i5,i6,i3,i4,f6.3,i8,i2,i3,1x,a22) |  | ||||||
| !    flush(79) |  | ||||||
| 
 | 
 | ||||||
|     !$omp end critical(decode_results) | !$omp end critical(decode_results) | ||||||
|     select type(this) |     select type(this) | ||||||
|     type is (counting_jt65_decoder) |     type is (counting_jt65_decoder) | ||||||
|        this%decoded = this%decoded + 1 |        this%decoded = this%decoded + 1 | ||||||
|  | |||||||
| @ -12,8 +12,9 @@ module jt65_decode | |||||||
|   ! Callback function to be called with each decode |   ! Callback function to be called with each decode | ||||||
|   ! |   ! | ||||||
|   abstract interface |   abstract interface | ||||||
|      subroutine jt65_decode_callback (this, utc, sync, snr, dt, freq, drift,          & |      subroutine jt65_decode_callback(this,utc,sync,snr,dt,freq,drift,     & | ||||||
|           decoded, ft, qual, candidates, tries, total_min, hard_min, aggression) |           decoded,ft,qual,nsmo,nsum,minsync,nsubmode,naggressive) | ||||||
|  | 
 | ||||||
|        import jt65_decoder |        import jt65_decoder | ||||||
|        implicit none |        implicit none | ||||||
|        class(jt65_decoder), intent(inout) :: this |        class(jt65_decoder), intent(inout) :: this | ||||||
| @ -26,19 +27,20 @@ module jt65_decode | |||||||
|        character(len=22), intent(in) :: decoded |        character(len=22), intent(in) :: decoded | ||||||
|        integer, intent(in) :: ft |        integer, intent(in) :: ft | ||||||
|        integer, intent(in) :: qual |        integer, intent(in) :: qual | ||||||
|        integer, intent(in) :: candidates |        integer, intent(in) :: nsmo | ||||||
|        integer, intent(in) :: tries |        integer, intent(in) :: nsum | ||||||
|        integer, intent(in) :: total_min |        integer, intent(in) :: minsync | ||||||
|        integer, intent(in) :: hard_min |        integer, intent(in) :: nsubmode | ||||||
|        integer, intent(in) :: aggression |        integer, intent(in) :: naggressive | ||||||
|  | 
 | ||||||
|      end subroutine jt65_decode_callback |      end subroutine jt65_decode_callback | ||||||
|   end interface |   end interface | ||||||
| 
 | 
 | ||||||
| contains | contains | ||||||
| 
 | 
 | ||||||
|   subroutine decode(this,callback,dd0,npts,newdat,nutc,nf1,nf2,nfqso,ntol,nsubmode,   & |   subroutine decode(this,callback,dd0,npts,newdat,nutc,nf1,nf2,nfqso,     & | ||||||
|        minsync,nagain,n2pass,nrobust,ntrials,naggressive,ndepth,       & |        ntol,nsubmode,minsync,nagain,n2pass,nrobust,ntrials,naggressive,   & | ||||||
|        mycall,hiscall,hisgrid,nexp_decode) |        ndepth,nclearave,mycall,hiscall,hisgrid,nexp_decode) | ||||||
| 
 | 
 | ||||||
|     !  Process dd0() data to find and decode JT65 signals. |     !  Process dd0() data to find and decode JT65 signals. | ||||||
| 
 | 
 | ||||||
| @ -167,7 +169,11 @@ contains | |||||||
|           call timer('decod65a',1) |           call timer('decod65a',1) | ||||||
|           nfreq=nint(freq+a(1)) |           nfreq=nint(freq+a(1)) | ||||||
|           ndrift=nint(2.0*a(2)) |           ndrift=nint(2.0*a(2)) | ||||||
| !### |           s2db=10.0*log10(sync2) - 35             !### empirical ### | ||||||
|  |           nsnr=nint(s2db) | ||||||
|  |           if(nsnr.lt.-30) nsnr=-30 | ||||||
|  |           if(nsnr.gt.-1) nsnr=-1 | ||||||
|  | 
 | ||||||
|           if(nft.ne.1 .and. ndepth.ge.4 .and. (.not.prtavg)) then |           if(nft.ne.1 .and. ndepth.ge.4 .and. (.not.prtavg)) then | ||||||
| ! Single-sequence FT decode failed, so try for an average FT decode. | ! Single-sequence FT decode failed, so try for an average FT decode. | ||||||
|              if(nutc.ne.nutc0 .or. abs(nfreq-nfreq0).gt.ntol) then |              if(nutc.ne.nutc0 .or. abs(nfreq-nfreq0).gt.ntol) then | ||||||
| @ -175,25 +181,29 @@ contains | |||||||
|                 nutc0=nutc |                 nutc0=nutc | ||||||
|                 nfreq0=nfreq |                 nfreq0=nfreq | ||||||
|                 nsave=nsave+1 |                 nsave=nsave+1 | ||||||
|  |                 nsave=mod(nsave-1,64)+1 | ||||||
|                 call avg65(nutc,nsave,sync1,dtx,nflip,nfreq,mode65,ntol,    & |                 call avg65(nutc,nsave,sync1,dtx,nflip,nfreq,mode65,ntol,    & | ||||||
|                      ndepth,neme,mycall,hiscall,hisgrid,nftt,avemsg,        & |                      ndepth,nclearave,neme,mycall,hiscall,hisgrid,nftt,     & | ||||||
|                      qave,deepave,ich,ndeepave) |                      avemsg,qave,deepave,nsum,ndeepave) | ||||||
| 
 | 
 | ||||||
|                 if (associated(this%callback)) then |                 if (associated(this%callback)) then | ||||||
|  | !                   print*,'FT1 failed; nsave,nftt: ',nsave,nftt | ||||||
|  | !                   print*,'A',nftt,nsum,nsmo | ||||||
|                    call this%callback(nutc,sync1,nsnr,dtx-1.0,nfreq,ndrift,  & |                    call this%callback(nutc,sync1,nsnr,dtx-1.0,nfreq,ndrift,  & | ||||||
|                         decoded,nft,nqual,ncandidates,ntry,ntotal_min,       & |                         avemsg,nftt,nqual,nsmo,nsum,minsync,nsubmode,       & | ||||||
|                         nhard_min,naggressive) |                         naggressive) | ||||||
|  |                    prtavg=.true. | ||||||
|  |                    cycle | ||||||
|                 end if |                 end if | ||||||
| 
 | 
 | ||||||
|              endif |              endif | ||||||
|           endif |           endif | ||||||
|           if(nftt.eq.1) then | !          if(nftt.eq.1) then | ||||||
| !             print*,'A: ',avemsg,nftt | !             nft=1 | ||||||
|              nft=1 | !             decoded=avemsg | ||||||
|              decoded=avemsg | !             go to 5 | ||||||
|              go to 5 | !          endif | ||||||
|           endif | 
 | ||||||
| !### |  | ||||||
|           n=naggressive |           n=naggressive | ||||||
|           rtt=0.001*nrtt1000 |           rtt=0.001*nrtt1000 | ||||||
|           if(nft.lt.2) then |           if(nft.lt.2) then | ||||||
| @ -203,10 +213,7 @@ contains | |||||||
|              if(rtt.gt.r0(n)) cycle |              if(rtt.gt.r0(n)) cycle | ||||||
|           endif |           endif | ||||||
| 
 | 
 | ||||||
| 5         continue | 5         if(decoded.eq.decoded0 .and. abs(freq-freq0).lt. 3.0 .and.    & | ||||||
| !          print*,'B: ',avemsg,nftt |  | ||||||
| 
 |  | ||||||
|           if(decoded.eq.decoded0 .and. abs(freq-freq0).lt. 3.0 .and.    & |  | ||||||
|                minsync.ge.0) cycle                  !Don't display dupes |                minsync.ge.0) cycle                  !Don't display dupes | ||||||
| 
 | 
 | ||||||
|           if(decoded.ne.'                      ' .or. minsync.lt.0) then |           if(decoded.ne.'                      ' .or. minsync.lt.0) then | ||||||
| @ -215,10 +222,6 @@ contains | |||||||
|                 call subtract65(dd,npts,freq,dtx) |                 call subtract65(dd,npts,freq,dtx) | ||||||
|                 call timer('subtr65 ',1) |                 call timer('subtr65 ',1) | ||||||
|              endif |              endif | ||||||
|              s2db=10.0*log10(sync2) - 35             !### empirical ### |  | ||||||
|              nsnr=nint(s2db) |  | ||||||
|              if(nsnr.lt.-30) nsnr=-30 |  | ||||||
|              if(nsnr.gt.-1) nsnr=-1 |  | ||||||
| 
 | 
 | ||||||
|              ndupe=0 ! de-dedupe |              ndupe=0 ! de-dedupe | ||||||
|              do i=1, ndecoded |              do i=1, ndecoded | ||||||
| @ -237,9 +240,10 @@ contains | |||||||
|                 dec(ndecoded)%decoded=decoded |                 dec(ndecoded)%decoded=decoded | ||||||
|                 nqual=min(qual,9999.0) |                 nqual=min(qual,9999.0) | ||||||
|                 if (associated(this%callback)) then |                 if (associated(this%callback)) then | ||||||
|  | !                   print*,'B',nsave,nft,nsmo,nsum | ||||||
|                    call this%callback(nutc,sync1,nsnr,dtx-1.0,nfreq,ndrift,  & |                    call this%callback(nutc,sync1,nsnr,dtx-1.0,nfreq,ndrift,  & | ||||||
|                         decoded,nft,nqual,ncandidates,ntry,ntotal_min,       & |                         decoded,nft,nqual,nsmo,nsum,minsync,nsubmode,        & | ||||||
|                         nhard_min,naggressive) |                         naggressive) | ||||||
|                 end if |                 end if | ||||||
|              endif |              endif | ||||||
|              decoded0=decoded |              decoded0=decoded | ||||||
| @ -254,9 +258,11 @@ contains | |||||||
|   end subroutine decode |   end subroutine decode | ||||||
| 
 | 
 | ||||||
|   subroutine avg65(nutc,nsave,snrsync,dtxx,nflip,nfreq,mode65,ntol,ndepth,  & |   subroutine avg65(nutc,nsave,snrsync,dtxx,nflip,nfreq,mode65,ntol,ndepth,  & | ||||||
|        neme,mycall,hiscall,hisgrid,nftt,avemsg,qave,deepave,ichbest,    & |        nclearave,neme,mycall,hiscall,hisgrid,nftt,avemsg,qave,deepave,      & | ||||||
|        ndeepave) |        nsum,ndeepave) | ||||||
|  | 
 | ||||||
| ! Decodes averaged JT65 data | ! Decodes averaged JT65 data | ||||||
|  | 
 | ||||||
|     parameter (MAXAVE=64) |     parameter (MAXAVE=64) | ||||||
|     character*22 avemsg,deepave,deepbest |     character*22 avemsg,deepave,deepbest | ||||||
|     character mycall*12,hiscall*12,hisgrid*6 |     character mycall*12,hiscall*12,hisgrid*6 | ||||||
| @ -276,12 +282,13 @@ contains | |||||||
|     common/test001/s3a(64,63) |     common/test001/s3a(64,63) | ||||||
|     save |     save | ||||||
| 
 | 
 | ||||||
|     if(first) then |     if(first .or. (nclearave.eq.1)) then | ||||||
|        iutc=-1 |        iutc=-1 | ||||||
|        nfsave=0 |        nfsave=0 | ||||||
|        dtdiff=0.2 |        dtdiff=0.2 | ||||||
|        first=.false. |        first=.false. | ||||||
|     endif |     endif | ||||||
|  |     nclearave=0 | ||||||
| 
 | 
 | ||||||
|     do i=1,64 |     do i=1,64 | ||||||
|        if(nutc.eq.iutc(i) .and. abs(nhz-nfsave(i)).le.ntol) go to 10 |        if(nutc.eq.iutc(i) .and. abs(nhz-nfsave(i)).le.ntol) go to 10 | ||||||
|  | |||||||
| @ -23,18 +23,21 @@ contains | |||||||
|     character(len=12), intent(in) :: mycall, hiscall |     character(len=12), intent(in) :: mycall, hiscall | ||||||
|     character(len=6), intent(in) :: hisgrid |     character(len=6), intent(in) :: hisgrid | ||||||
|     type(jt65_decoder) :: my_decoder |     type(jt65_decoder) :: my_decoder | ||||||
|  |     integer nclearave                          !### Should be a dummy arg? | ||||||
|  |     nclearave=0 | ||||||
| 
 | 
 | ||||||
|     call timer('jt65a   ',0) |     call timer('jt65a   ',0) | ||||||
|     call my_decoder%decode(my_callback,dd,npts=52*12000,newdat=.true.,nutc=nutc,nf1=nflow,nf2=nfhigh    & |     call my_decoder%decode(my_callback,dd,npts=52*12000,newdat=.true.,     & | ||||||
|          ,nfqso=nfqso,ntol=ntol,nsubmode=nsubmode, minsync=0,nagain=.false.     & |          nutc=nutc,nf1=nflow,nf2=nfhigh,nfqso=nfqso,ntol=ntol,             & | ||||||
|          ,n2pass=n2pass,nrobust=nrobust,ntrials=ntrials,naggressive=naggressive & |          nsubmode=nsubmode, minsync=0,nagain=.false.,n2pass=n2pass,        & | ||||||
|          ,ndepth=ndepth,mycall=mycall,hiscall=hiscall,hisgrid=hisgrid                & |          nrobust=nrobust,ntrials=ntrials,naggressive=naggressive,          & | ||||||
|          ,nexp_decode=nexp_decode) |          ndepth=ndepth,nclearave=nclearave,mycall=mycall,hiscall=hiscall,  & | ||||||
|  |          hisgrid=hisgrid,nexp_decode=nexp_decode) | ||||||
|     call timer('jt65a   ',1) |     call timer('jt65a   ',1) | ||||||
|   end subroutine test |   end subroutine test | ||||||
| 
 | 
 | ||||||
|   subroutine my_callback (this, utc, sync, snr, dt, freq, drift, decoded   & |   subroutine my_callback (this, utc, sync, snr, dt, freq, drift, decoded   & | ||||||
|        , ft, qual, candidates, tries, total_min, hard_min, aggression) |        , ft, qual) | ||||||
|     use jt65_decode |     use jt65_decode | ||||||
|     implicit none |     implicit none | ||||||
| 
 | 
 | ||||||
| @ -48,11 +51,6 @@ contains | |||||||
|     character(len=22), intent(in) :: decoded |     character(len=22), intent(in) :: decoded | ||||||
|     integer, intent(in) :: ft |     integer, intent(in) :: ft | ||||||
|     integer, intent(in) :: qual |     integer, intent(in) :: qual | ||||||
|     integer, intent(in) :: candidates |  | ||||||
|     integer, intent(in) :: tries |  | ||||||
|     integer, intent(in) :: total_min |  | ||||||
|     integer, intent(in) :: hard_min |  | ||||||
|     integer, intent(in) :: aggression |  | ||||||
| 
 | 
 | ||||||
|     write(*,1010) utc,snr,dt,freq,decoded |     write(*,1010) utc,snr,dt,freq,decoded | ||||||
| 1010 format(i4.4,i4,f5.1,i5,1x,'#',1x,a22) | 1010 format(i4.4,i4,f5.1,i5,1x,'#',1x,a22) | ||||||
|  | |||||||
		Loading…
	
	
			
			x
			
			
		
	
		Reference in New Issue
	
	Block a user