test_asfc Program

Uses

  • program~~test_asfc~~UsesGraph program~test_asfc test_asfc data_arch data_arch program~test_asfc->data_arch files files program~test_asfc->files miscellaneous miscellaneous program~test_asfc->miscellaneous module~asfc asfc program~test_asfc->module~asfc surfile surfile program~test_asfc->surfile module~asfc->data_arch module~asfc->miscellaneous module~asfc->surfile bspline bspline module~asfc->bspline least_squares least_squares module~asfc->least_squares minpack minpack module~asfc->minpack module~stat_mom stat_mom module~asfc->module~stat_mom module~stat_mom->data_arch sort_arrays sort_arrays module~stat_mom->sort_arrays

Asfc. Example of use


Calls

program~~test_asfc~~CallsGraph program~test_asfc test_asfc clean_scratch clean_scratch program~test_asfc->clean_scratch list_files list_files program~test_asfc->list_files proc~calcul_asfc_hermite calcul_asfc_hermite program~test_asfc->proc~calcul_asfc_hermite proc~indice_fractal indice_fractal program~test_asfc->proc~indice_fractal read_surf read_surf program~test_asfc->read_surf get_unit get_unit proc~calcul_asfc_hermite->get_unit lmder1 lmder1 proc~calcul_asfc_hermite->lmder1 omp_get_num_procs omp_get_num_procs proc~calcul_asfc_hermite->omp_get_num_procs proc~df_boltz df_boltz proc~calcul_asfc_hermite->proc~df_boltz proc~dnq_et_i dnq_et_i proc~calcul_asfc_hermite->proc~dnq_et_i proc~dnq_xi_i dnq_xi_i proc~calcul_asfc_hermite->proc~dnq_xi_i proc~f_boltz f_boltz proc~calcul_asfc_hermite->proc~f_boltz proc~init_beta_boltz init_beta_boltz proc~calcul_asfc_hermite->proc~init_beta_boltz proc~locate locate proc~calcul_asfc_hermite->proc~locate proc~locate2 locate2 proc~calcul_asfc_hermite->proc~locate2 proc~nq_i nq_i proc~calcul_asfc_hermite->proc~nq_i moindres_carres_lineaire moindres_carres_lineaire proc~indice_fractal->moindres_carres_lineaire proc~calc_moments calc_moments proc~indice_fractal->proc~calc_moments proc~calc_moments_1d calc_moments_1D proc~calc_moments->proc~calc_moments_1d proc~dn_i dn_i proc~dnq_et_i->proc~dn_i proc~n_i n_i proc~dnq_et_i->proc~n_i proc~dnq_xi_i->proc~dn_i proc~dnq_xi_i->proc~n_i proc~nq_i->proc~n_i

Variables

Type Attributes Name Initial
integer(kind=I4) :: i_g
real(kind=R8), dimension(1:3) :: ind_frac

result: indice fractal

character(len=512), allocatable, dimension(:) :: list_sur
character(len=512), allocatable, dimension(:) :: list_sur1
character(len=512), allocatable, dimension(:) :: list_sur2
integer(kind=I4) :: n1_g
integer(kind=I4) :: n2_g
integer(kind=I4) :: n_g
integer(kind=I4) :: nx
integer(kind=I4) :: ny
real(kind=R8), dimension(1:2) :: res_asfc

result: asfc, adjustment factor

type(SCALE_SURF) :: scal_surf

object SCALE_SURF

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

height array


Source Code

program test_asfc
use data_arch,     only : I4, R8
use miscellaneous, only : get_unit
use surfile,       only : read_surf, SCALE_SURF
use asfc,          only : calcul_asfc_hermite, indice_fractal
use files,         only : list_files, clean_scratch
implicit none

   type(SCALE_SURF) :: scal_surf                           !! *object [[SCALE_SURF]]*

   real(kind=R8), dimension(:,:), allocatable :: tab_surf  !! *height array*
   real(kind=R8), dimension(1:2)              :: res_asfc  !! *result: asfc, adjustment factor*
   real(kind=R8), dimension(1:3)              :: ind_frac  !! *result: indice fractal*

   character(len = 512), allocatable, dimension(:) :: list_sur
   character(len = 512), allocatable, dimension(:) :: list_sur1
   character(len = 512), allocatable, dimension(:) :: list_sur2

   integer(kind = I4) :: i_g, n_g, n1_g, n2_g, nx, ny

   call clean_scratch()

   call list_files(dir = "sur", list = list_sur1, ext = "sur")
   call list_files(dir = "sur", list = list_sur2, ext = "SUR")

   n1_g = ubound( list_sur1, 1 )
   n2_g = ubound( list_sur2, 1 )

   n_g  = n1_g + n2_g

   allocate( list_sur(1:n_g) )

   list_sur(       1:n1_g) = list_sur1(1:n1_g)
   list_sur(n1_g + 1:n_g ) = list_sur2(1:n2_g)

   do i_g = 1, n_g

      write(*,*) '==============================================='
      write(*,*) trim( list_sur(i_g) )

      call read_surf(nom_fic = trim( list_sur(i_g) ), &  ! IN
                          mu =  0._R8,                &  ! IN , OPT
                       tab_s = tab_surf,              &  ! OUT
                        scal = scal_surf)                ! OUT

      nx = scal_surf%xres
      ny = scal_surf%yres

      call calcul_asfc_hermite(tab_in = tab_surf,     &  !
                                 scal = scal_surf,    &  !
                             asfc_res = res_asfc,     &  !
                                  omp = .true.)          !

      call indice_fractal( tab_in = tab_surf(1:nx, 1:ny),   &  !
                           long   = nx,                     &  !
                           larg   = ny,                     &  !
                           indf   = ind_frac(1:3) )            !

      write(*,*) 'Asfc2 (asfc2 + correlation):             ', res_asfc(1:2)
      write(*,*) 'Box counting (frac. ind. + correlation): ', ind_frac(1), ind_frac(3)

   enddo

   deallocate( list_sur, list_sur1, list_sur2 )

endprogram test_asfc