Changeset 3614 for palm/trunk/SOURCE


Ignore:
Timestamp:
Dec 10, 2018 7:05:46 AM (5 years ago)
Author:
raasch
Message:

unused variables removed, abort renamed inifor_abort to avoid intrinsic problem in Fortran

Location:
palm/trunk/SOURCE
Files:
9 edited

Legend:

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

    r3593 r3614  
    2727! -----------------
    2828! $Id$
     29! unused variables removed
     30!
     31! 3593 2018-12-03 13:51:13Z kanani
    2932! Bugfix: additional tmrt_grid allocation in case bio_mrt not selected as ouput,
    3033! replace degree symbol by degree_C
     
    157160    LOGICAL ::  aver_v     = .FALSE.  !< switch: do v  averaging in this module?
    158161    LOGICAL ::  aver_w     = .FALSE.  !< switch: do w  averaging in this module?
    159     LOGICAL ::  aver_mrt   = .FALSE.  !< switch: do mrt averaging in this module?
    160162    LOGICAL ::  average_trigger_perct = .FALSE.  !< update averaged input on call to bio_perct?
    161163    LOGICAL ::  average_trigger_utci  = .FALSE.  !< update averaged input on call to bio_utci?
     
    10761078        ONLY: message_string
    10771079
    1078     USE netcdf_data_input_mod,                                                &
    1079         ONLY:  netcdf_data_input_uvem, uvem_projarea_f, uvem_radiance_f,      &
    1080                uvem_irradiance_f, uvem_integration_f, building_obstruction_f
     1080    USE netcdf_data_input_mod,                                                 &
     1081        ONLY:  netcdf_data_input_uvem
    10811082
    10821083    IMPLICIT NONE
     
    39303931
    39313932    USE indices,                                                                                                      &
    3932         ONLY:  nxlg, nxrg, nyng, nysg, nys, nyn, nxl, nxr
     3933        ONLY:  nys, nyn, nxl, nxr
    39333934   
    39343935   
     
    40344035!                                               
    40354036!                                               
    4036        DO  i = nxl, nxr    !nxlg, nxrg
    4037           DO  j = nys, nyn    !nysg, nyng
     4037       DO  i = nxl, nxr
     4038          DO  j = nys, nyn
    40384039!                   
    40394040! !--        extract obstruction from IBSET-Integer_Array ------------------'
  • palm/trunk/SOURCE/chem_photolysis_mod.f90

    r3298 r3614  
    2626! -----------------
    2727! $Id$
     28! unused variables removed
     29!
     30! 3298 2018-10-02 12:21:11Z kanani
    2831! Moved USE radiation_model_mod from MODULE section into Subroutine
    2932! in order to use constant photolysis without radiation module (forkel)
     
    136139
    137140
    138     REAL(wp) :: time_photolysis = 0.0_wp,         & !< time since last call of photolysis code
    139                 dt_photolysis = 0.0_wp,           & !< hotolysis model timestep
    140                 skip_time_do_photolysis = 0.0_wp    !< Radiation model is not called before this time
    141 
    142141    REAL(wp)     :: cosz = 0.7_wp                   !< cosine of Zenith angle (45 deg, if not specified otherwise)
    143142
  • palm/trunk/SOURCE/date_and_time_mod.f90

    r3467 r3614  
    2525! -----------------
    2626! $Id$
     27! further tabs removed
     28!
     29! 3467 2018-10-30 19:05:21Z suehring
    2730! Tabs removed
    2831!
     
    509512    SELECT CASE(TRIM(daytype_mdh))
    510513
    511                    CASE ("workday")
    512                
    513                    index_hh = nmonth+ nday + hh
    514 
    515                    CASE ("weekend")
    516                
    517                    index_hh = nmonth+ nday + nhour + hh
    518 
    519                    CASE ("holiday")
    520                
    521                    index_hh = nmonth+ nday + 2*nhour + hh
     514       CASE ("workday")
     515       
     516          index_hh = nmonth+ nday + hh
     517
     518       CASE ("weekend")
     519       
     520          index_hh = nmonth+ nday + nhour + hh
     521
     522       CASE ("holiday")
     523       
     524          index_hh = nmonth+ nday + 2*nhour + hh
     525
    522526    END SELECT
    523527
     
    566570    ELSE
    567571
    568     DO i_mon=1,index_mm
    569        
    570        sum_dd=sum_dd+days(i_mon)
    571 
    572     ENDDO
     572       DO i_mon=1,index_mm
     573
     574         sum_dd=sum_dd+days(i_mon)
     575
     576       ENDDO
    573577     
    574     index_hh=(sum_dd*nhour)+(index_dd*nhour)+(hh)
     578       index_hh=(sum_dd*nhour)+(index_dd*nhour)+(hh)
    575579
    576580    ENDIF
  • palm/trunk/SOURCE/large_scale_forcing_nudging_mod.f90

    r3428 r3614  
    2525! -----------------
    2626! $Id$
     27! unused variables removed
     28!
     29! 3428 2018-10-25 12:32:05Z gronemeier
    2730! Rename td_XXX_lpt to td_XXX_thetal
    2831!
     
    456459    SUBROUTINE lsf_init
    457460
    458        USE control_parameters,                                                 &
    459            ONLY:  bc_lr_cyc, bc_ns_cyc
    460 
    461461       IMPLICIT NONE
    462462
  • palm/trunk/SOURCE/netcdf_data_input_mod.f90

    r3560 r3614  
    2525! -----------------
    2626! $Id$
     27! unused variables removed
     28!
     29! 3560 2018-11-23 09:20:21Z raasch
    2730! Some formatting adjustment
    2831!
     
    12671270
    12681271       USE chem_modules,                                       &
    1269            ONLY:  do_emis, mode_emis, time_fac_type,           &
    1270                   surface_csflux_name
     1272           ONLY:  mode_emis, time_fac_type, surface_csflux_name
    12711273
    12721274       USE control_parameters,                                 &
     
    12741276
    12751277       USE indices,                                            &
    1276            ONLY:  nz, nx, ny, nxl, nxr, nys, nyn, nzb, nzt
     1278           ONLY:  nx, ny, nxl, nxr, nys, nyn
    12771279
    12781280       IMPLICIT NONE
     
    12811283       TYPE(chem_emis_val_type), ALLOCATABLE, DIMENSION(:), INTENT(INOUT)             :: emt
    12821284   
    1283        CHARACTER (LEN=80)                               :: units=''              !< units of chemistry inputs
    1284  
    12851285       INTEGER(iwp)                                     :: ispec                 !< index for number of emission species in input
    12861286
    1287        INTEGER(iwp), ALLOCATABLE, DIMENSION(:)          :: dum_var               !< value of variable read from netcdf input
    1288        INTEGER(iwp)                                     :: errno                 !< error number NF90_???? function
    1289        INTEGER(iwp)                                     :: id_var                !< variable id
    1290 !       INTEGER(iwp)                                     :: id_emis               !< NetCDF id of input file
    12911287       INTEGER(iwp)                                     :: num_vars              !< number of variables in netcdf input file
    1292        INTEGER(iwp)                                     :: len_dims,len_dims_2   !< Length of dimensions
    1293 
    1294        INTEGER(iwp)                                     :: max_string_length=25  !< Variable for the maximum length of a string
    1295  
    1296        CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE    :: var_names             !< Name of Variables
     1288       INTEGER(iwp)                                     :: len_dims              !< Length of dimension
    12971289
    12981290       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)          :: dum_var_3d            !< variable for storing temporary data of 3-dimensional
     
    15621554
    15631555       USE control_parameters,                                                 &
    1564            ONLY:  bc_lr_cyc, bc_ns_cyc, land_surface, plant_canopy,            &
    1565                   urban_surface
     1556           ONLY:  land_surface, plant_canopy, urban_surface
    15661557
    15671558       USE indices,                                                            &
    1568            ONLY:  nbgp, nx, nxl, nxr,ny, nyn, nys
     1559           ONLY:  nbgp, nxl, nxr, nyn, nys
    15691560
    15701561
     
    24062397
    24072398       USE control_parameters,                                                 &
    2408            ONLY:  bc_lr_cyc, bc_ns_cyc, message_string, topography
     2399           ONLY:  message_string, topography
    24092400
    24102401       USE indices,                                                            &
    2411            ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nzb
     2402           ONLY:  nbgp, nxl, nxr, ny, nyn, nys, nzb
    24122403
    24132404
  • palm/trunk/SOURCE/ocean_mod.f90

    r3568 r3614  
    2525! -----------------
    2626! $Id$
     27! unused variables removed
     28!
     29! 3568 2018-11-27 16:07:59Z raasch
    2730! bugifx: calculate equation of state for seawater even if salinity is switched
    2831!         off
     
    512515 SUBROUTINE ocean_parin
    513516
    514     USE control_parameters,                                                    &
    515         ONLY:  message_string
    516 
    517517    IMPLICIT NONE
    518518
     
    706706
    707707    USE control_parameters,                                                    &
    708         ONLY:  data_output_pr, message_string
     708        ONLY:  data_output_pr
    709709
    710710    USE indices
     
    11721172    USE indices,                                                               &
    11731173        ONLY:  nxlg, nxrg, nyng, nysg, nzb, nzt
    1174 
    1175     USE pmc_interface,                                                         &
    1176         ONLY:  nested_run
    11771174
    11781175    IMPLICIT NONE
     
    21602157
    21612158    USE indices,                                                               &
    2162         ONLY:  nxl, nxr, nys, nysv, nyn, nzb, nzt
     2159        ONLY:  nzb, nzt
    21632160
    21642161    IMPLICIT NONE
  • palm/trunk/SOURCE/plant_canopy_model_mod.f90

    r3589 r3614  
    2727! -----------------
    2828! $Id$
     29! unused variables removed
     30!
     31! 3589 2018-11-30 15:09:51Z suehring
    2932! Formatting adjustments
    3033!
     
    879882
    880883       USE control_parameters,                                                 &
    881            ONLY: message_string, ocean_mode, urban_surface
     884           ONLY: message_string, ocean_mode
    882885
    883886       USE netcdf_data_input_mod,                                              &
  • palm/trunk/SOURCE/surface_output_mod.f90

    r3572 r3614  
    2525! -----------------
    2626! $Id$
     27! unused variables removed
     28!
     29! 3572 2018-11-28 11:40:28Z suehring
    2730! Added short- and longwave radiation flux arrays (e.g. diffuse, direct,
    2831! reflected, resedual) for all surfaces (M. Salim)
     
    166169
    167170      INTEGER(iwp) ::  i                 !< grid index in x-direction, also running variable for counting non-average data output
    168       INTEGER(iwp) ::  ilen              !< string length
    169171      INTEGER(iwp) ::  j                 !< grid index in y-direction, also running variable for counting average data output
    170172      INTEGER(iwp) ::  k                 !< grid index in z-direction
    171173      INTEGER(iwp) ::  l                 !< running index for surface-element orientation
    172174      INTEGER(iwp) ::  m                 !< running index for surface elements
    173       INTEGER(iwp) ::  n_out             !< running index for number of output variables   
    174175      INTEGER(iwp) ::  npg               !< counter variable for all surface elements ( or polygons )
    175176      INTEGER(iwp) ::  point_index_count !< local counter variable for point index
     
    875876      INTEGER(iwp) ::  av     !< id indicating average or non-average data output
    876877      INTEGER(iwp) ::  i      !< loop index
    877       INTEGER(iwp) ::  l      !< running index for surface-element orientation
    878       INTEGER(iwp) ::  m      !< running index for surface elements
    879878      INTEGER(iwp) ::  n_out  !< counter variables for surface output
    880879
     
    22642263      CHARACTER(LEN=100) ::  trimvar !< dummy variable for current output variable
    22652264       
    2266       INTEGER(iwp) ::  l      !< running index for surface-element orientation
    2267       INTEGER(iwp) ::  m      !< running index for surface elements
    22682265      INTEGER(iwp) ::  n_out  !< counter variables for surface output
    22692266     
     
    35133510    SUBROUTINE surface_output_parin
    35143511
    3515        USE control_parameters,                                                 &
    3516            ONLY:  message_string
    3517 
    35183512       IMPLICIT NONE
    35193513
     
    35653559
    35663560       USE control_parameters,                                                 &
    3567            ONLY:  averaging_interval, dt_data_output, dt_data_output_av,       &
    3568                   message_string, skip_time_data_output,                       &
    3569                   skip_time_data_output_av
     3561           ONLY:  averaging_interval, dt_data_output, message_string
    35703562
    35713563       IMPLICIT NONE
  • palm/trunk/SOURCE/urban_surface_mod.f90

    r3607 r3614  
    2828! -----------------
    2929! $Id$
     30! unused variables removed
     31!
     32! 3607 2018-12-07 11:56:58Z suehring
    3033! Output of radiation-related quantities migrated to radiation_model_mod.
    3134!
     
    960963
    961964
    962 !-- arrays for time averages
    963 !-- Attention: the variable rad_net_av is also used in the 3d field variable in radiation_model_mod.f90. It may be better to rename it
    964     REAL(wp), DIMENSION(:), ALLOCATABLE            ::  wghf_eb_av       !< average of wghf_eb
    965     REAL(wp), DIMENSION(:), ALLOCATABLE            ::  wshf_eb_av       !< average of wshf_eb
    966     REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  t_wall_av        !< Average of t_wall
    967     REAL(wp), DIMENSION(:), ALLOCATABLE            ::  wghf_eb_green_av !< average of wghf_eb_green
    968     REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  t_green_av       !< Average of t_green
    969     REAL(wp), DIMENSION(:), ALLOCATABLE            ::  wghf_eb_window_av !< average of wghf_eb_window
    970     REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  t_window_av      !< Average of t_window
    971     REAL(wp), DIMENSION(:), ALLOCATABLE            ::  qsws_eb_av       !< average of qsws_eb
    972     REAL(wp), DIMENSION(:), ALLOCATABLE            ::  qsws_veg_av   !< average of qsws_veg
    973     REAL(wp), DIMENSION(:), ALLOCATABLE            ::  qsws_liq_av   !< average of qsws_liq
    974     REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  swc_av        !< Average of swc
    975    
    976 
    977965!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    978966!-- anthropogenic heat sources
     
    10611049   
    10621050#endif
    1063     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_wall_av          !< average of wall surface temperature (K)
    1064     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_av   !< average of window surface temperature (K)
    1065     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_av    !< average of green wall surface temperature (K)
    1066 
    1067 !-- Temporal tendencies for time stepping           
    1068     REAL(wp), DIMENSION(:), ALLOCATABLE            :: tt_surface_wall_m       !< surface temperature tendency of wall (K)
    1069     REAL(wp), DIMENSION(:), ALLOCATABLE            :: tt_surface_window_m !< surface temperature tendency of window (K)
    1070     REAL(wp), DIMENSION(:), ALLOCATABLE            :: tt_surface_green_m !< surface temperature tendency of green wall (K)
    10711051
    10721052!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    10771057#if defined( __nopointer )
    10781058    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h             !< Wall temperature (K)
    1079     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_av          !< Average of t_wall
    10801059    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_p           !< Prog. wall temperature (K)
    10811060    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h           !< Window temperature (K)
    1082     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_av        !< Average of t_window
    10831061    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_p         !< Prog. window temperature (K)
    10841062    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h            !< Green temperature (K)
    1085     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_av         !< Average of t_green
    10861063    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_p          !< Prog. green temperature (K)
    10871064    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h              !< soil water content green building layer
     
    10961073
    10971074    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v             !< Wall temperature (K)
    1098     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_av          !< Average of t_wall
    10991075    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_p           !< Prog. wall temperature (K)
    11001076    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v           !< Window temperature (K)
    1101     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_av        !< Average of t_window
    11021077    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_p         !< Prog. window temperature (K)
    11031078    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v            !< Green temperature (K)
    1104     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_av         !< Average of t_green
    11051079    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_p          !< Prog. green temperature (K)
    11061080    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v             !< Wall swc
    1107     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_av          !< Average of swc
    11081081    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_p           !< Prog. swc
    11091082   
    11101083#else
    11111084    REAL(wp), DIMENSION(:,:), POINTER                :: t_wall_h, t_wall_h_p
    1112     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_av, t_wall_h_1, t_wall_h_2
     1085    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_1, t_wall_h_2
    11131086    REAL(wp), DIMENSION(:,:), POINTER                :: t_window_h, t_window_h_p
    1114     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_av, t_window_h_1, t_window_h_2
     1087    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_1, t_window_h_2
    11151088    REAL(wp), DIMENSION(:,:), POINTER                :: t_green_h, t_green_h_p
    1116     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_av, t_green_h_1, t_green_h_2
     1089    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_1, t_green_h_2
    11171090    REAL(wp), DIMENSION(:,:), POINTER                :: swc_h, rootfr_h, wilt_h, fc_h, swc_sat_h, swc_h_p, swc_res_h
    11181091    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: swc_h_1, rootfr_h_1, &
     
    11211094
    11221095    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_wall_v, t_wall_v_p
    1123     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_av, t_wall_v_1, t_wall_v_2
     1096    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_1, t_wall_v_2
    11241097    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_window_v, t_window_v_p
    1125     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_av, t_window_v_1, t_window_v_2
     1098    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_1, t_window_v_2
    11261099    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_green_v, t_green_v_p
    1127     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_av, t_green_v_1, t_green_v_2
     1100    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_1, t_green_v_2
    11281101    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: swc_v, swc_v_p
    1129     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_av, swc_v_1, swc_v_2
     1102    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_1, swc_v_2
    11301103#endif
    1131 
    1132 !-- Wall temporal tendencies for time stepping
    1133     REAL(wp), DIMENSION(:,:), ALLOCATABLE          :: tt_wall_m          !< t_wall prognostic array
    1134     REAL(wp), DIMENSION(:,:), ALLOCATABLE          :: tt_window_m        !< t_window prognostic array
    1135     REAL(wp), DIMENSION(:,:), ALLOCATABLE          :: tt_green_m         !< t_green prognostic array
    11361104
    11371105!-- Surface and material parameters classes (surface_type)
     
    28502818        REAL(wp), DIMENSION(nzb:nzt+1,nys:nyn,nxl:nxr)     ::  temp_pf    !< temp array for urban surface output procedure
    28512819       
    2852         CHARACTER (len=varnamelength)                          :: var, surfid
     2820        CHARACTER (len=varnamelength)                          :: var
    28532821        INTEGER(iwp), PARAMETER                                :: nd = 5
    28542822        CHARACTER(len=6), DIMENSION(0:nd-1), PARAMETER         :: dirname = (/ '_roof ', '_south', '_north', '_west ', '_east ' /)
     
    28562824        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER             :: diridx =  (/       -1,        1,        0,        3,        2 /)
    28572825                                                                     !< index for surf_*_v: 0:3 = (North, South, East, West)
    2858         INTEGER(iwp)                                           :: ids,idsint,idsidx,isurf,isvf,isurfs,isurflt,ipcgb
    2859         INTEGER(iwp)                                           :: is,js,ks,i,j,k,iwl,istat, l, m
     2826        INTEGER(iwp)                                           :: ids,idsint,idsidx,isvf
     2827        INTEGER(iwp)                                           :: i,j,k,iwl,istat, l, m
    28602828
    28612829        found = .TRUE.
     
    74997467        INTEGER(iwp), DIMENSION(0:17, nysg:nyng, nxlg:nxrg)   :: usm_par
    75007468        REAL(wp), DIMENSION(1:14, nysg:nyng, nxlg:nxrg)       :: usm_val
    7501         INTEGER(iwp)                                          :: k, l, d, iw, jw, kw, it, ip, ii, ij, m
     7469        INTEGER(iwp)                                          :: k, l, iw, jw, kw, it, ip, ii, ij, m
    75027470        INTEGER(iwp)                                          :: i, j
    75037471        INTEGER(iwp)                                          :: nz, roof, dirwe, dirsn
     
    81458113        IMPLICIT NONE
    81468114
    8147         INTEGER(iwp)                          :: i, j, k, l, d, m   !< running indices
     8115        INTEGER(iwp)                          :: i, j, k, l, m   !< running indices
    81488116       
    81498117        INTEGER(iwp) ::  i_off     !< offset to determine index of surface element, seen from atmospheric grid point, for x
     
    81538121        LOGICAL                               :: spinup             !true during spinup
    81548122       
    8155         REAL(wp)                              :: u1,v1,w1           !< near wall u,v,w
    81568123        REAL(wp)                              :: stend_wall              !< surface tendency
    81578124       
Note: See TracChangeset for help on using the changeset viewer.