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

nopointer option removed

File:
1 edited

Legend:

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