source: palm/trunk/SOURCE/print_1d.f90 @ 4180

Last change on this file since 4180 was 4180, checked in by scharf, 5 years ago

removed comments in 'Former revisions' section that are older than 01.01.2019

  • Property svn:keywords set to Id
File size: 4.9 KB
RevLine 
[1682]1!> @file print_1d.f90
[2000]2!------------------------------------------------------------------------------!
[2696]3! This file is part of the PALM model system.
[1036]4!
[2000]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.
[1036]9!
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.
13!
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/>.
16!
[3655]17! Copyright 1997-2019 Leibniz Universitaet Hannover
[2000]18!------------------------------------------------------------------------------!
[1036]19!
[484]20! Current revisions:
[1]21! -----------------
[2001]22!
23!
[1321]24! Former revisions:
25! -----------------
26! $Id: print_1d.f90 4180 2019-08-21 14:37:54Z scharf $
[3421]27! Renamed output variables
28!
[1321]29!
[1]30! Description:
31! ------------
[1682]32!> List output of 1D-profiles.
[1]33!------------------------------------------------------------------------------!
[1682]34 SUBROUTINE print_1d
35 
[1]36
[1320]37    USE arrays_3d,                                                             &
38        ONLY:  zu, zw
39
40    USE control_parameters,                                                    &
41        ONLY:  run_description_header, simulated_time_chr
42
43    USE cpulog,                                                                &
44        ONLY:  cpu_log, log_point
45
46    USE indices,                                                               &
47        ONLY:  nzb, nzt
48
49    USE kinds
50
[1]51    USE pegrid
52
[1320]53    USE statistics,                                                            &
54        ONLY:  flow_statistics_called, hom, region, statistic_regions
55
[1]56    IMPLICIT NONE
57
58
[1682]59    CHARACTER (LEN=20) ::  period_chr  !<
[1]60
[1682]61    INTEGER(iwp) ::  k   !<
62    INTEGER(iwp) ::  sr  !<
[1]63
[1320]64
[1]65!
66!-- If required, compute statistics.
67    IF ( .NOT. flow_statistics_called )  CALL flow_statistics
68
69!
70!-- Flow_statistics has its own cpu-time measuring.
71    CALL cpu_log( log_point(18), 'print_1d', 'start' )
72
73    IF ( myid == 0 )  THEN
74!
75!--    Open file for list output of profiles.
76       CALL check_open( 16 )
77
78!
79!--    Prepare header.
80       period_chr = ' no time-average!'
81
82!
83!--    Output for the total domain (and each subregion, if applicable).
84       DO  sr = 0, statistic_regions
85!
86!--       Write header.
87          WRITE ( 16, 112 )
88          WRITE ( 16, 100 )  TRIM( run_description_header ) // '    ' // &
89                             TRIM( region( sr ) ), TRIM( period_chr ), 'uv'
90          WRITE ( 16, 105 )  TRIM( simulated_time_chr )
91          WRITE ( 16, 111 )
92
93!
94!--       Output of values on the scalar levels.
95          WRITE ( 16, 120 )
96          WRITE ( 16, 111 )
97          DO  k = nzt+1, nzb, -1
98             WRITE ( 16, 121)  k, zu(k), hom(k,1,1,sr),           &
99                               hom(k,1,1,sr) - hom(k,1,5,sr),     &
100                               hom(k,1,2,sr),                     &
101                               hom(k,1,2,sr) - hom(k,1,6,sr),     &
102                               hom(k,1,4,sr),                     &
103                               hom(k,1,4,sr) - hom(k,1,7,sr),     &
104                               hom(k,1,8,sr), hom(k,1,9,sr),      &
105                               hom(k,1,10,sr), hom(k,1,11,sr), zu(k), k
106          ENDDO
107          WRITE ( 16, 111 )
108          WRITE ( 16, 120 )
109          WRITE ( 16, 111 )
110
111!
112!--       Output of values on the w-levels.
113          WRITE ( 16, 112 )
114          WRITE ( 16, 100 )  TRIM( run_description_header ) // '    ' // &
115                             TRIM( region( sr ) ), TRIM( period_chr ), 'w'
116          WRITE ( 16, 105 )  TRIM( simulated_time_chr )
117          WRITE ( 16, 111 )
118
119          WRITE ( 16, 130 )
120          WRITE ( 16, 111 )
121          DO  k = nzt+1, nzb, -1
122             WRITE ( 16, 131)  k, zw(k), hom(k,1,16,sr),            &
123                               hom(k,1,18,sr), hom(k,1,12,sr), &
124                               hom(k,1,19,sr), hom(k,1,14,sr), &
125                               hom(k,1,20,sr), zw(k), k
126          ENDDO
127          WRITE ( 16, 111 )
128          WRITE ( 16, 130 )
129          WRITE ( 16, 111 )
130
131       ENDDO
132
133    ENDIF
134
[1318]135    CALL cpu_log( log_point(18), 'print_1d', 'stop' )
[1]136
137!
138!-- Formats.
139100 FORMAT (1X,A/1X,10('-')/ &
140            ' Horizontally',A,' averaged profiles on the ',A,'-level')
141105 FORMAT (' Time: ',A)
142111 FORMAT (1X,131('-'))
143112 FORMAT (/)
[3421]144120 FORMAT ('   k     zu      u     du     v     dv     theta dtheta ', &
[1697]145            ' e      Km    Kh     l      zu      k')
[1]146121 FORMAT (1X,I4,1X,F7.1,1X,F6.2,1X,F5.2,1X,F6.2,1X,F5.2,2X,F6.2,1X,F5.2, &
[1697]147            1X,F7.4,1X,F5.2,1X,F5.2,1X,F6.2,1X,F7.1,2X,I4)
[3421]148130 FORMAT ('   k     zw       w''theta''   wtheta     w''u''       wu       ',&
[1697]149            '  w''v''       wv        zw      k')
150131 FORMAT (1X,I4,1X,F7.1,6(1X,E10.3),1X,F7.1,2X,I4)
[1]151
152
153 END SUBROUTINE print_1d
Note: See TracBrowser for help on using the repository browser.