Ignore:
Timestamp:
Aug 16, 2019 1:50:17 PM (5 years ago)
Author:
suehring
Message:

Replace get_topography_top_index functions by pre-calculated arrays in order to save computational resources

File:
1 edited

Legend:

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

    r4159 r4168  
    2626! -----------------
    2727! $Id$
     28! Remove functions get_topography_top_index. These are now replaced by
     29! precalculated arrays because of too much CPU-time consumption
     30!
     31! 4159 2019-08-15 13:31:35Z suehring
    2832! Surface classification revised and adjusted to changes in init_grid
    2933!
     
    646650
    647651    PRIVATE
    648 
     652   
    649653    INTERFACE init_bc
    650654       MODULE PROCEDURE init_bc
     
    698702!
    699703!-- Public subroutines and functions
    700     PUBLIC get_topography_top_index,                                                               &
    701            get_topography_top_index_ji,                                                            &
    702            init_bc,                                                                                &
     704    PUBLIC init_bc,                                                                                &
    703705           init_single_surface_properties,                                                         &
    704706           init_surfaces,                                                                          &
     
    710712
    711713#if defined( _OPENACC )
    712     PUBLIC enter_surface_arrays, exit_surface_arrays
     714    PUBLIC enter_surface_arrays,                                                                   &
     715           exit_surface_arrays
    713716#endif
    714717
     
    31413144       
    31423145    END SUBROUTINE init_single_surface_properties
    3143 
    3144 !------------------------------------------------------------------------------!
    3145 ! Description:
    3146 ! ------------
    3147 !> Determines topography-top index at given (j,i)-position. 
    3148 !------------------------------------------------------------------------------!
    3149     FUNCTION get_topography_top_index_ji( j, i, grid )
    3150 
    3151        IMPLICIT NONE
    3152 
    3153        CHARACTER(LEN=*) ::  grid                         !< flag to distinquish between staggered grids
    3154        INTEGER(iwp)     ::  i                            !< grid index in x-dimension
    3155        INTEGER(iwp)     ::  ibit                         !< bit position where topography information is stored on respective grid
    3156        INTEGER(iwp)     ::  j                            !< grid index in y-dimension
    3157        INTEGER(iwp)     ::  get_topography_top_index_ji  !< topography top index
    3158 
    3159        SELECT CASE ( TRIM( grid ) )
    3160 
    3161           CASE ( 's'     )
    3162              ibit = 12
    3163           CASE ( 'u'     )
    3164              ibit = 14
    3165           CASE ( 'v'     )
    3166              ibit = 16
    3167           CASE ( 'w'     )
    3168              ibit = 18
    3169           CASE ( 's_out' )
    3170              ibit = 24
    3171           CASE DEFAULT
    3172 !
    3173 !--          Set default to scalar grid
    3174              ibit = 12
    3175 
    3176        END SELECT
    3177 
    3178        get_topography_top_index_ji = MAXLOC(                                   &
    3179                                      MERGE( 1, 0,                              &
    3180                                             BTEST( wall_flags_0(:,j,i), ibit ) &
    3181                                           ), DIM = 1                           &
    3182                                            ) - 1
    3183 
    3184        RETURN
    3185 
    3186     END FUNCTION get_topography_top_index_ji
    3187 
    3188 !------------------------------------------------------------------------------!
    3189 ! Description:
    3190 ! ------------
    3191 !> Determines topography-top index at each (j,i)-position. 
    3192 !------------------------------------------------------------------------------!
    3193     FUNCTION get_topography_top_index( grid )
    3194 
    3195        IMPLICIT NONE
    3196 
    3197        CHARACTER(LEN=*) ::  grid                      !< flag to distinquish between staggered grids
    3198        INTEGER(iwp)     ::  ibit                      !< bit position where topography information is stored on respective grid
    3199        INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  get_topography_top_index  !< topography top index
    3200 
    3201        SELECT CASE ( TRIM( grid ) )
    3202 
    3203           CASE ( 's'     )
    3204              ibit = 12
    3205           CASE ( 'u'     )
    3206              ibit = 14
    3207           CASE ( 'v'     )
    3208              ibit = 16
    3209           CASE ( 'w'     )
    3210              ibit = 18
    3211           CASE ( 's_out' )
    3212              ibit = 24
    3213           CASE DEFAULT
    3214 !
    3215 !--          Set default to scalar grid
    3216              ibit = 12
    3217 
    3218        END SELECT
    3219 
    3220        get_topography_top_index(nys:nyn,nxl:nxr) = MAXLOC(                     &
    3221                          MERGE( 1, 0,                                          &
    3222                                  BTEST( wall_flags_0(:,nys:nyn,nxl:nxr), ibit )&
    3223                               ), DIM = 1                                       &
    3224                                                          ) - 1
    3225 
    3226        RETURN
    3227 
    3228     END FUNCTION get_topography_top_index
    32293146
    32303147!------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.