Ignore:
Timestamp:
Feb 18, 2021 12:08:41 PM (3 years ago)
Author:
suehring
Message:

Minor formatting adjustments and some comments added in get_variable_surf

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/netcdf_data_input_mod.f90

    r4878 r4880  
    2424! -----------------
    2525! $Id$
     26! Minor formatting adjustments and some comments added in get_variable_surf
     27!
     28! 4878 2021-02-18 09:47:49Z suehring
    2629! Rename resize_array into add_ghost_layers; remove number of passed indices; replace subroutine
    2730! calls with interface name
     
    41904193
    41914194    USE grid_variables,                                                                            &
    4192         ONLY: dx, dy
     4195        ONLY: ddx, ddy
    41934196
    41944197    USE basic_constants_and_equations_mod,                                                         &
     
    42024205    CHARACTER(LEN=*)                          ::  variable_name !< variable name
    42034206
    4204     INTEGER(iwp)                              ::  i, j
     4207    INTEGER(iwp)                              ::  i             !< grid index in x-direction
     4208    INTEGER(iwp)                              ::  j             !< grid index in y-direction
    42054209    INTEGER(iwp), INTENT(IN)                  ::  id            !< file id
    42064210    INTEGER(iwp)                              ::  id_azimuth    !< azimuth variable id
     
    42154219    INTEGER(iwp)                              ::  nsurf         !< total number of surfaces in file
    42164220
    4217     INTEGER(iwp), DIMENSION(6)                ::  coords        !< integer coordinates of surface
     4221    INTEGER(iwp), DIMENSION(6)                ::  coords        !< integer coordinates of surface location
    42184222    INTEGER(iwp), DIMENSION(2)                ::  id_dim        !< dimension ids
    42194223
     
    42244228    REAL(wp), DIMENSION(:), ALLOCATABLE       ::  azimuth       !< read buffer for azimuth(s)
    42254229    REAL(wp), DIMENSION(:), ALLOCATABLE       ::  zenith        !< read buffer for zenith(s)
    4226     REAL(wp), DIMENSION(:), ALLOCATABLE       ::  zs, ys, xs    !< read buffer for zs(s), ys, xs
    4227 
    4228     REAL(wp), DIMENSION(:,:), ALLOCATABLE     ::  pars_read     !< read buffer
     4230    REAL(wp), DIMENSION(:), ALLOCATABLE       ::  xs            !< surface coordinate array of x-dimension
     4231    REAL(wp), DIMENSION(:), ALLOCATABLE       ::  ys            !< surface coordinate array of y-dimension
     4232    REAL(wp), DIMENSION(:), ALLOCATABLE       ::  zs            !< surface coordinate array of z-dimension
     4233
     4234    REAL(wp), DIMENSION(:,:), ALLOCATABLE     ::  pars_read     !< read buffer for the building parameters
    42294235
    42304236    TYPE(pars_surf)                           ::  surf          !< parameters variable to be loaded
     
    42334239#if defined( __netcdf )
    42344240!
    4235 !-- First, inquire variable ID
     4241!-- First, inquire variable ID's
    42364242    nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
    42374243    nc_stat = NF90_INQ_VARID( id, 'zs',                  id_zs )
     
    42414247    nc_stat = NF90_INQ_VARID( id, 'azimuth',             id_azimuth )
    42424248!
    4243 !-- Inquire dimension sizes
     4249!-- Inquire dimension sizes for the number of surfaces and parameters given
    42444250    nc_stat = NF90_INQUIRE_VARIABLE( id, id_var, DIMIDS = id_dim )
    42454251    nc_stat = NF90_INQUIRE_DIMENSION( id, id_dim(1), LEN = nsurf )
     
    42504256              xs(nsurf_pars_read), zenith(nsurf_pars_read),                                        &
    42514257              azimuth(nsurf_pars_read),                                                            &
    4252               nsurf_ji(nys:nyn, nxl:nxr) )
     4258              nsurf_ji(nys:nyn,nxl:nxr) )
    42534259
    42544260    nsurf_ji(:,:) = 0
    42554261!
    4256 !-- Scan surface coordinates, count local
     4262!-- Scan surface coordinates, count locally
    42574263    is0 = 1
    42584264    DO
     
    42814287               coords(3) < nxl  .OR.  coords(3) > nxr )  CYCLE
    42824288
    4283           nsurf_ji(coords(2), coords(3)) = nsurf_ji(coords(2), coords(3)) + 1
     4289          nsurf_ji(coords(2),coords(3)) = nsurf_ji(coords(2),coords(3)) + 1
    42844290       ENDDO
    42854291       is0 = is0 + isc
     
    42874293!
    42884294!-- Populate reverse index from surface counts
    4289     ALLOCATE( surf%index_ji( 2, nys:nyn, nxl:nxr ) )
     4295    ALLOCATE( surf%index_ji( 2,nys:nyn,nxl:nxr ) )
    42904296    isurf = 1
    42914297    DO  j = nys, nyn
     
    42974303
    42984304    surf%nsurf = isurf - 1
    4299     ALLOCATE( surf%pars( 0:surf%np-1, surf%nsurf ), &
    4300               surf%coords( 6, surf%nsurf ) )
     4305    ALLOCATE( surf%pars(0:surf%np-1,surf%nsurf),                                                  &
     4306              surf%coords(6,surf%nsurf) )
    43014307!
    43024308!-- Scan surfaces again, saving pars into allocated structures
     
    43374343!--       Determine maximum terrain under building (base z-coordinate). Using normal vector to
    43384344!--       locate building inner coordinates.
    4339           oro_max_l = buildings_f%oro_max(coords(2)-coords(5), coords(3)-coords(6))
     4345          oro_max_l = buildings_f%oro_max(coords(2)-coords(5),coords(3)-coords(6))
    43404346          IF ( oro_max_l == buildings_f%fill1 )  THEN
    43414347             WRITE( message_string, * ) 'Found building surface on '   //                          &
     
    43514357!
    43524358!--       Save surface entry
    4353           is = surf%index_ji(1, coords(2), coords(3)) + nsurf_ji(coords(2), coords(3))
     4359          is = surf%index_ji(1,coords(2),coords(3)) + nsurf_ji(coords(2),coords(3))
    43544360          surf%pars(:,is) = pars_read(isurf,:)
    43554361          surf%coords(:,is) = coords(:)
    43564362
    4357           nsurf_ji(coords(2), coords(3)) = nsurf_ji(coords(2), coords(3)) + 1
     4363          nsurf_ji(coords(2),coords(3)) = nsurf_ji(coords(2),coords(3)) + 1
    43584364       ENDDO
    43594365
     
    43704376
    43714377       REAL(wp), INTENT(in) ::  azimuth  !< surface normal azimuth angle in degrees
    4372        REAL(wp), INTENT(in) ::  x, y     !< surface centre coordinates in metres from origin
     4378       REAL(wp), INTENT(in) ::  x        !< surface centre coordinate in x in metres from origin
     4379       REAL(wp), INTENT(in) ::  y        !< surface centre coordinate in y in metres from origin
    43734380       REAL(wp), INTENT(in) ::  zenith   !< surface normal zenith angle in degrees
    43744381
     
    43834390
    43844391       transform_coords(1) = -999.0_wp ! not calculated here
    4385        transform_coords(2) = NINT( y / dy - 0.5_wp + 0.5_wp * transform_coords(5), KIND=iwp )
    4386        transform_coords(3) = NINT( x / dx - 0.5_wp + 0.5_wp * transform_coords(6), KIND=iwp )
     4392       transform_coords(2) = NINT( y * ddy - 0.5_wp + 0.5_wp * transform_coords(5), KIND=iwp )
     4393       transform_coords(3) = NINT( x * ddx - 0.5_wp + 0.5_wp * transform_coords(6), KIND=iwp )
    43874394
    43884395    END FUNCTION transform_coords
Note: See TracChangeset for help on using the changeset viewer.