Ignore:
Timestamp:
Apr 15, 2020 2:26:31 PM (4 years ago)
Author:
raasch
Message:

bugfix for creation of filetypes, argument removed from rd_mpi_io_open, files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4360 r4498  
    11!> @file user_init_3d_model.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
    98!
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
    1312!
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
     18!
    1919!
    2020! Current revisions:
     
    2525! -----------------
    2626! $Id$
     27! file re-formatted to follow the PALM coding standard
     28!
     29!
     30! 4360 2020-01-07 11:25:50Z suehring
    2731! Corrected "Former revisions" section
    28 ! 
     32!
    2933! 3768 2019-02-27 14:35:58Z raasch
    3034! variables commented out to avoid compiler warnings about unused variables
    31 ! 
     35!
    3236! 3655 2019-01-07 16:51:22Z knoop
    3337! Corrected "Former revisions" section
     
    4246!> @attention The user is responsible to set at least all those quantities which
    4347!>            are normally set within init_3d_model!
    44 !------------------------------------------------------------------------------!
     48!--------------------------------------------------------------------------------------------------!
    4549 SUBROUTINE user_init_3d_model
    46  
     50
    4751
    4852    USE arrays_3d
    49    
     53
    5054    USE control_parameters
    51    
     55
    5256    USE indices
    53    
     57
    5458    USE kinds
    5559
    5660    USE surface_mod
    57    
     61
    5862    USE user
    5963
    6064    IMPLICIT NONE
    6165
    62 !    INTEGER(iwp) ::  l !< running index surface orientation
    63 !    INTEGER(iwp) ::  m !< running index surface elements
     66!    INTEGER(iwp) ::  l  !< running index surface orientation
     67!    INTEGER(iwp) ::  m  !< running index surface elements
    6468
    6569!
    6670!-- Initialization of surface-related quantities.
    67 !-- The following example shows required initialization of surface quantitites
    68 !-- at default-type upward-facing surfaces. 
     71!-- The following example shows required initialization of surface quantitites at default-type
     72!-- upward-facing surfaces.
    6973!   DO  m = 1, surf_def_h(0)%ns
    7074!      surf_def_h(0)%ol(m)   = ...    ! Obukhov length
     
    8791!         surf_def_h(0)%ssws(m) = ... ! surface latent heat flux
    8892!      ENDIF
    89 !   ENDDO 
     93!   ENDDO
    9094!
    9195!-- Same for natural and urban type surfaces
    9296!   DO  m = 1, surf_lsm_h%ns
    9397!      ...
    94 !   ENDDO 
     98!   ENDDO
    9599!   DO  m = 1, surf_usm_h%ns
    96100!      ...
    97101!   ENDDO
    98102!
    99 !-- Also care for vertically aligned surfaces (default-, natural-, and 
     103!-- Also care for vertically aligned surfaces (default-, natural-, and
    100104!-- urban-type).
    101105!   DO  l = 0, 3
Note: See TracChangeset for help on using the changeset viewer.