Ignore:
Timestamp:
Aug 25, 2020 12:11:17 PM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4360 r4649  
    11!> @file print_1d.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:
    2121! -----------------
    22 ! 
    23 ! 
     22!
     23!
    2424! Former 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! 3655 2019-01-07 16:51:22Z knoop
    3034! Renamed output variables
     
    3337! Initial revision
    3438!
    35 !
     39!--------------------------------------------------------------------------------------------------!
    3640! Description:
    3741! ------------
    3842!> List output of 1D-profiles.
    39 !------------------------------------------------------------------------------!
     43!--------------------------------------------------------------------------------------------------!
    4044 SUBROUTINE print_1d
    41  
    4245
    43     USE arrays_3d,                                                             &
    44         ONLY:  zu, zw
    4546
    46     USE control_parameters,                                                    &
    47         ONLY:  run_description_header, simulated_time_chr
     47    USE arrays_3d,                                                                                 &
     48        ONLY:  zu,                                                                                 &
     49               zw
    4850
    49     USE cpulog,                                                                &
    50         ONLY:  cpu_log, log_point
     51    USE control_parameters,                                                                        &
     52        ONLY:  run_description_header,                                                             &
     53               simulated_time_chr
    5154
    52     USE indices,                                                               &
    53         ONLY:  nzb, nzt
     55    USE cpulog,                                                                                    &
     56        ONLY:  cpu_log,                                                                            &
     57               log_point
     58
     59    USE indices,                                                                                   &
     60        ONLY:  nzb,                                                                                &
     61               nzt
    5462
    5563    USE kinds
     
    5765    USE pegrid
    5866
    59     USE statistics,                                                            &
    60         ONLY:  flow_statistics_called, hom, region, statistic_regions
     67    USE statistics,                                                                                &
     68        ONLY:  flow_statistics_called,                                                             &
     69               hom,                                                                                &
     70               region,                                                                             &
     71               statistic_regions
    6172
    6273    IMPLICIT NONE
    6374
    6475
    65     CHARACTER (LEN=20) ::  period_chr  !<
     76    CHARACTER(LEN=20) ::  period_chr  !<
    6677
    6778    INTEGER(iwp) ::  k   !<
     
    91102!
    92103!--       Write header.
    93           WRITE ( 16, 112 )
    94           WRITE ( 16, 100 )  TRIM( run_description_header ) // '    ' // &
    95                              TRIM( region( sr ) ), TRIM( period_chr ), 'uv'
    96           WRITE ( 16, 105 )  TRIM( simulated_time_chr )
    97           WRITE ( 16, 111 )
     104          WRITE( 16, 112 )
     105          WRITE( 16, 100 )  TRIM( run_description_header ) // '    ' //                            &
     106                            TRIM( region( sr ) ), TRIM( period_chr ), 'uv'
     107          WRITE( 16, 105 )  TRIM( simulated_time_chr )
     108          WRITE( 16, 111 )
    98109
    99110!
    100111!--       Output of values on the scalar levels.
    101           WRITE ( 16, 120 )
    102           WRITE ( 16, 111 )
     112          WRITE( 16, 120 )
     113          WRITE( 16, 111 )
    103114          DO  k = nzt+1, nzb, -1
    104              WRITE ( 16, 121)  k, zu(k), hom(k,1,1,sr),           &
    105                                hom(k,1,1,sr) - hom(k,1,5,sr),     &
    106                                hom(k,1,2,sr),                     &
    107                                hom(k,1,2,sr) - hom(k,1,6,sr),     &
    108                                hom(k,1,4,sr),                     &
    109                                hom(k,1,4,sr) - hom(k,1,7,sr),     &
    110                                hom(k,1,8,sr), hom(k,1,9,sr),      &
    111                                hom(k,1,10,sr), hom(k,1,11,sr), zu(k), k
     115             WRITE( 16, 121)  k, zu(k), hom(k,1,1,sr), hom(k,1,1,sr) - hom(k,1,5,sr),              &
     116                              hom(k,1,2,sr), hom(k,1,2,sr) - hom(k,1,6,sr), hom(k,1,4,sr),         &
     117                              hom(k,1,4,sr) - hom(k,1,7,sr), hom(k,1,8,sr), hom(k,1,9,sr),         &
     118                              hom(k,1,10,sr), hom(k,1,11,sr), zu(k), k
    112119          ENDDO
    113           WRITE ( 16, 111 )
    114           WRITE ( 16, 120 )
    115           WRITE ( 16, 111 )
     120          WRITE( 16, 111 )
     121          WRITE( 16, 120 )
     122          WRITE( 16, 111 )
    116123
    117124!
    118125!--       Output of values on the w-levels.
    119           WRITE ( 16, 112 )
    120           WRITE ( 16, 100 )  TRIM( run_description_header ) // '    ' // &
    121                              TRIM( region( sr ) ), TRIM( period_chr ), 'w'
    122           WRITE ( 16, 105 )  TRIM( simulated_time_chr )
    123           WRITE ( 16, 111 )
     126          WRITE( 16, 112 )
     127          WRITE( 16, 100 )  TRIM( run_description_header ) // '    ' //                            &
     128                            TRIM( region( sr ) ), TRIM( period_chr ), 'w'
     129          WRITE( 16, 105 )  TRIM( simulated_time_chr )
     130          WRITE( 16, 111 )
    124131
    125           WRITE ( 16, 130 )
    126           WRITE ( 16, 111 )
     132          WRITE( 16, 130 )
     133          WRITE( 16, 111 )
    127134          DO  k = nzt+1, nzb, -1
    128              WRITE ( 16, 131)  k, zw(k), hom(k,1,16,sr),            &
    129                                hom(k,1,18,sr), hom(k,1,12,sr), &
    130                                hom(k,1,19,sr), hom(k,1,14,sr), &
    131                                hom(k,1,20,sr), zw(k), k
     135             WRITE( 16, 131)  k, zw(k), hom(k,1,16,sr), hom(k,1,18,sr), hom(k,1,12,sr),            &
     136                              hom(k,1,19,sr), hom(k,1,14,sr), hom(k,1,20,sr), zw(k), k
    132137          ENDDO
    133           WRITE ( 16, 111 )
    134           WRITE ( 16, 130 )
    135           WRITE ( 16, 111 )
     138          WRITE( 16, 111 )
     139          WRITE( 16, 130 )
     140          WRITE( 16, 111 )
    136141
    137142       ENDDO
     
    143148!
    144149!-- Formats.
    145 100 FORMAT (1X,A/1X,10('-')/ &
    146             ' Horizontally',A,' averaged profiles on the ',A,'-level')
    147 105 FORMAT (' Time: ',A)
    148 111 FORMAT (1X,131('-'))
    149 112 FORMAT (/)
    150 120 FORMAT ('   k     zu      u     du     v     dv     theta dtheta ', &
    151             ' e      Km    Kh     l      zu      k')
    152 121 FORMAT (1X,I4,1X,F7.1,1X,F6.2,1X,F5.2,1X,F6.2,1X,F5.2,2X,F6.2,1X,F5.2, &
    153             1X,F7.4,1X,F5.2,1X,F5.2,1X,F6.2,1X,F7.1,2X,I4)
    154 130 FORMAT ('   k     zw       w''theta''   wtheta     w''u''       wu       ',&
    155             '  w''v''       wv        zw      k')
    156 131 FORMAT (1X,I4,1X,F7.1,6(1X,E10.3),1X,F7.1,2X,I4)
     150100 FORMAT( 1X, A / 1X, 10( '-' ) / ' Horizontally', A, ' averaged profiles on the ', A, '-level' )
     151105 FORMAT( ' Time: ', A )
     152111 FORMAT( 1X, 131( '-' ) )
     153112 FORMAT( / )
     154120 FORMAT( '   k     zu      u     du     v     dv     theta dtheta ',                            &
     155            ' e      Km    Kh     l    zu      k' )
     156121 FORMAT( 1X, I4, 1X, F7.1, 1X, F6.2, 1X, F5.2, 1X, F6.2, 1X, F5.2, 2X, F6.2, 1X, F5.2, 1X,      &
     157            F7.4, 1X, F5.2, 1X, F5.2, 1X, F6.2, 1X, F7.1, 2X, I4 )
     158130 FORMAT( '   k     zw       w''theta''   wtheta     w''u''       wu       ',                    &
     159            '  w''v''       wv        zw      k' )
     160131 FORMAT( 1X, I4, 1X, F7.1, 6( 1X, E10.3 ), 1X, F7.1, 2X, I4 )
    157161
    158162
Note: See TracChangeset for help on using the changeset viewer.