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

nopointer option removed

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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
Note: See TracChangeset for help on using the changeset viewer.