2017-06-18 08:26:41 -04:00
|
|
|
module ft8_decode
|
|
|
|
|
|
|
|
type :: ft8_decoder
|
|
|
|
procedure(ft8_decode_callback), pointer :: callback
|
|
|
|
contains
|
|
|
|
procedure :: decode
|
|
|
|
end type ft8_decoder
|
|
|
|
|
|
|
|
abstract interface
|
|
|
|
subroutine ft8_decode_callback (this, sync, snr, dt, freq, drift, &
|
|
|
|
decoded)
|
|
|
|
import ft8_decoder
|
|
|
|
implicit none
|
|
|
|
class(ft8_decoder), intent(inout) :: this
|
|
|
|
real, intent(in) :: sync
|
|
|
|
integer, intent(in) :: snr
|
|
|
|
real, intent(in) :: dt
|
|
|
|
real, intent(in) :: freq
|
|
|
|
integer, intent(in) :: drift
|
|
|
|
character(len=22), intent(in) :: decoded
|
|
|
|
end subroutine ft8_decode_callback
|
|
|
|
end interface
|
|
|
|
|
|
|
|
contains
|
|
|
|
|
2017-06-19 16:15:43 -04:00
|
|
|
subroutine decode(this,callback,ss,iwave,nfqso,newdat,npts8,nfa, &
|
2017-06-18 08:26:41 -04:00
|
|
|
nfsplit,nfb,ntol,nzhsym,nagain,ndepth,nmode,nsubmode,nexp_decode)
|
|
|
|
use timer_module, only: timer
|
|
|
|
|
2017-06-19 16:15:43 -04:00
|
|
|
! include 'constants.f90'
|
|
|
|
include 'fsk4hf/ft8_params.f90'
|
|
|
|
|
2017-06-18 08:26:41 -04:00
|
|
|
class(ft8_decoder), intent(inout) :: this
|
|
|
|
procedure(ft8_decode_callback) :: callback
|
2017-06-19 16:15:43 -04:00
|
|
|
real ss(1,1) !### dummy, to be removed ###
|
|
|
|
real s(NH1,NHSYM)
|
|
|
|
real candidate(3,100)
|
2017-06-18 08:26:41 -04:00
|
|
|
logical, intent(in) :: newdat, nagain
|
2017-06-19 16:15:43 -04:00
|
|
|
integer*2 iwave(15*12000)
|
|
|
|
character*13 datetime
|
|
|
|
|
|
|
|
datetime="000000_000000" !### TEMPORARY ###
|
2017-06-18 08:26:41 -04:00
|
|
|
|
2017-06-19 16:15:43 -04:00
|
|
|
call sync8(iwave,s,candidate,ncand)
|
|
|
|
call ft8b(datetime,s,candidate,ncand)
|
|
|
|
! if (associated(this%callback)) then
|
|
|
|
! call this%callback(sync,nsnr,xdt,freq,ndrift,msg)
|
|
|
|
! end if
|
|
|
|
|
2017-06-18 08:26:41 -04:00
|
|
|
return
|
|
|
|
end subroutine decode
|
2017-06-19 16:15:43 -04:00
|
|
|
|
2017-06-18 08:26:41 -04:00
|
|
|
end module ft8_decode
|