calc_imp_acf Subroutine

public subroutine calc_imp_acf(long, larg, tau1, tau2, alpha, ang, tab_acf, apod)

Note

Function that returns the theoretical autocorrelation function in an array.
The autocorrelation function is supposed to be obtained from a real surface which must be periodic or nearly periodic (because of the use of FFTs). In addition, the surface is supposed to be 0 mean and normalized (), therefore acf is zero-mean and normalized so that its max value is 1.

Arguments

Type IntentOptional Attributes Name
integer(kind=I4), intent(in) :: long

surface acf width

integer(kind=I4), intent(in) :: larg

surface acf height

real(kind=R8), intent(in) :: tau1

first correlation length

real(kind=R8), intent(in) :: tau2

surface second correlation length

real(kind=R8), intent(in) :: alpha

parameter that controls the expondential decrease

real(kind=R8), intent(in) :: ang

acf ellipsis angle

real(kind=R8), intent(out), dimension(1:long, 1:larg) :: tab_acf

resulting acf

logical(kind=I4), intent(in) :: apod

apodization?


Calls

proc~~calc_imp_acf~~CallsGraph proc~calc_imp_acf calc_imp_acf proc~apod2 apod2 proc~calc_imp_acf->proc~apod2 proc~autocov_impo autocov_impo proc~calc_imp_acf->proc~autocov_impo

Called by

proc~~calc_imp_acf~~CalledByGraph proc~calc_imp_acf calc_imp_acf proc~acf_theo acf_theo proc~acf_theo->proc~calc_imp_acf proc~sub_surf sub_surf proc~sub_surf->proc~calc_imp_acf proc~read_job read_job proc~read_job->proc~acf_theo proc~read_job->proc~sub_surf proc~prg_surf prg_surf proc~prg_surf->proc~read_job program~main main program~main->proc~prg_surf

Source Code

   subroutine calc_imp_acf(long, larg, tau1, tau2, alpha, ang, tab_acf, apod)
   !================================================================================================
   !<@note Function that returns the theoretical autocorrelation function in an array.<br/>
   !< The autocorrelation function is supposed to be obtained from a real surface which must be periodic
   !< or nearly periodic (because of the use of FFTs).
   !< In addition, the surface is supposed to be 0 mean and normalized (\(\sigma = 1 \)),
   !< therefore *acf* is zero-mean and normalized so that its max value is 1.<br/>
   !<
   !<@endnote
   !------------------------------------------------------------------------------------------------
   implicit none
   integer(kind=I4), intent(in) :: long   !! *surface acf width*
   integer(kind=I4), intent(in) :: larg   !! *surface acf height*
   logical(kind=I4), intent(in) :: apod   !! *apodization?*
   real   (kind=R8), intent(in) :: tau1   !! *first correlation length*
   real   (kind=R8), intent(in) :: tau2   !! *surface second correlation length*
   real   (kind=R8), intent(in) :: alpha  !! *parameter that controls the expondential decrease*
   real   (kind=R8), intent(in) :: ang    !! *acf ellipsis angle*
   real   (kind=R8), dimension(1:long, 1:larg), intent(out) :: tab_acf  !! *resulting acf*

      integer(kind=I4) :: i, j, long2, larg2
      real   (kind=R8) :: xi, xj, s, c, coeff

      real(kind=R8), dimension(:,:), allocatable:: tab_tmp

      ! acf array, centered and normalized
      !.........................................
      c = cos(ang) ; s = sin(ang)

      long2 = long / 2
      larg2 = larg / 2

      if ( long == 2 * (long/2) ) long2 = long/2 + 1
      if ( larg == 2 * (larg/2) ) larg2 = larg/2 + 1

      do j = 1, larg
      do i = 1, long

         xi = real(i - long2, kind=R8) * PARAM%surf_dx      ! dimensioned coordinate x
         xj = real(j - larg2, kind=R8) * PARAM%surf_dy      ! dimensioned coordinate y

         tab_acf(i, j) = autocov_impo( xi    = xi,       &  ! IN
                                       xj    = xj,       &  ! IN
                                       tau1  = tau1,     &  ! IN
                                       tau2  = tau2,     &  ! IN
                                       alpha = alpha,    &  ! IN
                                       ang   = ang )        ! IN

      enddo
      enddo
      !.........................................


      ! For long correlation lengths and roughness orientation, the acf is far from periodic
      ! Furthermore, far from the center, respecting the acf becomes less important. A windowing
      ! can be determined so that at a given distance from the center, the acf is lessened.
      !.........................................
      if ( apod ) then

         allocate( tab_tmp(1:long, 1:larg) )

         coeff = 0.4 * PARAM%surf_width * c / tau1

         ! along the primary axis (longest correlation length) the acf is reduce beyond
         ! 0.4 * image width * cos(ang)
         ! (0.4 * image width is less than half width)

         call apod2(  tab_in = tab_acf(1:long, 1:larg),     &  ! IN
                     tab_out = tab_tmp(1:long, 1:larg),     &  ! OUT
                        long = long,                        &  ! IN
                        larg = larg,                        &  ! IN
                        tau1 = coeff * tau1 ,               &  ! IN
                        tau2 = coeff * tau2 ,               &  ! IN
                         ang = ang )                           ! IN

         tab_acf(1:long, 1:larg) = tab_tmp(1:long, 1:larg)

         deallocate( tab_tmp )

      endif
      !.........................................

      ! acf centered
      tab_acf(1:long, 1:larg) = tab_acf(1:long, 1:larg) - sum( tab_acf(1:long, 1:larg) ) / (long * larg)

      ! acf scaled (maximum = 1)
      tab_acf(1:long, 1:larg) = tab_acf(1:long, 1:larg) / tab_acf(long2, larg2)

   return
   endsubroutine calc_imp_acf