Changeset 3636


Ignore:
Timestamp:
Dec 19, 2018 1:48:34 PM (5 years ago)
Author:
raasch
Message:

nopointer option removed

Location:
palm/trunk/SOURCE
Files:
19 edited

Legend:

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

    r2718 r3636  
    2525! -----------------
    2626! $Id$
     27! nopointer option removed
     28!
     29! 2718 2018-01-02 08:49:38Z maronga
    2730! Corrected "Former revisions" section
    2831!
     
    205208       REAL(wp) ::  fmax_l(2) !<
    206209       
    207 #if defined( __nopointer )
    208        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !<
    209 #else
    210210       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk
    211 #endif
    212211
    213212       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  a0   !<
  • palm/trunk/SOURCE/advec_s_pw.f90

    r3547 r3636  
    2525! -----------------
    2626! $Id$
     27! nopointer option removed
     28!
     29! 3547 2018-11-21 13:21:24Z suehring
    2730! variables documented
    2831!
     
    136139       REAL(wp)     ::  gv  !< local additional advective velocity
    137140
    138 #if defined( __nopointer )
    139        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !<
    140 #else
    141141       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk
    142 #endif
    143142 
    144143
     
    207206       REAL(wp)     ::  gv  !< local additional advective velocity
    208207
    209 #if defined( __nopointer )
    210        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !<
    211 #else
    212208       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk
    213 #endif
    214209
    215210
  • palm/trunk/SOURCE/advec_s_up.f90

    r3547 r3636  
    2525! -----------------
    2626! $Id$
     27! nopointer option removed
     28!
     29! 3547 2018-11-21 13:21:24Z suehring
    2730! variables documented
    2831!
     
    133136       REAL(wp) ::  vkomp !< advection velocity along y-direction
    134137       REAL(wp) ::  wkomp !< advection velocity along z-direction
    135 #if defined( __nopointer )
    136        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !< treated scalar
    137 #else
     138
    138139       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk !< treated scalar
    139 #endif
    140140
    141141
     
    213213       REAL(wp) ::  wkomp !< advection velocity along z-direction
    214214       
    215 #if defined( __nopointer )
    216        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk !< treated scalar
    217 #else
    218215       REAL(wp), DIMENSION(:,:,:), POINTER ::  sk !< treated scalar
    219 #endif
    220216
    221217
  • palm/trunk/SOURCE/bulk_cloud_model_mod.f90

    r3622 r3636  
    2525! -----------------
    2626! $Id$
     27! nopointer option removed
     28!
     29! 3622 2018-12-12 09:52:53Z schwenkel
    2730! Important bugfix in case of restart runs.
    2831!
     
    185188
    186189    USE arrays_3d,                                                             &
    187 #if defined (__nopointer)
    188         ONLY:  ddzu, diss, dzu, dzw, hyp, hyrho,                               &
    189                nc,                   nc_p, nr,                   nr_p,         &
    190                precipitation_amount, prr, pt, d_exner, pt_init, q, ql,         &
    191                qc,                   qc_p, qr,                   qr_p,         &
    192                exner, zu, tnc_m, tnr_m, tqc_m, tqr_m
    193 #else
    194190        ONLY:  ddzu, diss, dzu, dzw, hyp, hyrho,                               &
    195191               nc, nc_1, nc_2, nc_3, nc_p, nr, nr_1, nr_2, nr_3, nr_p,         &
     
    197193               qc, qc_1, qc_2, qc_3, qc_p, qr, qr_1, qr_2, qr_3, qr_p,         &
    198194               exner, zu, tnc_m, tnr_m, tqc_m, tqr_m
    199 #endif
    200195
    201196    USE averaging,                                                             &
     
    824819       INTEGER(iwp) ::  k !<
    825820!
    826 !--          Liquid water content
    827 #if defined( __nopointer )
    828        ALLOCATE ( ql(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    829 #else
     821!--    Liquid water content
    830822       ALLOCATE ( ql_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    831 #endif
    832823
    833824!
    834825!--    3D-cloud water content
    835826       IF ( .NOT. microphysics_morrison )  THEN
    836 #if defined( __nopointer )
    837           ALLOCATE( qc(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    838 #else
    839827          ALLOCATE( qc_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    840 #endif
    841828       ENDIF
    842829!
     
    851838!
    852839!--       3D-cloud drop water content, cloud drop concentration arrays
    853 #if defined( __nopointer )
    854           ALLOCATE( nc(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                      &
    855                     nc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                    &
    856                     qc(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                      &
    857                     qc_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                    &
    858                     tnc_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                   &
    859                     tqc_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    860 #else
    861840          ALLOCATE( nc_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                    &
    862841                    nc_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                    &
     
    865844                    qc_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                    &
    866845                    qc_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    867 #endif
    868846       ENDIF
    869847
     
    871849!
    872850!--       3D-rain water content, rain drop concentration arrays
    873 #if defined( __nopointer )
    874           ALLOCATE( nr(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                      &
    875                     nr_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                    &
    876                     qr(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                      &
    877                     qr_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                    &
    878                     tnr_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                   &
    879                     tqr_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    880 #else
    881851          ALLOCATE( nr_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                    &
    882852                    nr_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                    &
     
    885855                    qr_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                    &
    886856                    qr_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    887 #endif
    888857       ENDIF
    889858
    890 #if ! defined( __nopointer )
    891859!
    892860!--    Initial assignment of the pointers
     
    903871          nr => nr_1;  nr_p  => nr_2;  tnr_m  => nr_3
    904872       ENDIF
    905 #endif
    906873
    907874
     
    1032999       IF ( bulk_cloud_model )  THEN
    10331000
    1034 #if defined( __nopointer )
    1035           IF ( microphysics_morrison )  THEN
    1036              qc = qc_p
    1037              nc = nc_p
    1038           ENDIF
    1039           IF ( microphysics_seifert )  THEN
    1040              qr = qr_p
    1041              nr = nr_p
    1042           ENDIF
    1043 #else
    10441001          SELECT CASE ( mod_count )
    10451002
     
    10671024
    10681025          END SELECT
    1069 #endif
    10701026
    10711027       ENDIF
  • palm/trunk/SOURCE/buoyancy.f90

    r3634 r3636  
    2525! -----------------
    2626! $Id$
     27! nopointer option removed
     28!
     29! 3634 2018-12-18 12:31:28Z knoop
    2730! OpenACC port for SPEC
    2831!
     
    168171       INTEGER(iwp) ::  wind_component !<
    169172       
    170 #if defined( __nopointer )
    171        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var !<
    172 #else
    173173       REAL(wp), DIMENSION(:,:,:), POINTER ::  var
    174 #endif
    175174
    176175
     
    261260       INTEGER(iwp) ::  wind_component !<
    262261       
    263 #if defined( __nopointer )
    264        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var !<
    265 #else
    266262       REAL(wp), DIMENSION(:,:,:), POINTER ::  var
    267 #endif
    268263
    269264
  • palm/trunk/SOURCE/calc_mean_profile.f90

    r3241 r3636  
    2525! -----------------
    2626! $Id$
     27! nopointer option removed
     28!
     29! 3241 2018-09-12 15:02:00Z raasch
    2730! omp_get_thread_num now declared in openmp directive,
    2831! unused variable removed
     
    110113       INTEGER(iwp) ::  tn                 !<
    111114       
    112 #if defined( __nopointer )
    113        REAL(wp), DIMENSION(:,:,:) ::  var  !<
    114 #else
    115115       REAL(wp), DIMENSION(:,:,:), POINTER ::  var
    116 #endif
    117116
    118117!
  • palm/trunk/SOURCE/chem_modules.f90

    r3611 r3636  
    2727! -----------------
    2828! $Id$
     29! nopointer option removed
     30!
     31! 3611 2018-12-07 14:14:11Z banzhafs
    2932! Minor formatting
    3033!
     
    4346! Initial revision
    4447!
    45 !
    46 !
    47 !
    4848! Authors:
    4949! --------
     
    5656! Description:
    5757! ------------
    58 !> Definition of global palm-4u chemistry variables
    59 !> (Module written to define global palm-4u chemistry variables. basit 16Nov2017)
     58!> Definition of global PALM-4U chemistry variables
    6059!------------------------------------------------------------------------------!
    6160!
     
    115114    REAL(wp), DIMENSION(99,100)                       ::  cs_profile = 9999999.9_wp !< Namelist parameter: Chem conc for each spcs defined
    116115
    117 
    118 #if defined( __nopointer )
    119     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   ::  cs                        !< chem spcs
    120     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   ::  cs_p                      !< prognostic value of chem spc
    121     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   ::  tcs_m                     !< weighted tendency of cs for previous sub-timestep (Runge-Kutta)
    122 
    123 #else                                                               
    124116!
    125117!-- Use pointers cs, cs_p and tcs_m to point arrays cs_1, cs_2, and cs_3
     
    130122    REAL(wp), DIMENSION(:,:,:), POINTER               ::  cs_p                      !< pointer: prognostic value of sgs chem spcs
    131123    REAL(wp), DIMENSION(:,:,:), POINTER               ::  tcs_m                     !< pointer:
    132 
    133 #endif                                                                           
    134124 
    135125    CHARACTER (LEN=20)                ::  bc_cs_b             = 'dirichlet'         !< namelist parameter
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r3611 r3636  
    2222! Current revisions:
    2323! -----------------
    24 !
    25 !
     24! 
     25! 
    2626! Former revisions:
    2727! -----------------
    2828! $Id$
     29! nopointer option removed
     30!
     31! 3611 2018-12-07 14:14:11Z banzhafs
    2932! Minor formatting             
    3033!
     
    16741677
    16751678    IMPLICIT NONE
    1676 !-- local variables
     1679
     1680!
     1681!-- Local variables
    16771682    INTEGER(iwp) ::  i                 !< running index for for horiz numerical grid points
    16781683    INTEGER(iwp) ::  j                 !< running index for for horiz numerical grid points
    16791684    INTEGER(iwp) ::  lsp               !< running index for chem spcs
    16801685    INTEGER(iwp) ::  lpr_lev           !< running index for chem spcs profile level
    1681 !
    1682 !-- NOPOINTER version not implemented yet
    1683 ! #if defined( __nopointer )
    1684 !     message_string = 'The chemistry module only runs with POINTER version'
    1685 !     CALL message( 'chemistry_model_mod', 'CM0001', 1, 2, 0, 6, 0 )     
    1686 ! #endif
     1686
    16871687!
    16881688!-- Allocate memory for chemical species
     
    17031703
    17041704
    1705     DO lsp = 1, nspec
     1705    DO  lsp = 1, nspec
    17061706       chem_species(lsp)%name    = spc_names(lsp)
    17071707
  • palm/trunk/SOURCE/diffusion_s.f90

    r3634 r3636  
    2525! -----------------
    2626! $Id$
     27! nopointer option removed
     28!
     29! 3634 2018-12-18 12:31:28Z knoop
    2730! OpenACC port for SPEC
    2831!
     
    191194       REAL(wp), DIMENSION(1:surf_usm_v(3)%ns) ::  s_flux_usm_v_west  !< flux at west-facing vertical urban-type surfaces
    192195       REAL(wp), DIMENSION(1:surf_def_h(2)%ns) ::  s_flux_t           !< flux at model top
    193 #if defined( __nopointer )
    194        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  s  !< treated scalar
    195 #else
     196
    196197       REAL(wp), DIMENSION(:,:,:), POINTER ::  s  !< treated scalar
    197 #endif
     198
    198199
    199200       !$ACC PARALLEL LOOP COLLAPSE(2) PRIVATE(i, j, k, m) &
     
    522523       REAL(wp), DIMENSION(1:surf_usm_v(3)%ns) ::  s_flux_usm_v_west  !< flux at west-facing vertical urban-type surfaces
    523524       REAL(wp), DIMENSION(1:surf_def_h(2)%ns) ::  s_flux_t           !< flux at model top
    524 #if defined( __nopointer )
    525        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  s !< treated scalar
    526 #else
     525
    527526       REAL(wp), DIMENSION(:,:,:), POINTER ::  s  !< treated scalar
    528 #endif
    529527
    530528!
  • palm/trunk/SOURCE/init_3d_model.f90

    r3609 r3636  
    2525! -----------------
    2626! $Id$
     27! nopointer option removed
     28!
     29! 3609 2018-12-07 13:37:59Z suehring
    2730! Furhter correction in initialization of surfaces in cyclic-fill case
    2831!
     
    771774              tend(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    772775
    773 #if defined( __nopointer )
    774     ALLOCATE( pt(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                               &
    775               pt_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                             &
    776               u(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                                &
    777               u_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                              &
    778               v(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                                &
    779               v_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                              &
    780               w(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                                &
    781               w_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                              &
    782               tpt_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                            &
    783               tu_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                             &
    784               tv_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                             &
    785               tw_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    786 #else
    787776    ALLOCATE( pt_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                             &
    788777              pt_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                             &
     
    799788       ALLOCATE( pt_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    800789    ENDIF
    801 #endif
    802790
    803791!
     
    824812!
    825813!--    3D-humidity
    826 #if defined( __nopointer )
    827        ALLOCATE( q(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                             &
    828                  q_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                           &
    829                  tq_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                          &
    830                  vpt(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    831 #else
    832814       ALLOCATE( q_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                           &
    833815                 q_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                           &
    834816                 q_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                           &
    835817                 vpt_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    836 #endif
    837818
    838819       IF ( cloud_droplets )  THEN
    839820!
    840821!--       Liquid water content, change in liquid water content
    841 #if defined( __nopointer )
    842           ALLOCATE ( ql(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                        &
    843                      ql_c(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    844 #else
    845822          ALLOCATE ( ql_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                      &
    846823                     ql_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    847 #endif
    848824!
    849825!--       Real volume of particles (with weighting), volume of particles
     
    858834!
    859835!--    3D scalar arrays
    860 #if defined( __nopointer )
    861        ALLOCATE( s(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                             &
    862                  s_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                           &
    863                  ts_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    864 #else
    865836       ALLOCATE( s_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                           &
    866837                 s_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                           &
    867838                 s_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    868 #endif
     839
    869840    ENDIF
    870841
     
    10701041    ENDIF
    10711042
    1072 
    1073 #if ! defined( __nopointer )
    10741043!
    10751044!-- Initial assignment of the pointers
     
    10951064       s => s_1;  s_p => s_2;  ts_m => s_3
    10961065    ENDIF   
    1097 #endif
    10981066
    10991067!
  • palm/trunk/SOURCE/land_surface_model_mod.f90

    r3620 r3636  
    2525! -----------------
    2626! $Id$
     27! nopointer option removed
     28!
     29! 3620 2018-12-11 12:29:43Z moh.hefny
    2730! update the 3d rad_lw_out array
    2831!
     
    655658                                   zs_layer = 9999999.9_wp         !< soil layer depths (edge)
    656659                                 
    657 #if defined( __nopointer )
    658     TYPE(surf_type_lsm), TARGET  ::  t_soil_h,    & !< Soil temperature (K), horizontal surface elements
    659                                      t_soil_h_p,  & !< Prog. soil temperature (K), horizontal surface elements
    660                                      m_soil_h,    & !< Soil moisture (m3/m3), horizontal surface elements
    661                                      m_soil_h_p     !< Prog. soil moisture (m3/m3), horizontal surface elements
    662 
    663     TYPE(surf_type_lsm), DIMENSION(0:3), TARGET  ::  &
    664                                      t_soil_v,       & !< Soil temperature (K), vertical surface elements
    665                                      t_soil_v_p,     & !< Prog. soil temperature (K), vertical surface elements
    666                                      m_soil_v,       & !< Soil moisture (m3/m3), vertical surface elements
    667                                      m_soil_v_p        !< Prog. soil moisture (m3/m3), vertical surface elements
    668 
    669 #else
    670660    TYPE(surf_type_lsm), POINTER ::  t_soil_h,    & !< Soil temperature (K), horizontal surface elements
    671661                                     t_soil_h_p,  & !< Prog. soil temperature (K), horizontal surface elements
     
    689679                                     m_soil_v_1,  & !<
    690680                                     m_soil_v_2     !<
    691 #endif   
    692 
    693 #if defined( __nopointer )
    694     TYPE(surf_type_lsm), TARGET   ::  t_surface_h,    & !< surface temperature (K), horizontal surface elements
    695                                       t_surface_h_p,  & !< progn. surface temperature (K), horizontal surface elements
    696                                       m_liq_h,        & !< liquid water reservoir (m), horizontal surface elements
    697                                       m_liq_h_p         !< progn. liquid water reservoir (m), horizontal surface elements
    698 
    699     TYPE(surf_type_lsm), DIMENSION(0:3), TARGET   ::  &
    700                                       t_surface_v,    & !< surface temperature (K), vertical surface elements
    701                                       t_surface_v_p,  & !< progn. surface temperature (K), vertical surface elements
    702                                       m_liq_v,        & !< liquid water reservoir (m), vertical surface elements
    703                                       m_liq_v_p         !< progn. liquid water reservoir (m), vertical surface elements
    704 #else
     681
    705682    TYPE(surf_type_lsm), POINTER  ::  t_surface_h,    & !< surface temperature (K), horizontal surface elements
    706683                                      t_surface_h_p,  & !< progn. surface temperature (K), horizontal surface elements
     
    724701                                      m_liq_v_1,      & !<
    725702                                      m_liq_v_2         !<
    726 #endif
    727 
    728 #if defined( __nopointer )
     703
    729704    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET :: m_liq_av
    730 #else
    731     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET :: m_liq_av
    732 #endif
    733 
    734 #if defined( __nopointer )
     705
    735706    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  t_soil_av, & !< Average of t_soil
    736707                                                        m_soil_av    !< Average of m_soil
    737 #else
    738     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  t_soil_av, & !< Average of t_soil
    739                                                         m_soil_av    !< Average of m_soil
    740 #endif
    741708
    742709    TYPE(surf_type_lsm), TARGET ::  tm_liq_h_m      !< liquid water reservoir tendency (m), horizontal surface elements
     
    48224789!--    even if they do not belong to the data type due to the
    48234790!--    pointer arithmetric (TARGET attribute is not allowed in a data-type).
    4824 #if defined( __nopointer )
    4825 !
    4826 !--    Horizontal surfaces
    4827        ALLOCATE ( m_liq_h_p%var_1d(1:surf_lsm_h%ns)                      )
    4828        ALLOCATE ( t_surface_h%var_1d(1:surf_lsm_h%ns)                    )
    4829        ALLOCATE ( t_surface_h_p%var_1d(1:surf_lsm_h%ns)                  )
    4830        ALLOCATE ( m_soil_h_p%var_2d(nzb_soil:nzt_soil,1:surf_lsm_h%ns)   )
    4831        ALLOCATE ( t_soil_h_p%var_2d(nzb_soil:nzt_soil+1,1:surf_lsm_h%ns) )
    4832 
    4833 !
    4834 !--    Vertical surfaces
    4835        DO  l = 0, 3
    4836           ALLOCATE ( m_liq_v(l)%var_1d(1:surf_lsm_v(l)%ns)                        )
    4837           ALLOCATE ( m_liq_v_p(l)%var_1d(1:surf_lsm_v(l)%ns)                      )
    4838           ALLOCATE ( t_surface_v(l)%var_1d(1:surf_lsm_v(l)%ns)                    )
    4839           ALLOCATE ( t_surface_v_p(l)%var_1d(1:surf_lsm_v(l)%ns)                  )
    4840           ALLOCATE ( m_soil_v(l)%var_2d(nzb_soil:nzt_soil,1:surf_lsm_v(l)%ns)     )
    4841           ALLOCATE ( m_soil_v_p(l)%var_2d(nzb_soil:nzt_soil,1:surf_lsm_v(l)%ns)   )
    4842           ALLOCATE ( t_soil_v(l)%var_2d(nzb_soil:nzt_soil+1,1:surf_lsm_v(l)%ns)   )
    4843           ALLOCATE ( t_soil_v_p(l)%var_2d(nzb_soil:nzt_soil+1,1:surf_lsm_v(l)%ns) )
    4844        ENDDO
    4845 !
    4846 !--    Allocate soil temperature and moisture. As these variables might be
    4847 !--    already allocated in case of restarts, check this.
    4848        IF ( .NOT. ALLOCATED( m_liq_h%var_1d ) )                                &
    4849           ALLOCATE ( m_liq_h%var_1d(1:surf_lsm_h%ns) )
    4850        IF ( .NOT. ALLOCATED( m_soil_h%var_2d ) )                               &
    4851           ALLOCATE ( m_soil_h%var_2d(nzb_soil:nzt_soil,1:surf_lsm_h%ns) )
    4852        IF ( .NOT. ALLOCATED( t_soil_h%var_2d ) )                               &
    4853           ALLOCATE ( t_soil_h%var_2d(nzb_soil:nzt_soil,1:surf_lsm_h%ns) )
    4854 
    4855        DO  l = 0, 3
    4856           IF ( .NOT. ALLOCATED( m_liq_v(l)%var_1d ) )                          &
    4857              ALLOCATE ( m_liq_v(l)%var_1d(1:surf_lsm_v(l)%ns) )
    4858           IF ( .NOT. ALLOCATED( m_soil_v(l)%var_2d ) )                         &
    4859              ALLOCATE ( m_soil_v(l)%var_2d(nzb_soil:nzt_soil,1:surf_lsm_v(l)%ns) )
    4860           IF ( .NOT. ALLOCATED( t_soil_v(l)%var_2d ) )                         &
    4861              ALLOCATE ( t_soil_v(l)%var_2d(nzb_soil:nzt_soil,1:surf_lsm_v(l)%ns) )
    4862        ENDDO
    4863 #else
    48644791!
    48654792!--    Horizontal surfaces
     
    48844811          ALLOCATE ( t_soil_v_2(l)%var_2d(nzb_soil:nzt_soil+1,1:surf_lsm_v(l)%ns) )
    48854812       ENDDO
    4886 #endif
     4813
    48874814!
    48884815!--    Allocate array for heat flux in W/m2, required for radiation?
     
    49864913       ENDDO
    49874914
    4988    
    4989 #if ! defined( __nopointer )
    49904915!
    49914916!--    Initial assignment of the pointers
     
    50014926       m_soil_v    => m_soil_v_1;    m_soil_v_p    => m_soil_v_2
    50024927       m_liq_v     => m_liq_v_1;     m_liq_v_p     => m_liq_v_2
    5003 
    5004 #endif
    50054928
    50064929
     
    54775400       INTEGER, INTENT(IN) :: mod_count
    54785401
    5479 #if defined( __nopointer )
    5480 !
    5481 !--    Horizontal surfaces
    5482        t_surface_h  = t_surface_h_p
    5483        t_soil_h     = t_soil_h_p
    5484        IF ( humidity )  THEN
    5485           m_soil_h    = m_soil_h_p
    5486           m_liq_h  = m_liq_h_p
    5487        ENDIF
    5488 !
    5489 !--    Vertical surfaces
    5490        t_surface_v  = t_surface_v_p
    5491        t_soil_v     = t_soil_v_p
    5492        IF ( humidity )  THEN
    5493           m_soil_v    = m_soil_v_p
    5494           m_liq_v  = m_liq_v_p
    5495        ENDIF
    5496 
    5497 #else
    54985402   
    54995403       SELECT CASE ( mod_count )
     
    55415445
    55425446       END SELECT
    5543 #endif
    55445447
    55455448    END SUBROUTINE lsm_swap_timelevel
  • palm/trunk/SOURCE/modules.f90

    r3597 r3636  
    2525! -----------------
    2626! $Id$
     27! nopointer option removed
     28!
     29! 3597 2018-12-04 08:40:18Z maronga
    2730! Added flag parameter do_output_at_2m for automatic output of 2m-temperature
    2831!
     
    882885    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_s       !< velocity data (w at south boundary) from time level t-dt required for radiation boundary condition
    883886
    884 #if defined( __nopointer )
    885     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss       !< TKE dissipation
    886     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss_p     !< prognostic value TKE dissipation
    887     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  e          !< subgrid-scale turbulence kinetic energy (sgs tke)
    888     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  e_p        !< prognostic value of sgs tke
    889     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nc         !< cloud drop number density
    890     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nc_p       !< prognostic value of cloud drop number density
    891     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nr         !< rain drop number density
    892     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nr_p       !< prognostic value of rain drop number density
    893     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  p          !< perturbation pressure
    894     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  prho       !< potential density
    895     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pt         !< potential temperature
    896     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pt_p       !< prognostic value of potential temperature
    897     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  q          !< mixing ratio 
    898                                                                    !< (or total water content with active cloud physics)
    899     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  q_p        !< prognostic value of mixing ratio
    900     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qc         !< cloud water content
    901     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qc_p       !< cloud water content
    902     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql         !< liquid water content
    903     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_c       !< change in liquid water content due to
    904                                                                    !< condensation/evaporation during last time step
    905     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_v       !< volume of liquid water
    906     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_vp      !< liquid water weighting factor
    907     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qr         !< rain water content
    908     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qr_p       !< prognostic value of rain water content
    909     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  rho_ocean  !< density of ocean
    910     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s          !< passive scalar
    911     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_p        !< prognostic value of passive scalar
    912     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  sa         !< ocean salinity
    913     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  sa_p       !< prognostic value of ocean salinity
    914     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  tdiss_m    !< weighted tendency of diss for previous sub-timestep (Runge-Kutta)
    915     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  te_m       !< weighted tendency of e for previous sub-timestep (Runge-Kutta)
    916     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  tnc_m      !< weighted tendency of nc for previous sub-timestep (Runge-Kutta)
    917     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  tnr_m      !< weighted tendency of nr for previous sub-timestep (Runge-Kutta)
    918     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  tpt_m      !< weighted tendency of pt for previous sub-timestep (Runge-Kutta)
    919     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  tq_m       !< weighted tendency of q for previous sub-timestep (Runge-Kutta)
    920     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  tqc_m      !< weighted tendency of qc for previous sub-timestep (Runge-Kutta)
    921     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  tqr_m      !< weighted tendency of qr for previous sub-timestep (Runge-Kutta)
    922     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ts_m       !< weighted tendency of s for previous sub-timestep (Runge-Kutta)
    923     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  tsa_m      !< weighted tendency of sa for previous sub-timestep (Runge-Kutta)
    924     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  tu_m       !< weighted tendency of u for previous sub-timestep (Runge-Kutta)
    925     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  tv_m       !< weighted tendency of v for previous sub-timestep (Runge-Kutta)
    926     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  tw_m       !< weighted tendency of w for previous sub-timestep (Runge-Kutta)
    927     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  u          !< horizontal velocity component u (x-direction)
    928     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  u_p        !< prognostic value of u
    929     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  v          !< horizontal velocity component v (y-direction)
    930     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  v_p        !< prognostic value of v
    931     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  vpt        !< virtual potential temperature
    932     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  w          !< vertical velocity component w (z-direction)
    933     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  w_p        !< prognostic value of w
    934 #else
    935887    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss_1  !< pointer for swapping of timelevels for respective quantity
    936888    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss_2  !< pointer for swapping of timelevels for respective quantity
     
    1026978    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  w          !< pointer: vertical velocity component w (z-direction)
    1027979    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  w_p        !< pointer: prognostic value of w
    1028 #endif
    1029980
    1030981    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  tri    !<  array to hold the tridiagonal matrix for solution of the Poisson equation in Fourier space (4th dimension for threads)
     
    19521903
    19531904          CHARACTER (LEN=*), INTENT(IN) ::  sk_char  !< string for treated scalar in Bott-Chlond scheme
    1954 #if defined( __nopointer )
    1955           REAL(wp), DIMENSION(:,:,:) ::  sk  !< treated scalar array in Bott-Chlond scheme
    1956 #else
     1905
    19571906          REAL(wp), DIMENSION(:,:,:), POINTER ::  sk  !< treated scalar array in Bott-Chlond scheme
    1958 #endif
     1907
    19591908       END SUBROUTINE advec_s_bc
    19601909
  • palm/trunk/SOURCE/ocean_mod.f90

    r3614 r3636  
    2525! -----------------
    2626! $Id$
     27! nopointer option removed
     28!
     29! 3614 2018-12-10 07:05:46Z raasch
    2730! unused variables removed
    2831!
     
    6467 
    6568
    66 #if defined( __nopointer )
    67     USE arrays_3d,                                                             &
    68         ONLY:  prho, rho_ocean, sa, sa_init, sa_p, tsa_m
    69 #else
    7069    USE arrays_3d,                                                             &
    7170        ONLY:  prho, prho_1, rho_ocean, rho_1, sa, sa_init, sa_1, sa_2, sa_3,  &
    7271               sa_p, tsa_m
    73 #endif
    7472
    7573    USE control_parameters,                                                    &
     
    11751173    IMPLICIT NONE
    11761174
    1177 #if defined( __nopointer )
    1178     ALLOCATE( prho(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                             &
    1179               rho_ocean(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                        &
    1180               sa(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                               &
    1181               sa_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                             &
    1182               tsa_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    1183 #else
    11841175    ALLOCATE( prho_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                           &
    11851176              rho_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                            &
     
    11941185    rho_ocean  => rho_1  ! routines calc_mean_profile and diffusion_e require
    11951186                         ! density to be a pointer
    1196 #endif
    1197 
    1198 #if ! defined( __nopointer )
     1187
    11991188!
    12001189!-- Initial assignment of pointers
     
    12041193       sa => sa_1;  sa_p => sa_1;  tsa_m => sa_3
    12051194    ENDIF
    1206 #endif
    12071195
    12081196 END SUBROUTINE ocean_init_arrays
     
    17861774    INTEGER, INTENT(IN) ::  mod_count  !< flag defining where pointers point to
    17871775
    1788 #if defined( __nopointer )
    1789 
    1790     sa = sa_p
    1791 
    1792 #else
    1793    
     1776
    17941777    SELECT CASE ( mod_count )
    17951778
     
    18051788
    18061789    END SELECT
    1807 
    1808 #endif
    18091790
    18101791 END SUBROUTINE ocean_swap_timelevel
  • palm/trunk/SOURCE/pmc_interface_mod.f90

    r3592 r3636  
    2525! -----------------
    2626! $Id$
     27! nopointer option removed
     28!
     29! 3592 2018-12-03 12:38:40Z suehring
    2730! Number of coupled arrays is determined dynamically (instead of a fixed value
    2831! of 32)
     
    328331
    329332
    330 #if defined( __nopointer )
    331     USE arrays_3d,                                                             &
    332         ONLY:  diss, dzu, dzw, e, e_p, nc, nr, pt, q, qc, qr, s, u, u_p,       &
    333                v, v_p, w, w_p, zu, zw
    334 #else
    335333   USE arrays_3d,                                                              &
    336334        ONLY:  diss, diss_2, dzu, dzw, e, e_p, e_2, nc, nc_2, nc_p, nr, nr_2,  &
    337335               pt, pt_2, q, q_2, qc, qc_2, qr, qr_2, s, s_2,                   &
    338336               u, u_p, u_2, v, v_p, v_2, w, w_p, w_2, zu, zw
    339 #endif
    340337
    341338    USE control_parameters,                                                    &
     
    37713768!    IF ( TRIM(name) == "z0" )    p_2d => z0
    37723769
    3773 #if defined( __nopointer )
    3774     IF ( ASSOCIATED( p_3d ) )  THEN
    3775        CALL pmc_s_set_dataarray( child_id, p_3d, nz_cl, nz )
    3776     ELSEIF ( ASSOCIATED( p_2d ) )  THEN
    3777        CALL pmc_s_set_dataarray( child_id, p_2d )
    3778     ELSEIF ( ASSOCIATED( i_2d ) )  THEN
    3779        CALL pmc_s_set_dataarray( child_id, i_2d )
    3780     ELSE
    3781 !
    3782 !--    Give only one message for the root domain
    3783        IF ( myid == 0  .AND.  cpl_id == 1 )  THEN
    3784 
    3785           message_string = 'pointer for array "' // TRIM( name ) //            &
    3786                            '" can''t be associated'
    3787           CALL message( 'pmci_set_array_pointer', 'PA0117', 3, 2, 0, 6, 0 )
    3788        ELSE
    3789 !
    3790 !--       Avoid others to continue
    3791           CALL MPI_BARRIER( comm2d, ierr )
    3792        ENDIF
    3793     ENDIF
    3794 #else
    37953770    IF ( TRIM(name) == "u"    )  p_3d_sec => u_2
    37963771    IF ( TRIM(name) == "v"    )  p_3d_sec => v_2
     
    38293804
    38303805   ENDIF
    3831 #endif
    38323806
    38333807#endif
  • palm/trunk/SOURCE/radiation_model_mod.f90

    r3633 r3636  
    2828! -----------------
    2929! $Id$
     30! nopointer option removed
     31!
     32! 3633 2018-12-17 16:17:57Z schwenkel
    3033! Include check for rrtmg files
    3134!
     
    48624865     REAL(wp)                          :: area_hor           !< total horizontal area of domain in all processor
    48634866
    4864 #if ! defined( __nopointer )
     4867
    48654868     IF ( plant_canopy )  THEN
    48664869         pchf_prep(:) = r_d * exner(nzub:nzut)                                 &
    48674870                     / (c_p * hyp(nzub:nzut) * dx*dy*dz(1)) !< equals to 1 / (rho * c_p * Vbox * T)
    48684871     ENDIF
    4869 #endif
     4872
    48704873     sun_direction = .TRUE.
    48714874     CALL calc_zenith  !< required also for diffusion radiation
  • palm/trunk/SOURCE/salsa_mod.f90

    r3630 r3636  
    2626! -----------------
    2727! $Id$
     28! nopointer option removed
     29!
     30! 3630 2018-12-17 11:04:17Z knoop
    2831! - Moved the control parameter "salsa" from salsa_mod.f90 to control_parameters
    2932! - Updated salsa_rrd_local and salsa_wrd_local
     
    935938!
    936939!-- Allocate prognostic variables (see salsa_swap_timelevel)
    937 #if defined( __nopointer )
    938     message_string = 'SALSA runs only with POINTER Version'
    939     CALL message( 'salsa_mod: salsa_init_arrays', 'SA0023', 1, 2, 0, 6, 0 )
    940 #else         
     940
    941941!
    942942!-- Set derived indices:
     
    11601160    ENDIF
    11611161   
    1162 #endif
    1163 
    11641162 END SUBROUTINE salsa_init_arrays
    11651163
     
    19581956    INTEGER(iwp) ::  g  !<
    19591957
    1960 !
    1961 !-- Example for prognostic variable "prog_var"
    1962 #if defined( __nopointer )
    1963     IF ( myid == 0 )  THEN
    1964        message_string =  ' SALSA runs only with POINTER Version'
    1965        CALL message( 'salsa_swap_timelevel', 'SA0022', 1, 2, 0, 6, 0 )
    1966     ENDIF
    1967 #else
    1968    
     1958
    19691959    SELECT CASE ( mod_count )
    19701960
     
    20202010
    20212011    END SELECT
    2022 #endif
    20232012
    20242013 END SUBROUTINE salsa_swap_timelevel
  • palm/trunk/SOURCE/swap_timelevel.f90

    r3589 r3636  
    2525! -----------------
    2626! $Id$
     27! nopointer option removed
     28!
     29! 3589 2018-11-30 15:09:51Z suehring
    2730! Move the control parameter "salsa" from salsa_mod to control_parameters
    2831! (M. Kurppa)
     
    142145 
    143146
    144 #if defined( __nopointer )
    145     USE arrays_3d,                                                             &
    146         ONLY:  nc, nc_p, nr, nr_p, pt, pt_p, q, q_p, qc, qc_p, qr, qr_p, s,    &
    147                s_p, sa, sa_p, u, u_p, v, v_p, w, w_p
    148 #else
    149147    USE arrays_3d,                                                             &
    150148        ONLY:  nc, nc_1, nc_2, nc_p, nr, nr_1, nr_2, nr_p, pt, pt_1, pt_2,     &
     
    152150               qr_p, s, s_1, s_2, s_p, sa, sa_1, sa_2, sa_p, u, u_1, u_2, u_p, &
    153151               v, v_1, v_2, v_p, w, w_1, w_2, w_p
    154 #endif
    155152
    156153    USE bulk_cloud_model_mod,                                                  &
     
    170167    USE gust_mod,                                                              &
    171168        ONLY: gust_module_enabled, gust_swap_timelevel
    172 
    173 #if defined( __nopointer )
    174     USE indices,                                                               &
    175         ONLY:  nxlg, nxrg, nyng, nysg, nzb, nzt
    176 #endif
    177169
    178170    USE land_surface_model_mod,                                                &
     
    197189    IMPLICIT NONE
    198190
    199 #if defined( __nopointer )
    200     INTEGER ::  i, j, k     !> loop indices
    201 #endif
    202191    INTEGER ::  swap_level  !> swap_level for steering the pmc data transfer
    203192
     
    208197!
    209198!-- Swap of variables
    210 #if defined( __nopointer )
    211     CALL cpu_log( log_point(28), 'swap_timelevel (nop)', 'start' )
    212 
    213     DO  i = nxlg, nxrg
    214        DO  j = nysg, nyng
    215           DO  k = nzb, nzt+1
    216              u(k,j,i)  = u_p(k,j,i)
    217              v(k,j,i)  = v_p(k,j,i)
    218              w(k,j,i)  = w_p(k,j,i)
    219              pt(k,j,i) = pt_p(k,j,i)
    220           ENDDO
    221        ENDDO
    222     ENDDO
    223 
    224     IF ( humidity )  THEN
    225        q = q_p
    226     ENDIF
    227 
    228     IF ( passive_scalar )  s = s_p             
    229 
    230 !
    231 !-- Swapping the timelevel of other modules
    232     IF ( humidity  .AND.  bulk_cloud_model )  CALL bcm_swap_timelevel( 0 )
    233     IF ( gust_module_enabled )                CALL gust_swap_timelevel( 0 )
    234     IF ( land_surface )                       CALL lsm_swap_timelevel( 0 )
    235     IF ( ocean_mode )                         CALL ocean_swap_timelevel( 0 )
    236     CALL tcm_swap_timelevel( 0 )
    237     IF ( urban_surface )                      CALL usm_swap_timelevel( 0 )
    238 
    239     CALL cpu_log( log_point(28), 'swap_timelevel (nop)', 'stop' )
    240 #else
    241199    CALL cpu_log( log_point(28), 'swap_timelevel', 'start' )
    242200
     
    312270
    313271    CALL cpu_log( log_point(28), 'swap_timelevel', 'stop' )
    314 #endif
    315272
    316273 END SUBROUTINE swap_timelevel
  • palm/trunk/SOURCE/turbulence_closure_mod.f90

    r3634 r3636  
    2525! -----------------
    2626! $Id$
     27! nopointer option removed
     28!
     29! 3634 2018-12-18 12:31:28Z knoop
    2730! OpenACC port for SPEC
    2831!
     
    177180 
    178181
    179 #if defined( __nopointer )
    180     USE arrays_3d,                                                             &
    181         ONLY:  diss, diss_p, dzu, e, e_p, kh, km,                              &
    182                mean_inflow_profiles, prho, pt, tdiss_m, te_m, tend, u, v, vpt, w
    183 #else
    184182    USE arrays_3d,                                                             &
    185183        ONLY:  diss, diss_1, diss_2, diss_3, diss_p, dzu, e, e_1, e_2, e_3,    &
    186184               e_p, kh, km, mean_inflow_profiles, prho, pt, tdiss_m,           &
    187185               te_m, tend, u, v, vpt, w
    188 #endif
    189186
    190187    USE basic_constants_and_equations_mod,                                     &
     
    911908    ALLOCATE( km(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    912909
    913 #if defined( __nopointer )
    914     ALLOCATE( e(nzb:nzt+1,nysg:nyng,nxlg:nxrg)    )
    915     ALLOCATE( e_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  )
    916     ALLOCATE( te_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    917 
    918 #else
    919910    ALLOCATE( e_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    920911    ALLOCATE( e_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    921912    ALLOCATE( e_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    922 #endif
     913
    923914!
    924915!-- Allocate arrays required for dissipation.
     
    928919    IF ( rans_mode  .OR.  use_sgs_for_particles  .OR.  wang_kernel  .OR.       &
    929920         collision_turbulence  .OR.  nested_run )  THEN
    930 #if defined( __nopointer )
    931        ALLOCATE( diss(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    932        IF ( rans_tke_e )  THEN
    933           ALLOCATE( diss_p(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  )
    934           ALLOCATE( tdiss_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    935        ENDIF
    936 #else
     921
    937922       ALLOCATE( diss_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    938923       IF ( rans_tke_e  .OR.  nested_run )  THEN
     
    940925          ALLOCATE( diss_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    941926       ENDIF
    942 #endif
     927
    943928    ENDIF
    944929
    945 #if ! defined( __nopointer )
    946930!
    947931!-- Initial assignment of pointers
     
    955939       ENDIF
    956940    ENDIF
    957 #endif
    958941
    959942 END SUBROUTINE tcm_init_arrays
     
    37313714#endif
    37323715
    3733 #if defined( __nopointer )
    3734     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var  !< temperature
    3735 #else
     3716    REAL(wp)     ::  dissipation  !< TKE dissipation
     3717
    37363718    REAL(wp), DIMENSION(:,:,:), POINTER ::  var  !< temperature
    3737 #endif
    3738     REAL(wp)     ::  dissipation  !< TKE dissipation
    37393719
    37403720
     
    39303910    REAL(wp)     ::  var_reference  !< reference temperature
    39313911
    3932 #if defined( __nopointer )
    3933     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var  !< temperature
    3934 #else
     3912    REAL(wp), DIMENSION(nzb+1:nzt) ::  dissipation  !< dissipation of TKE
     3913
    39353914    REAL(wp), DIMENSION(:,:,:), POINTER ::  var     !< temperature
    3936 #endif
    3937     REAL(wp), DIMENSION(nzb+1:nzt) ::  dissipation  !< dissipation of TKE
    39383915
    39393916!
     
    41614138    REAL(wp)     :: var_reference   !< var at reference height
    41624139
    4163 #if defined( __nopointer )
    4164     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var  !< temperature
    4165 #else
    41664140    REAL(wp), DIMENSION(:,:,:), POINTER ::  var  !< temperature
    4167 #endif
     4141
    41684142
    41694143    dvar_dz = atmos_ocean_sign * ( var(k+1,j,i) - var(k-1,j,i) ) * dd2zu(k)
     
    42184192    REAL(wp)     :: var_reference   !< var at reference height
    42194193
    4220 #if defined( __nopointer )
    4221     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var  !< temperature
    4222 #else
    42234194    REAL(wp), DIMENSION(:,:,:), POINTER ::  var  !< temperature
    4224 #endif
     4195
    42254196
    42264197    dvar_dz = atmos_ocean_sign * ( var(k+1,j,i) - var(k-1,j,i) ) * dd2zu(k)
     
    42824253    REAL(wp) ::  var_reference  !< reference temperature
    42834254
    4284 #if defined( __nopointer )
    4285     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var  !< temperature
    4286 #else
    42874255    REAL(wp), DIMENSION(:,:,:), POINTER ::  var  !< temperature
    4288 #endif
     4256
    42894257
    42904258!
     
    44884456#endif
    44894457
    4490 #if defined( __nopointer )
    4491     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var  !< temperature
    4492 #else
    44934458    REAL(wp), DIMENSION(:,:,:), POINTER ::  var  !< temperature
    4494 #endif
     4459
    44954460
    44964461!
     
    49424907
    49434908
    4944 #if defined( __nopointer )
    4945     INTEGER(iwp) ::  i      !< loop index x direction
    4946     INTEGER(iwp) ::  j      !< loop index y direction
    4947     INTEGER(iwp) ::  k      !< loop index z direction
    4948 #endif
    49494909    INTEGER, INTENT(IN) ::  mod_count  !< flag defining where pointers point to
    49504910
    4951 #if defined( __nopointer )
    4952 
    4953     IF ( .NOT. constant_diffusion )  THEN
    4954        DO  i = nxlg, nxrg
    4955           DO  j = nysg, nyng
    4956              DO  k = nzb, nzt+1
    4957                 e(k,j,i) = e_p(k,j,i)
    4958              ENDDO
    4959           ENDDO
    4960        ENDDO
    4961     ENDIF
    4962 
    4963     IF ( rans_tke_e )  THEN
    4964        DO  i = nxlg, nxrg
    4965           DO  j = nysg, nyng
    4966              DO  k = nzb, nzt+1
    4967                 diss(k,j,i) = diss_p(k,j,i)
    4968              ENDDO
    4969           ENDDO
    4970        ENDDO
    4971     ENDIF
    4972 
    4973 #else
    4974    
     4911
    49754912    SELECT CASE ( mod_count )
    49764913
     
    49964933
    49974934    END SELECT
    4998 #endif
    49994935
    50004936 END SUBROUTINE tcm_swap_timelevel
  • palm/trunk/SOURCE/urban_surface_mod.f90

    r3614 r3636  
    2828! -----------------
    2929! $Id$
     30! nopointer option removed
     31!
     32! 3614 2018-12-10 07:05:46Z raasch
    3033! unused variables removed
    3134!
     
    393396
    394397    USE arrays_3d,                                                             &
    395 #if ! defined( __nopointer )
    396398        ONLY:  hyp, zu, pt, p, u, v, w, tend, exner, hyrho, prr, q, ql, vpt
    397 #else
    398         ONLY:  hyp,     pt,    u, v, w, tend, exner, hyrho, prr, q, ql, vpt
    399 #endif
     399
    400400    USE calc_mean_profile_mod,                                                 &
    401401        ONLY:  calc_mean_profile
     
    936936    END TYPE surf_type_usm
    937937   
    938 #if defined( __nopointer )
    939     TYPE(surf_type_usm), TARGET   ::  m_liq_usm_h,        & !< liquid water reservoir (m), horizontal surface elements
    940                                       m_liq_usm_h_p         !< progn. liquid water reservoir (m), horizontal surface elements
    941 
    942     TYPE(surf_type_usm), DIMENSION(0:3), TARGET   ::  &
    943                                       m_liq_usm_v,        & !< liquid water reservoir (m), vertical surface elements
    944                                       m_liq_usm_v_p         !< progn. liquid water reservoir (m), vertical surface elements
    945 #else
    946938    TYPE(surf_type_usm), POINTER  ::  m_liq_usm_h,        & !< liquid water reservoir (m), horizontal surface elements
    947939                                      m_liq_usm_h_p         !< progn. liquid water reservoir (m), horizontal surface elements
     
    957949                                      m_liq_usm_v_1,      & !<
    958950                                      m_liq_usm_v_2         !<
    959 #endif
    960951
    961952    TYPE(surf_type_usm), TARGET ::  tm_liq_usm_h_m      !< liquid water reservoir tendency (m), horizontal surface elements
     
    1006997    REAL(wp), DIMENSION(:), ALLOCATABLE            :: zwn_green          !< normalized green layer depths (m)
    1007998
    1008 #if defined( __nopointer )
    1009     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h           !< wall surface temperature (K) at horizontal walls
    1010     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_h_p         !< progn. wall surface temperature (K) at horizontal walls
    1011     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h    !< window surface temperature (K) at horizontal walls
    1012     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_h_p  !< progn. window surface temperature (K) at horizontal walls
    1013     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h     !< green surface temperature (K) at horizontal walls
    1014     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_h_p   !< progn. green surface temperature (K) at horizontal walls
    1015     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_wall_v
    1016     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_wall_v_p
    1017     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_window_v
    1018     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_window_v_p
    1019     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_green_v
    1020     TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  ::  t_surf_green_v_p
    1021 #else
    1022999    REAL(wp), DIMENSION(:), POINTER                :: t_surf_wall_h
    10231000    REAL(wp), DIMENSION(:), POINTER                :: t_surf_wall_h_p
     
    10471024    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_1
    10481025    TYPE(t_surf_vertical), DIMENSION(0:3), TARGET  :: t_surf_green_v_2
    1049    
    1050 #endif
    10511026
    10521027!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    10551030!-- parameters of the land, roof and wall surfaces
    10561031
    1057 #if defined( __nopointer )
    1058     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h             !< Wall temperature (K)
    1059     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_p           !< Prog. wall temperature (K)
    1060     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h           !< Window temperature (K)
    1061     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_p         !< Prog. window temperature (K)
    1062     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h            !< Green temperature (K)
    1063     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_p          !< Prog. green temperature (K)
    1064     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h              !< soil water content green building layer
    1065     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h_av              !< avg of soil water content green building layer
    1066     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h_p              !< Prog. soil water content green building layer
    1067     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_sat_h          !< soil water content green building layer at saturation
    1068     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_res_h          !< soil water content green building layer residual
    1069     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: rootfr_h           !< root fraction green green building layer
    1070     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: wilt_h             !< wilting point green building layer
    1071     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: fc_h               !< field capacity green building layer
    1072 
    1073 
    1074     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v             !< Wall temperature (K)
    1075     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_p           !< Prog. wall temperature (K)
    1076     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v           !< Window temperature (K)
    1077     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_p         !< Prog. window temperature (K)
    1078     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v            !< Green temperature (K)
    1079     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_p          !< Prog. green temperature (K)
    1080     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v             !< Wall swc
    1081     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_p           !< Prog. swc
    1082    
    1083 #else
    10841032    REAL(wp), DIMENSION(:,:), POINTER                :: t_wall_h, t_wall_h_p
    10851033    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_1, t_wall_h_2
     
    11011049    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: swc_v, swc_v_p
    11021050    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_1, swc_v_2
    1103 #endif
    11041051
    11051052!-- Surface and material parameters classes (surface_type)
     
    14171364
    14181365!--     allocate wall and roof temperature arrays, for horizontal walls
    1419 #if defined( __nopointer )
    1420         IF ( .NOT. ALLOCATED( t_surf_wall_h ) )                                     &
    1421            ALLOCATE ( t_surf_wall_h(1:surf_usm_h%ns) )
    1422         IF ( .NOT. ALLOCATED( t_surf_wall_h_p ) )                                   &
    1423            ALLOCATE ( t_surf_wall_h_p(1:surf_usm_h%ns) )
    1424         IF ( .NOT. ALLOCATED( t_wall_h ) )                                     &           
    1425            ALLOCATE ( t_wall_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1426         IF ( .NOT. ALLOCATED( t_wall_h_p ) )                                   &           
    1427            ALLOCATE ( t_wall_h_p(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
    1428         IF ( .NOT. ALLOCATED( t_surf_window_h ) )                              &
    1429            ALLOCATE ( t_surf_window_h(1:surf_usm_h%ns) )
    1430         IF ( .NOT. ALLOCATED( t_surf_window_h_p ) )                            &
    1431            ALLOCATE ( t_surf_window_h_p(1:surf_usm_h%ns) )
    1432         IF ( .NOT. ALLOCATED( t_window_h ) )                                   &           
    1433            ALLOCATE ( t_window_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1434         IF ( .NOT. ALLOCATED( t_window_h_p ) )                                 &           
    1435            ALLOCATE ( t_window_h_p(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
    1436         IF ( .NOT. ALLOCATED( t_surf_green_h ) )                               &
    1437            ALLOCATE ( t_surf_green_h(1:surf_usm_h%ns) )
    1438         IF ( .NOT. ALLOCATED( t_surf_green_h_p ) )                             &
    1439            ALLOCATE ( t_surf_green_h_p(1:surf_usm_h%ns) )           
    1440         IF ( .NOT. ALLOCATED( t_green_h ) )                                    &           
    1441            ALLOCATE ( t_green_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1442         IF ( .NOT. ALLOCATED( t_green_h_p ) )                                  &           
    1443            ALLOCATE ( t_green_h_p(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) ) 
    1444         IF ( .NOT. ALLOCATED( swc_h ) )                                    &           
    1445            ALLOCATE ( swc_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1446         IF ( .NOT. ALLOCATED( swc_sat_h ) )                                    &           
    1447            ALLOCATE ( swc_sat_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1448         IF ( .NOT. ALLOCATED( swc_res_h ) )                                    &           
    1449            ALLOCATE ( swc_res_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1450         IF ( .NOT. ALLOCATED( rootfr_h ) )                                    &           
    1451            ALLOCATE ( rootfr_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1452         IF ( .NOT. ALLOCATED( wilt_h ) )                                    &           
    1453            ALLOCATE ( wilt_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1454         IF ( .NOT. ALLOCATED( fc_h ) )                                    &           
    1455            ALLOCATE ( fc_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    1456 
    1457        IF ( .NOT. ALLOCATED( m_liq_usm_h%var_usm_1d ) )                            &
    1458           ALLOCATE ( m_liq_usm_h%var_usm_1d(1:surf_usm_h%ns) )
    1459 
    1460 !--    Horizontal surfaces
    1461        ALLOCATE ( m_liq_usm_h_p%var_usm_1d(1:surf_usm_h%ns)                      )
    1462 !
    1463 !--    Vertical surfaces
    1464        DO  l = 0, 3
    1465           ALLOCATE ( m_liq_usm_v_p(l)%var_usm_1d(1:surf_usm_v(l)%ns)                      )
    1466        ENDDO
    1467          
    1468 #else
    14691366!
    14701367!--     Allocate if required. Note, in case of restarts, some of these arrays
     
    15291426        wilt_h       => wilt_h_1
    15301427        fc_h       => fc_h_1
    1531  
    1532 #endif
    15331428
    15341429!--     allocate wall and roof temperature arrays, for vertical walls if required
    1535 #if defined( __nopointer )
    1536         DO  l = 0, 3
    1537            IF ( .NOT. ALLOCATED( t_surf_wall_v(l)%t ) )                             &
    1538               ALLOCATE ( t_surf_wall_v(l)%t(1:surf_usm_v(l)%ns) )
    1539            IF ( .NOT. ALLOCATED( t_surf_wall_v_p(l)%t ) )                           &
    1540               ALLOCATE ( t_surf_wall_v_p(l)%t(1:surf_usm_v(l)%ns) )
    1541            IF ( .NOT. ALLOCATED( t_wall_v(l)%t ) )                             &
    1542               ALLOCATE ( t_wall_v(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1543            IF ( .NOT. ALLOCATED( t_wall_v_p(l)%t ) )                           &                 
    1544               ALLOCATE ( t_wall_v_p(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1545            IF ( .NOT. ALLOCATED( t_surf_window_v(l)%t ) )                      &
    1546               ALLOCATE ( t_surf_window_v(l)%t(1:surf_usm_v(l)%ns) )
    1547            IF ( .NOT. ALLOCATED( t_surf_window_v_p(l)%t ) )                    &
    1548               ALLOCATE ( t_surf_window_v_p(l)%t(1:surf_usm_v(l)%ns) )
    1549            IF ( .NOT. ALLOCATED( t_window_v(l)%t ) )                           &
    1550               ALLOCATE ( t_window_v(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1551            IF ( .NOT. ALLOCATED( t_window_v_p(l)%t ) )                         &                 
    1552               ALLOCATE ( t_window_v_p(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1553            IF ( .NOT. ALLOCATED( t_green_v(l)%t ) )                            &
    1554               ALLOCATE ( t_green_v(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1555            IF ( .NOT. ALLOCATED( t_green_v_p(l)%t ) )                          &                 
    1556               ALLOCATE ( t_green_v_p(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1557            IF ( .NOT. ALLOCATED( t_surf_green_v(l)%t ) )                       &
    1558               ALLOCATE ( t_surf_green_v(l)%t(1:surf_usm_v(l)%ns) )
    1559            IF ( .NOT. ALLOCATED( t_surf_green_v_p(l)%t ) )                     &
    1560               ALLOCATE ( t_surf_green_v_p(l)%t(1:surf_usm_v(l)%ns) )
    1561            IF ( .NOT. ALLOCATED( m_liq_usm_v(l)%var_usm_1d ) )                 &
    1562              ALLOCATE ( m_liq_usm_v(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
    1563            IF ( .NOT. ALLOCATED( swc_v(l)%t ) )                             &
    1564               ALLOCATE ( swc_v(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1565            IF ( .NOT. ALLOCATED( swc_v_p(l)%t ) )                           &                 
    1566               ALLOCATE ( swc_v_p(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1567         ENDDO
    1568 #else
    15691430!
    15701431!--     Allocate if required. Note, in case of restarts, some of these arrays
     
    16151476        swc_v    => swc_v_1;    swc_v_p    => swc_v_2
    16161477
    1617 #endif
    16181478!
    16191479!--     Allocate intermediate timestep arrays. For horizontal surfaces.
     
    40593919        REAL(wp)     ::  z_agl                        !< height above ground
    40603920
    4061 !
    4062 !-- NOPOINTER version not implemented yet
    4063 #if defined( __nopointer )
    4064     message_string = 'The urban surface module only runs with POINTER version'
    4065     CALL message( 'urban_surface_mod', 'PA0452', 1, 2, 0, 6, 0 )
    4066 #endif
    40673921
    40683922        CALL cpu_log( log_point_s(78), 'usm_init', 'start' )
     
    51755029!--         At horizontal surfaces. Please note, t_surf_wall_h is defined on a
    51765030!--         different data type, but with the same dimension.
    5177 #if ! defined( __nopointer )
    51785031            DO  m = 1, surf_usm_h%ns
    51795032               i = surf_usm_h%i(m)           
     
    52005053               ENDDO
    52015054            ENDDO
    5202 #endif
     5055
    52035056!
    52045057!--         For the sake of correct initialization, set also q_surface.
     
    64166269         
    64176270             CASE ( 't_surf_wall_h' )
    6418 #if defined( __nopointer )                   
    6419                 IF ( k == 1 )  THEN
    6420                    IF ( .NOT.  ALLOCATED( t_surf_wall_h ) )                         &
    6421                       ALLOCATE( t_surf_wall_h(1:surf_usm_h%ns) )
    6422                    READ ( 13 )  tmp_surf_wall_h
    6423                 ENDIF
    6424                 CALL surface_restore_elements(                                 &
    6425                                         t_surf_wall_h, tmp_surf_wall_h,                  &
    6426                                         surf_usm_h%start_index,                & 
    6427                                         start_index_on_file,                   &
    6428                                         end_index_on_file,                     &
    6429                                         nxlc, nysc,                            &
    6430                                         nxlf, nxrf, nysf, nynf,                &
    6431                                         nys_on_file, nyn_on_file,              &
    6432                                         nxl_on_file,nxr_on_file )
    6433 #else                 
    64346271                IF ( k == 1 )  THEN
    64356272                   IF ( .NOT.  ALLOCATED( t_surf_wall_h_1 ) )                       &
     
    64466283                                        nys_on_file, nyn_on_file,              &
    64476284                                        nxl_on_file,nxr_on_file )
    6448 #endif
    64496285
    64506286             CASE ( 't_surf_wall_v(0)' )
    6451 #if defined( __nopointer )           
    6452                 IF ( k == 1 )  THEN
    6453                    IF ( .NOT.  ALLOCATED( t_surf_wall_v(0)%t ) )                    &
    6454                       ALLOCATE( t_surf_wall_v(0)%t(1:surf_usm_v(0)%ns) )
    6455                    READ ( 13 )  tmp_surf_wall_v(0)%t
    6456                 ENDIF
    6457                 CALL surface_restore_elements(                                 &
    6458                                         t_surf_wall_v(0)%t, tmp_surf_wall_v(0)%t,        &
    6459                                         surf_usm_v(0)%start_index,             &
    6460                                         start_index_on_file,                   &
    6461                                         end_index_on_file,                     &
    6462                                         nxlc, nysc,                            &
    6463                                         nxlf, nxrf, nysf, nynf,                &
    6464                                         nys_on_file, nyn_on_file,              &
    6465                                         nxl_on_file,nxr_on_file )
    6466 #else                     
    64676287                IF ( k == 1 )  THEN
    64686288                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(0)%t ) )                  &
     
    64796299                                        nys_on_file, nyn_on_file,              &
    64806300                                        nxl_on_file,nxr_on_file )
    6481 #endif
    64826301                     
    64836302             CASE ( 't_surf_wall_v(1)' )
    6484 #if defined( __nopointer )       
    6485                 IF ( k == 1 )  THEN
    6486                    IF ( .NOT.  ALLOCATED( t_surf_wall_v(1)%t ) )                    &
    6487                       ALLOCATE( t_surf_wall_v(1)%t(1:surf_usm_v(1)%ns) )
    6488                    READ ( 13 )  tmp_surf_wall_v(1)%t
    6489                 ENDIF
    6490                 CALL surface_restore_elements(                                 &
    6491                                         t_surf_wall_v(1)%t, tmp_surf_wall_v(1)%t,        &
    6492                                         surf_usm_v(1)%start_index,             &
    6493                                         start_index_on_file,                   &
    6494                                         end_index_on_file,                     &
    6495                                         nxlc, nysc,                            &
    6496                                         nxlf, nxrf, nysf, nynf,                &
    6497                                         nys_on_file, nyn_on_file,              &
    6498                                         nxl_on_file,nxr_on_file )                 
    6499 #else                     
    65006303                IF ( k == 1 )  THEN
    65016304                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(1)%t ) )                  &
     
    65126315                                        nys_on_file, nyn_on_file,              &
    65136316                                        nxl_on_file,nxr_on_file )
    6514 #endif
    65156317
    65166318             CASE ( 't_surf_wall_v(2)' )
    6517 #if defined( __nopointer )         
    6518                 IF ( k == 1 )  THEN
    6519                    IF ( .NOT.  ALLOCATED( t_surf_wall_v(2)%t ) )                    &
    6520                       ALLOCATE( t_surf_wall_v(2)%t(1:surf_usm_v(2)%ns) )
    6521                    READ ( 13 )  tmp_surf_wall_v(2)%t
    6522                 ENDIF
    6523                 CALL surface_restore_elements(                                 &
    6524                                         t_surf_wall_v(2)%t, tmp_surf_wall_v(2)%t,        &
    6525                                         surf_usm_v(2)%start_index,             &
    6526                                         start_index_on_file,                   &
    6527                                         end_index_on_file,                     &
    6528                                         nxlc, nysc,                            &
    6529                                         nxlf, nxrf, nysf, nynf,                &
    6530                                         nys_on_file, nyn_on_file,              &
    6531                                         nxl_on_file,nxr_on_file )
    6532 #else                     
    65336319                IF ( k == 1 )  THEN
    65346320                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(2)%t ) )                  &
     
    65456331                                        nys_on_file, nyn_on_file,              &
    65466332                                        nxl_on_file,nxr_on_file )
    6547 #endif
    65486333                     
    65496334             CASE ( 't_surf_wall_v(3)' )
    6550 #if defined( __nopointer )   
    6551                 IF ( k == 1 )  THEN
    6552                    IF ( .NOT.  ALLOCATED( t_surf_wall_v(3)%t ) )                    &
    6553                       ALLOCATE( t_surf_wall_v(3)%t(1:surf_usm_v(3)%ns) )
    6554                    READ ( 13 )  tmp_surf_wall_v(3)%t
    6555                 ENDIF
    6556                 CALL surface_restore_elements(                                 &
    6557                                         t_surf_wall_v(3)%t, tmp_surf_wall_v(3)%t,        &
    6558                                         surf_usm_v(3)%start_index,             &
    6559                                         start_index_on_file,                   &
    6560                                         end_index_on_file,                     &
    6561                                         nxlc, nysc,                            &
    6562                                         nxlf, nxrf, nysf, nynf,                &
    6563                                         nys_on_file, nyn_on_file,              &
    6564                                         nxl_on_file,nxr_on_file )
    6565 #else                     
    65666335                IF ( k == 1 )  THEN
    65676336                   IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(3)%t ) )                  &
     
    65786347                                        nys_on_file, nyn_on_file,              &
    65796348                                        nxl_on_file,nxr_on_file )
    6580 #endif
     6349
    65816350             CASE ( 't_surf_green_h' )
    6582 #if defined( __nopointer )                   
    6583                 IF ( k == 1 )  THEN
    6584                    IF ( .NOT.  ALLOCATED( t_surf_green_h ) )                   &
    6585                       ALLOCATE( t_surf_green_h(1:surf_usm_h%ns) )
    6586                    READ ( 13 )  tmp_surf_green_h
    6587                 ENDIF
    6588                 CALL surface_restore_elements(                                 &
    6589                                         t_surf_green_h, tmp_surf_green_h,      &
    6590                                         surf_usm_h%start_index,                &
    6591                                         start_index_on_file,                   &
    6592                                         end_index_on_file,                     &
    6593                                         nxlc, nysc,                            &
    6594                                         nxlf, nxrf, nysf, nynf,                &
    6595                                         nys_on_file, nyn_on_file,              &
    6596                                         nxl_on_file,nxr_on_file )
    6597 #else                     
    65986351                IF ( k == 1 )  THEN
    65996352                   IF ( .NOT.  ALLOCATED( t_surf_green_h_1 ) )                 &
     
    66106363                                        nys_on_file, nyn_on_file,              &
    66116364                                        nxl_on_file,nxr_on_file )
    6612 #endif
    66136365
    66146366             CASE ( 't_surf_green_v(0)' )
    6615 #if defined( __nopointer )           
    6616                 IF ( k == 1 )  THEN
    6617                    IF ( .NOT.  ALLOCATED( t_surf_green_v(0)%t ) )              &
    6618                       ALLOCATE( t_surf_green_v(0)%t(1:surf_usm_v(0)%ns) )
    6619                    READ ( 13 )  tmp_surf_green_v(0)%t
    6620                 ENDIF
    6621                 CALL surface_restore_elements(                                 &
    6622                                         t_surf_green_v(0)%t,                   &
    6623                                         tmp_surf_green_v(0)%t,                 &
    6624                                         surf_usm_v(0)%start_index,             &
    6625                                         start_index_on_file,                   &
    6626                                         end_index_on_file,                     &
    6627                                         nxlc, nysc,                            &
    6628                                         nxlf, nxrf, nysf, nynf,                &
    6629                                         nys_on_file, nyn_on_file,              &
    6630                                         nxl_on_file,nxr_on_file )
    6631 #else                     
    66326367                IF ( k == 1 )  THEN
    66336368                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(0)%t ) )            &
     
    66456380                                        nys_on_file, nyn_on_file,              &
    66466381                                        nxl_on_file,nxr_on_file )
    6647 #endif
    66486382                   
    66496383             CASE ( 't_surf_green_v(1)' )
    6650 #if defined( __nopointer )       
    6651                 IF ( k == 1 )  THEN
    6652                    IF ( .NOT.  ALLOCATED( t_surf_green_v(1)%t ) )              &
    6653                       ALLOCATE( t_surf_green_v(1)%t(1:surf_usm_v(1)%ns) )
    6654                    READ ( 13 )  tmp_surf_green_v(1)%t
    6655                 ENDIF
    6656                 CALL surface_restore_elements(                                 &
    6657                                         t_surf_green_v(1)%t,                   &
    6658                                         tmp_surf_green_v(1)%t,                 &
    6659                                         surf_usm_v(1)%start_index,             &
    6660                                         start_index_on_file,                   &
    6661                                         end_index_on_file,                     &
    6662                                         nxlc, nysc,                            &
    6663                                         nxlf, nxrf, nysf, nynf,                &
    6664                                         nys_on_file, nyn_on_file,              &
    6665                                         nxl_on_file,nxr_on_file )                 
    6666 #else                     
    66676384                IF ( k == 1 )  THEN
    66686385                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(1)%t ) )            &
     
    66806397                                        nys_on_file, nyn_on_file,              &
    66816398                                        nxl_on_file,nxr_on_file )
    6682 #endif
    66836399
    66846400             CASE ( 't_surf_green_v(2)' )
    6685 #if defined( __nopointer )         
    6686                 IF ( k == 1 )  THEN
    6687                    IF ( .NOT.  ALLOCATED( t_surf_green_v(2)%t ) )              &
    6688                       ALLOCATE( t_surf_green_v(2)%t(1:surf_usm_v(2)%ns) )
    6689                    READ ( 13 )  tmp_surf_green_v(2)%t
    6690                 ENDIF
    6691                 CALL surface_restore_elements(                                 &
    6692                                         t_surf_green_v(2)%t,                   &
    6693                                         tmp_surf_green_v(2)%t,                 &
    6694                                         surf_usm_v(2)%start_index,             &
    6695                                         start_index_on_file,                   &
    6696                                         end_index_on_file,                     &
    6697                                         nxlc, nysc,                            &
    6698                                         nxlf, nxrf, nysf, nynf,                &
    6699                                         nys_on_file, nyn_on_file,              &
    6700                                         nxl_on_file,nxr_on_file )
    6701 #else                     
    67026401                IF ( k == 1 )  THEN
    67036402                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(2)%t ) )            &
     
    67156414                                        nys_on_file, nyn_on_file,              &
    67166415                                        nxl_on_file,nxr_on_file )
    6717 #endif
    67186416                   
    67196417             CASE ( 't_surf_green_v(3)' )
    6720 #if defined( __nopointer )   
    6721                 IF ( k == 1 )  THEN
    6722                    IF ( .NOT.  ALLOCATED( t_surf_green_v(3)%t ) )              &
    6723                       ALLOCATE( t_surf_green_v(3)%t(1:surf_usm_v(3)%ns) )
    6724                    READ ( 13 )  tmp_surf_green_v(3)%t
    6725                 ENDIF
    6726                 CALL surface_restore_elements(                                 &
    6727                                         t_surf_green_v(3)%t,                   &
    6728                                         tmp_surf_green_v(3)%t,                 &
    6729                                         surf_usm_v(3)%start_index,             &
    6730                                         start_index_on_file,                   &
    6731                                         end_index_on_file,                     &
    6732                                         nxlc, nysc,                            &
    6733                                         nxlf, nxrf, nysf, nynf,                &
    6734                                         nys_on_file, nyn_on_file,              &
    6735                                         nxl_on_file,nxr_on_file )
    6736 #else                     
    67376418                IF ( k == 1 )  THEN
    67386419                   IF ( .NOT.  ALLOCATED( t_surf_green_v_1(3)%t ) )            &
     
    67506431                                        nys_on_file, nyn_on_file,              &
    67516432                                        nxl_on_file,nxr_on_file )
    6752 #endif
     6433
    67536434             CASE ( 't_surf_window_h' )
    6754 #if defined( __nopointer )                   
    6755                 IF ( k == 1 )  THEN
    6756                    IF ( .NOT.  ALLOCATED( t_surf_window_h ) )                  &
    6757                       ALLOCATE( t_surf_window_h(1:surf_usm_h%ns) )
    6758                    READ ( 13 )  tmp_surf_window_h
    6759                 ENDIF
    6760                 CALL surface_restore_elements(                                 &
    6761                                         t_surf_window_h, tmp_surf_window_h,    &
    6762                                         surf_usm_h%start_index,                &
    6763                                         start_index_on_file,                   &
    6764                                         end_index_on_file,                     &
    6765                                         nxlc, nysc,                            &
    6766                                         nxlf, nxrf, nysf, nynf,                &
    6767                                         nys_on_file, nyn_on_file,              &
    6768                                         nxl_on_file,nxr_on_file )
    6769 #else                     
    67706435                IF ( k == 1 )  THEN
    67716436                   IF ( .NOT.  ALLOCATED( t_surf_window_h_1 ) )                &
     
    67836448                                        nys_on_file, nyn_on_file,              &
    67846449                                        nxl_on_file,nxr_on_file )
    6785 #endif
    67866450
    67876451             CASE ( 't_surf_window_v(0)' )
    6788 #if defined( __nopointer )           
    6789                 IF ( k == 1 )  THEN
    6790                    IF ( .NOT.  ALLOCATED( t_surf_window_v(0)%t ) )             &
    6791                       ALLOCATE( t_surf_window_v(0)%t(1:surf_usm_v(0)%ns) )
    6792                    READ ( 13 )  tmp_surf_window_v(0)%t
    6793                 ENDIF
    6794                 CALL surface_restore_elements(                                 &
    6795                                         t_surf_window_v(0)%t,                  &
    6796                                         tmp_surf_window_v(0)%t,                &
    6797                                         surf_usm_v(0)%start_index,             &
    6798                                         start_index_on_file,                   &
    6799                                         end_index_on_file,                     &
    6800                                         nxlc, nysc,                            &
    6801                                         nxlf, nxrf, nysf, nynf,                &
    6802                                         nys_on_file, nyn_on_file,              &
    6803                                         nxl_on_file,nxr_on_file )
    6804 #else                     
    68056452                IF ( k == 1 )  THEN
    68066453                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(0)%t ) )           &
     
    68186465                                        nys_on_file, nyn_on_file,              &
    68196466                                        nxl_on_file,nxr_on_file )
    6820 #endif
    68216467                   
    68226468             CASE ( 't_surf_window_v(1)' )
    6823 #if defined( __nopointer )       
    6824                 IF ( k == 1 )  THEN
    6825                    IF ( .NOT.  ALLOCATED( t_surf_window_v(1)%t ) )             &
    6826                       ALLOCATE( t_surf_window_v(1)%t(1:surf_usm_v(1)%ns) )
    6827                    READ ( 13 )  tmp_surf_window_v(1)%t
    6828                 ENDIF
    6829                 CALL surface_restore_elements(                                 &
    6830                                         t_surf_window_v(1)%t,                  &
    6831                                         tmp_surf_window_v(1)%t,                &
    6832                                         surf_usm_v(1)%start_index,             &
    6833                                         start_index_on_file,                   &
    6834                                         end_index_on_file,                     &
    6835                                         nxlc, nysc,                            &
    6836                                         nxlf, nxrf, nysf, nynf,                &
    6837                                         nys_on_file, nyn_on_file,              &
    6838                                         nxl_on_file,nxr_on_file )                 
    6839 #else                     
    68406469                IF ( k == 1 )  THEN
    68416470                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(1)%t ) )           &
     
    68536482                                        nys_on_file, nyn_on_file,              &
    68546483                                        nxl_on_file,nxr_on_file )
    6855 #endif
    68566484
    68576485             CASE ( 't_surf_window_v(2)' )
    6858 #if defined( __nopointer )         
    6859                 IF ( k == 1 )  THEN
    6860                    IF ( .NOT.  ALLOCATED( t_surf_window_v(2)%t ) )             &
    6861                       ALLOCATE( t_surf_window_v(2)%t(1:surf_usm_v(2)%ns) )
    6862                    READ ( 13 )  tmp_surf_window_v(2)%t
    6863                 ENDIF
    6864                 CALL surface_restore_elements(                                 &
    6865                                         t_surf_window_v(2)%t,                  &
    6866                                         tmp_surf_window_v(2)%t,                &
    6867                                         surf_usm_v(2)%start_index,             &   
    6868                                         start_index_on_file,                   &
    6869                                         end_index_on_file,                     &
    6870                                         nxlc, nysc,                            &
    6871                                         nxlf, nxrf, nysf, nynf,                &
    6872                                         nys_on_file, nyn_on_file,              &
    6873                                         nxl_on_file,nxr_on_file )
    6874 #else                     
    68756486                IF ( k == 1 )  THEN
    68766487                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(2)%t ) )           &
     
    68886499                                        nys_on_file, nyn_on_file,              &
    68896500                                        nxl_on_file,nxr_on_file )
    6890 #endif
    68916501                   
    68926502             CASE ( 't_surf_window_v(3)' )
    6893 #if defined( __nopointer )   
    6894                 IF ( k == 1 )  THEN
    6895                    IF ( .NOT.  ALLOCATED( t_surf_window_v(3)%t ) )             &
    6896                       ALLOCATE( t_surf_window_v(3)%t(1:surf_usm_v(3)%ns) )
    6897                    READ ( 13 )  tmp_surf_window_v(3)%t
    6898                 ENDIF
    6899                 CALL surface_restore_elements(                                 &
    6900                                         t_surf_window_v(3)%t,                  &
    6901                                         tmp_surf_window_v(3)%t,                &
    6902                                         surf_usm_v(3)%start_index,             &
    6903                                         start_index_on_file,                   &
    6904                                         end_index_on_file,                     &
    6905                                         nxlc, nysc,                            &
    6906                                         nxlf, nxrf, nysf, nynf,                &
    6907                                         nys_on_file, nyn_on_file,              &
    6908                                         nxl_on_file,nxr_on_file )
    6909 #else                     
    69106503                IF ( k == 1 )  THEN
    69116504                   IF ( .NOT.  ALLOCATED( t_surf_window_v_1(3)%t ) )           &
     
    69236516                                        nys_on_file, nyn_on_file,              &
    69246517                                        nxl_on_file,nxr_on_file )
    6925 #endif
     6518
    69266519             CASE ( 't_wall_h' )
    6927 #if defined( __nopointer )
    6928                 IF ( k == 1 )  THEN
    6929                    IF ( .NOT.  ALLOCATED( t_wall_h ) )                         &
    6930                       ALLOCATE( t_wall_h(nzb_wall:nzt_wall+1,1:surf_usm_h%ns) )
    6931                    READ ( 13 )  tmp_wall_h
    6932                 ENDIF
    6933                 CALL surface_restore_elements(                                 &
    6934                                         t_wall_h, tmp_wall_h,                  &
    6935                                         surf_usm_h%start_index,                &
    6936                                         start_index_on_file,                   &
    6937                                         end_index_on_file,                     &
    6938                                         nxlc, nysc,                            &
    6939                                         nxlf, nxrf, nysf, nynf,                &
    6940                                         nys_on_file, nyn_on_file,              &
    6941                                         nxl_on_file,nxr_on_file )
    6942 #else
    69436520                IF ( k == 1 )  THEN
    69446521                   IF ( .NOT.  ALLOCATED( t_wall_h_1 ) )                       &
     
    69566533                                        nys_on_file, nyn_on_file,              &
    69576534                                        nxl_on_file,nxr_on_file )
    6958 #endif
     6535
    69596536             CASE ( 't_wall_v(0)' )
    6960 #if defined( __nopointer )
    6961                 IF ( k == 1 )  THEN
    6962                    IF ( .NOT.  ALLOCATED( t_wall_v(0)%t ) )                    &
    6963                       ALLOCATE( t_wall_v(0)%t(nzb_wall:nzt_wall+1,             &
    6964                                               1:surf_usm_v(0)%ns) )
    6965                    READ ( 13 )  tmp_wall_v(0)%t
    6966                 ENDIF
    6967                 CALL surface_restore_elements(                                 &
    6968                                         t_wall_v(0)%t, tmp_wall_v(0)%t,        &
    6969                                         surf_usm_v(0)%start_index,             &   
    6970                                         start_index_on_file,                   &
    6971                                         end_index_on_file,                     &
    6972                                         nxlc, nysc,                            &
    6973                                         nxlf, nxrf, nysf, nynf,                &
    6974                                         nys_on_file, nyn_on_file,              &
    6975                                         nxl_on_file,nxr_on_file )
    6976 #else
    69776537                IF ( k == 1 )  THEN
    69786538                   IF ( .NOT.  ALLOCATED( t_wall_v_1(0)%t ) )                  &
     
    69906550                                        nys_on_file, nyn_on_file,              &
    69916551                                        nxl_on_file,nxr_on_file )
    6992 #endif
     6552
    69936553             CASE ( 't_wall_v(1)' )
    6994 #if defined( __nopointer )
    6995                 IF ( k == 1 )  THEN
    6996                    IF ( .NOT.  ALLOCATED( t_wall_v(1)%t ) )                    &
    6997                       ALLOCATE( t_wall_v(1)%t(nzb_wall:nzt_wall+1,             &
    6998                                               1:surf_usm_v(1)%ns) )
    6999                    READ ( 13 )  tmp_wall_v(1)%t
    7000                 ENDIF
    7001                 CALL surface_restore_elements(                                 &
    7002                                         t_wall_v(1)%t, tmp_wall_v(1)%t,        &
    7003                                         surf_usm_v(1)%start_index,             &
    7004                                         start_index_on_file,                   &
    7005                                         end_index_on_file ,                    &
    7006                                         nxlc, nysc,                            &
    7007                                         nxlf, nxrf, nysf, nynf,                &
    7008                                         nys_on_file, nyn_on_file,              &
    7009                                         nxl_on_file, nxr_on_file )
    7010 #else
    70116554                IF ( k == 1 )  THEN
    70126555                   IF ( .NOT.  ALLOCATED( t_wall_v_1(1)%t ) )                  &
     
    70246567                                        nys_on_file, nyn_on_file,              &
    70256568                                        nxl_on_file,nxr_on_file )
    7026 #endif
     6569
    70276570             CASE ( 't_wall_v(2)' )
    7028 #if defined( __nopointer )
    7029                 IF ( k == 1 )  THEN
    7030                    IF ( .NOT.  ALLOCATED( t_wall_v(2)%t ) )                    &
    7031                       ALLOCATE( t_wall_v(2)%t(nzb_wall:nzt_wall+1,             &
    7032                                               1:surf_usm_v(2)%ns) )
    7033                    READ ( 13 )  tmp_wall_v(2)%t
    7034                 ENDIF
    7035                 CALL surface_restore_elements(                                 &
    7036                                         t_wall_v(2)%t, tmp_wall_v(2)%t,        &
    7037                                         surf_usm_v(2)%start_index,             & 
    7038                                         start_index_on_file,                   &
    7039                                         end_index_on_file,                     &
    7040                                         nxlc, nysc,                            &
    7041                                         nxlf, nxrf, nysf, nynf,                &
    7042                                         nys_on_file, nyn_on_file,              &
    7043                                         nxl_on_file,nxr_on_file )
    7044 #else
    70456571                IF ( k == 1 )  THEN
    70466572                   IF ( .NOT.  ALLOCATED( t_wall_v_1(2)%t ) )                  &
     
    70586584                                        nys_on_file, nyn_on_file,              &
    70596585                                        nxl_on_file,nxr_on_file )
    7060 #endif
     6586
    70616587             CASE ( 't_wall_v(3)' )
    7062 #if defined( __nopointer )
    7063                 IF ( k == 1 )  THEN
    7064                    IF ( .NOT.  ALLOCATED( t_wall_v(3)%t ) )                    &
    7065                       ALLOCATE( t_wall_v(3)%t(nzb_wall:nzt_wall+1,             &
    7066                                               1:surf_usm_v(3)%ns) )
    7067                    READ ( 13 )  tmp_wall_v(3)%t
    7068                 ENDIF
    7069                 CALL surface_restore_elements(                                 &
    7070                                         t_wall_v(3)%t, tmp_wall_v(3)%t,        &
    7071                                         surf_usm_v(3)%start_index,             &   
    7072                                         start_index_on_file,                   &
    7073                                         end_index_on_file,                     &
    7074                                         nxlc, nysc,                            &
    7075                                         nxlf, nxrf, nysf, nynf,                &
    7076                                         nys_on_file, nyn_on_file,              &
    7077                                         nxl_on_file,nxr_on_file )
    7078 #else
    70796588                IF ( k == 1 )  THEN
    70806589                   IF ( .NOT.  ALLOCATED( t_wall_v_1(3)%t ) )                  &
     
    70926601                                        nys_on_file, nyn_on_file,              &
    70936602                                        nxl_on_file,nxr_on_file )
    7094 #endif
     6603
    70956604             CASE ( 't_green_h' )
    7096 #if defined( __nopointer )
    7097                 IF ( k == 1 )  THEN
    7098                    IF ( .NOT.  ALLOCATED( t_green_h ) )                        &
    7099                       ALLOCATE( t_green_h(nzb_wall:nzt_wall+1,                 &
    7100                                           1:surf_usm_h%ns) )
    7101                    READ ( 13 )  tmp_green_h
    7102                 ENDIF
    7103                 CALL surface_restore_elements(                                 &
    7104                                         t_green_h, tmp_green_h,                &
    7105                                         surf_usm_h%start_index,                &
    7106                                         start_index_on_file,                   &
    7107                                         end_index_on_file,                     &
    7108                                         nxlc, nysc,                            &
    7109                                         nxlf, nxrf, nysf, nynf,                &
    7110                                         nys_on_file, nyn_on_file,              &
    7111                                         nxl_on_file,nxr_on_file )
    7112 #else
    71136605                IF ( k == 1 )  THEN
    71146606                   IF ( .NOT.  ALLOCATED( t_green_h_1 ) )                      &
     
    71266618                                        nys_on_file, nyn_on_file,              &
    71276619                                        nxl_on_file,nxr_on_file )
    7128 #endif
     6620
    71296621             CASE ( 't_green_v(0)' )
    7130 #if defined( __nopointer )
    7131                 IF ( k == 1 )  THEN
    7132                    IF ( .NOT.  ALLOCATED( t_green_v(0)%t ) )                   &
    7133                       ALLOCATE( t_green_v(0)%t(nzb_wall:nzt_wall+1,            &
    7134                                                1:surf_usm_v(0)%ns) )
    7135                    READ ( 13 )  tmp_green_v(0)%t
    7136                 ENDIF
    7137                 CALL surface_restore_elements(                                 &
    7138                                         t_green_v(0)%t, tmp_green_v(0)%t,      &
    7139                                         surf_usm_v(0)%start_index,             &
    7140                                         start_index_on_file,                   &
    7141                                         end_index_on_file,                     &
    7142                                         nxlc, nysc,                            &
    7143                                         nxlf, nxrf, nysf, nynf,                &
    7144                                         nys_on_file, nyn_on_file,              &
    7145                                         nxl_on_file,nxr_on_file )
    7146 #else
    71476622                IF ( k == 1 )  THEN
    71486623                   IF ( .NOT.  ALLOCATED( t_green_v_1(0)%t ) )                 &
     
    71606635                                        nys_on_file, nyn_on_file,              &
    71616636                                        nxl_on_file,nxr_on_file )
    7162 #endif
     6637
    71636638             CASE ( 't_green_v(1)' )
    7164 #if defined( __nopointer )
    7165                 IF ( k == 1 )  THEN
    7166                    IF ( .NOT.  ALLOCATED( t_green_v(1)%t ) )                   &
    7167                       ALLOCATE( t_green_v(1)%t(nzb_wall:nzt_wall+1,            &
    7168                                                1:surf_usm_v(1)%ns) )
    7169                    READ ( 13 )  tmp_green_v(1)%t
    7170                 ENDIF
    7171                 CALL surface_restore_elements(                                 &
    7172                                         t_green_v(1)%t, tmp_green_v(1)%t,      &
    7173                                         surf_usm_v(1)%start_index,             &
    7174                                         start_index_on_file,                   &
    7175                                         end_index_on_file ,                    &
    7176                                         nxlc, nysc,                            &
    7177                                         nxlf, nxrf, nysf, nynf,                &
    7178                                         nys_on_file, nyn_on_file,              &
    7179                                         nxl_on_file,nxr_on_file )
    7180 #else
    71816639                IF ( k == 1 )  THEN
    71826640                   IF ( .NOT.  ALLOCATED( t_green_v_1(1)%t ) )                 &
     
    71946652                                        nys_on_file, nyn_on_file,              &
    71956653                                        nxl_on_file,nxr_on_file )
    7196 #endif
     6654
    71976655             CASE ( 't_green_v(2)' )
    7198 #if defined( __nopointer )
    7199                 IF ( k == 1 )  THEN
    7200                    IF ( .NOT.  ALLOCATED( t_green_v(2)%t ) )                   &
    7201                       ALLOCATE( t_green_v(2)%t(nzb_wall:nzt_wall+1,            &
    7202                                                1:surf_usm_v(2)%ns) )
    7203                    READ ( 13 )  tmp_green_v(2)%t
    7204                 ENDIF
    7205                 CALL surface_restore_elements(                                 &
    7206                                         t_green_v(2)%t, tmp_green_v(2)%t,      &
    7207                                         surf_usm_v(2)%start_index,             &
    7208                                         start_index_on_file,                   &
    7209                                         end_index_on_file,                     &
    7210                                         nxlc, nysc,                            &
    7211                                         nxlf, nxrf, nysf, nynf,                &
    7212                                         nys_on_file, nyn_on_file,              &
    7213                                         nxl_on_file,nxr_on_file )
    7214 #else
    72156656                IF ( k == 1 )  THEN
    72166657                   IF ( .NOT.  ALLOCATED( t_green_v_1(2)%t ) )                 &
     
    72286669                                        nys_on_file, nyn_on_file,              &
    72296670                                        nxl_on_file,nxr_on_file )
    7230 #endif
     6671
    72316672             CASE ( 't_green_v(3)' )
    7232 #if defined( __nopointer )
    7233                 IF ( k == 1 )  THEN
    7234                    IF ( .NOT.  ALLOCATED( t_green_v(3)%t ) )                   &
    7235                       ALLOCATE( t_green_v(3)%t(nzb_wall:nzt_wall+1,            &
    7236                                                1:surf_usm_v(3)%ns) )
    7237                    READ ( 13 )  tmp_green_v(3)%t
    7238                 ENDIF
    7239                 CALL surface_restore_elements(                                 &
    7240                                         t_green_v(3)%t, tmp_green_v(3)%t,      &
    7241                                         surf_usm_v(3)%start_index,             & 
    7242                                         start_index_on_file,                   &
    7243                                         end_index_on_file,                     &
    7244                                         nxlc, nysc,                            &
    7245                                         nxlf, nxrf, nysf, nynf,                &
    7246                                         nys_on_file, nyn_on_file,              &
    7247                                         nxl_on_file,nxr_on_file )
    7248 #else
    72496673                IF ( k == 1 )  THEN
    72506674                   IF ( .NOT.  ALLOCATED( t_green_v_1(3)%t ) )                 &
     
    72626686                                        nys_on_file, nyn_on_file,              &
    72636687                                        nxl_on_file,nxr_on_file )
    7264 #endif
     6688
    72656689             CASE ( 't_window_h' )
    7266 #if defined( __nopointer )
    7267                 IF ( k == 1 )  THEN
    7268                    IF ( .NOT.  ALLOCATED( t_window_h ) )                       &
    7269                       ALLOCATE( t_window_h(nzb_wall:nzt_wall+1,                &
    7270                                            1:surf_usm_h%ns) )
    7271                    READ ( 13 )  tmp_window_h
    7272                 ENDIF
    7273                 CALL surface_restore_elements(                                 &
    7274                                         t_window_h, tmp_window_h,              &
    7275                                         surf_usm_h%start_index,                &
    7276                                         start_index_on_file,                   &
    7277                                         end_index_on_file,                     &
    7278                                         nxlc, nysc,                            &
    7279                                         nxlf, nxrf, nysf, nynf,                &
    7280                                         nys_on_file, nyn_on_file,              &
    7281                                         nxl_on_file,nxr_on_file )
    7282 #else
    72836690                IF ( k == 1 )  THEN
    72846691                   IF ( .NOT.  ALLOCATED( t_window_h_1 ) )                     &
     
    72966703                                        nys_on_file, nyn_on_file,              &
    72976704                                        nxl_on_file, nxr_on_file )
    7298 #endif
     6705
    72996706             CASE ( 't_window_v(0)' )
    7300 #if defined( __nopointer )
    7301                 IF ( k == 1 )  THEN
    7302                    IF ( .NOT.  ALLOCATED( t_window_v(0)%t ) )                  &
    7303                       ALLOCATE( t_window_v(0)%t(nzb_wall:nzt_wall+1,           &
    7304                                                 1:surf_usm_v(0)%ns) )
    7305                    READ ( 13 )  tmp_window_v(0)%t
    7306                 ENDIF
    7307                 CALL surface_restore_elements(                                 &
    7308                                         t_window_v(0)%t, tmp_window_v(0)%t,    &
    7309                                         surf_usm_v(0)%start_index,             &
    7310                                         start_index_on_file,                   &
    7311                                         end_index_on_file,                     &
    7312                                         nxlc, nysc,                            &
    7313                                         nxlf, nxrf, nysf, nynf,                &
    7314                                         nys_on_file, nyn_on_file,              &
    7315                                         nxl_on_file, nxr_on_file )
    7316 #else
    73176707                IF ( k == 1 )  THEN
    73186708                   IF ( .NOT.  ALLOCATED( t_window_v_1(0)%t ) )                &
     
    73316721                                        nys_on_file, nyn_on_file,              &
    73326722                                        nxl_on_file,nxr_on_file )
    7333 #endif
     6723
    73346724             CASE ( 't_window_v(1)' )
    7335 #if defined( __nopointer )
    7336                 IF ( k == 1 )  THEN
    7337                    IF ( .NOT.  ALLOCATED( t_window_v(1)%t ) )                  &
    7338                       ALLOCATE( t_window_v(1)%t(nzb_wall:nzt_wall+1,           &
    7339                                                 1:surf_usm_v(1)%ns) )
    7340                    READ ( 13 )  tmp_window_v(1)%t
    7341                 ENDIF
    7342                 CALL surface_restore_elements(                                 &
    7343                                         t_window_v(1)%t, tmp_window_v(1)%t,    &
    7344                                         surf_usm_v(1)%start_index,             &
    7345                                         start_index_on_file,                   &
    7346                                         end_index_on_file ,                    &
    7347                                         nxlc, nysc,                            &
    7348                                         nxlf, nxrf, nysf, nynf,                &
    7349                                         nys_on_file, nyn_on_file,              &
    7350                                         nxl_on_file, nxr_on_file )
    7351 #else
    73526725                IF ( k == 1 )  THEN
    73536726                   IF ( .NOT.  ALLOCATED( t_window_v_1(1)%t ) )                &
     
    73666739                                        nys_on_file, nyn_on_file,              &
    73676740                                        nxl_on_file,nxr_on_file )
    7368 #endif
     6741
    73696742             CASE ( 't_window_v(2)' )
    7370 #if defined( __nopointer )
    7371                 IF ( k == 1 )  THEN
    7372                    IF ( .NOT.  ALLOCATED( t_window_v(2)%t ) )                  &
    7373                       ALLOCATE( t_window_v(2)%t(nzb_wall:nzt_wall+1,           &
    7374                                                 1:surf_usm_v(2)%ns) )
    7375                    READ ( 13 )  tmp_window_v(2)%t
    7376                 ENDIF
    7377                 CALL surface_restore_elements(                                 &
    7378                                         t_window_v(2)%t, tmp_window_v(2)%t,    &
    7379                                         surf_usm_v(2)%start_index,             &
    7380                                         start_index_on_file,                   &
    7381                                         end_index_on_file,                     &
    7382                                         nxlc, nysc,                            &
    7383                                         nxlf, nxrf, nysf, nynf,                &
    7384                                         nys_on_file, nyn_on_file,              &
    7385                                         nxl_on_file,nxr_on_file )
    7386 #else
    73876743                IF ( k == 1 )  THEN
    73886744                   IF ( .NOT.  ALLOCATED( t_window_v_1(2)%t ) )                &
     
    74016757                                        nys_on_file, nyn_on_file,              &
    74026758                                        nxl_on_file,nxr_on_file )
    7403 #endif
     6759
    74046760             CASE ( 't_window_v(3)' )
    7405 #if defined( __nopointer )
    7406                 IF ( k == 1 )  THEN
    7407                    IF ( .NOT.  ALLOCATED( t_window_v(3)%t ) )                  &
    7408                       ALLOCATE( t_window_v(3)%t(nzb_wall:nzt_wall+1,           &
    7409                                                 1:surf_usm_v(3)%ns) )
    7410                    READ ( 13 )  tmp_window_v(3)%t
    7411                 ENDIF
    7412                 CALL surface_restore_elements(                                 &
    7413                                         t_window_v(3)%t, tmp_window_v(3)%t,    &
    7414                                         surf_usm_v(3)%start_index,             &
    7415                                         start_index_on_file,                   &
    7416                                         end_index_on_file,                     &
    7417                                         nxlc, nysc,                            &
    7418                                         nxlf, nxrf, nysf, nynf,                &
    7419                                         nys_on_file, nyn_on_file,              &
    7420                                         nxl_on_file,nxr_on_file )
    7421 #else
    74226761                IF ( k == 1 )  THEN
    74236762                   IF ( .NOT.  ALLOCATED( t_window_v_1(3)%t ) )                &
     
    74356774                                        nys_on_file, nyn_on_file,              &
    74366775                                        nxl_on_file,nxr_on_file )
    7437 #endif
     6776
    74386777             CASE DEFAULT
    74396778
     
    76326971
    76336972           IF ( usm_par(5,jw,iw) == 0 )  THEN
    7634 #if ! defined( __nopointer )
     6973
    76356974              IF ( zu(kw) >= roof_height_limit )  THEN
    76366975                 surf_usm_h%isroof_surf(m)   = .TRUE.
     
    76406979                 surf_usm_h%surface_types(m) = land_category         !< default category for land surface
    76416980              ENDIF
    7642 #endif
     6981
    76436982              surf_usm_h%albedo(:,m)    = -1.0_wp
    76446983              surf_usm_h%thickness_wall(m) = -1.0_wp
     
    81887527              lambda_surface_green = surf_usm_h%lambda_surf_green(m)
    81897528           ENDIF
    8190 #if ! defined( __nopointer )
     7529
    81917530!            pt1  = pt(k,j,i)
    81927531           IF ( humidity )  THEN
     
    81997538           rho_cp  = c_p * hyp(k) / ( r_d * surf_usm_h%pt1(m) * exner(k) )
    82007539
    8201 if (surf_usm_h%frac(ind_pav_green,m).gt.0.0_wp) then
    8202 !
    8203 !--         Calculate frequently used parameters
    8204             rho_lv    = rho_cp / c_p * l_v
    8205             drho_l_lv = 1.0_wp / (rho_l * l_v)
    8206 endif
    8207 #endif
     7540           IF ( surf_usm_h%frac(ind_pav_green,m) > 0.0_wp )  THEN
     7541!
     7542!--           Calculate frequently used parameters
     7543              rho_lv    = rho_cp / c_p * l_v
     7544              drho_l_lv = 1.0_wp / (rho_l * l_v)
     7545           ENDIF
     7546
    82087547!
    82097548!--        Calculate aerodyamic resistance.
     
    86377976             lambda_surface_green = surf_usm_v(l)%lambda_surf_green(m)
    86387977
    8639 #if ! defined( __nopointer )         
    86407978!            pt1  = pt(k,j,i)
    86417979           IF ( humidity )  THEN
     
    86487986             rho_cp  = c_p * hyp(k) / ( r_d * surf_usm_v(l)%pt1(m) * exner(k) )
    86497987             
    8650 if (surf_usm_v(l)%frac(1,m).gt.0.0_wp) then
    8651 !
    8652 !--         Calculate frequently used parameters
    8653             rho_lv    = rho_cp / c_p * l_v
    8654             drho_l_lv = 1.0_wp / (rho_l * l_v)
    8655 endif
    8656 #endif
     7988            IF (surf_usm_v(l)%frac(1,m) > 0.0_wp )  THEN
     7989!
     7990!--            Calculate frequently used parameters
     7991               rho_lv    = rho_cp / c_p * l_v
     7992               drho_l_lv = 1.0_wp / (rho_l * l_v)
     7993            ENDIF
    86577994
    86587995!--          Calculation of r_a for vertical surfaces
     
    90538390!--     pt and shf are defined on nxlg:nxrg,nysg:nyng
    90548391!--     get the borders from neighbours
    9055 #if ! defined( __nopointer )
    90568392        CALL exchange_horiz( pt, nbgp )
    9057 #endif
    90588393
    90598394!--     calculation of force_radiation_call:
     
    91888523
    91898524       INTEGER(iwp), INTENT(IN) ::  mod_count
     8525
    91908526     
    9191 #if defined( __nopointer )
    9192        t_surf_wall_h    = t_surf_wall_h_p
    9193        t_wall_h    = t_wall_h_p
    9194        t_surf_wall_v    = t_surf_wall_v_p
    9195        t_wall_v    = t_wall_v_p
    9196        t_surf_window_h    = t_surf_window_h_p
    9197        t_window_h    = t_window_h_p
    9198        t_surf_window_v    = t_surf_window_v_p
    9199        t_window_v    = t_window_v_p
    9200        t_surf_green_h    = t_surf_green_h_p
    9201        t_surf_green_v    = t_surf_green_v_p
    9202        t_green_h    = t_green_h_p
    9203        t_green_v    = t_green_v_p
    9204 #else
    92058527       SELECT CASE ( mod_count )
     8528
    92068529          CASE ( 0 )
    92078530!
     
    92398562             t_green_v     => t_green_v_2;    t_green_v_p     => t_green_v_1
    92408563       END SELECT
    9241 #endif
    92428564       
    92438565    END SUBROUTINE usm_swap_timelevel
Note: See TracChangeset for help on using the changeset viewer.