source: palm/trunk/SOURCE/data_log.f90 @ 4281

Last change on this file since 4281 was 4182, checked in by scharf, 5 years ago
  • corrected "Former revisions" section
  • minor formatting in "Former revisions" section
  • added "Author" section
  • Property svn:keywords set to Id
File size: 4.0 KB
RevLine 
[1682]1!> @file data_log.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! -----------------
[1683]22!
[2001]23!
[1321]24! Former revisions:
25! -----------------
26! $Id: data_log.f90 4182 2019-08-22 15:20:23Z schwenkel $
[4182]27! Corrected "Former revisions" section
28!
29! 3725 2019-02-07 10:11:02Z raasch
[3725]30! preprocessor directives removed to avoid compiler warnings
31!
32! 3655 2019-01-07 16:51:22Z knoop
[2716]33! Corrected "Former revisions" section
[1321]34!
[4182]35! Revision 1.1  2006/02/23 10:09:29  raasch
36! Initial revision
37!
38!
[1]39! Description:
40! ------------
[1682]41!> Complete logging of data
[1]42!------------------------------------------------------------------------------!
[1682]43 SUBROUTINE data_log( array, i1, i2, j1, j2, k1, k2 )
44 
[1320]45    USE control_parameters,                                                    &
46        ONLY:  log_message, simulated_time
47       
48    USE kinds
49       
[1]50    USE pegrid
51
52    IMPLICIT NONE
53
[1682]54    INTEGER(iwp) ::  i1  !<
55    INTEGER(iwp) ::  i2  !<
56    INTEGER(iwp) ::  j1  !<
57    INTEGER(iwp) ::  j2  !<
58    INTEGER(iwp) ::  k1  !<
59    INTEGER(iwp) ::  k2  !<
[1]60
[1682]61    REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2) ::  array  !<
[1]62
63
64!
65!-- Open the file for data logging
66    CALL check_open( 20 )
67
68!
69!-- Write the message string
70    WRITE ( 20 )  log_message
71
72!
73!-- Write the simulated time and the array indices
74    WRITE ( 20 )  simulated_time, i1, i2, j1, j2, k1, k2
75
76!
77!-- Write the array
78    WRITE ( 20 )  array
79
80 END SUBROUTINE data_log
81
82
83
84!------------------------------------------------------------------------------!
85! Description:
86! ------------
[1682]87!> Complete logging of data for 2d arrays
[1]88!------------------------------------------------------------------------------!
[1682]89 
90 SUBROUTINE data_log_2d( array, i1, i2, j1, j2)
91
[1320]92    USE control_parameters,                                                    &
93        ONLY:  log_message, simulated_time
94
95    USE kinds
96           
[1]97    USE pegrid
98
99    IMPLICIT NONE
100
[1682]101    INTEGER(iwp) ::  i1  !<
102    INTEGER(iwp) ::  i2  !<
103    INTEGER(iwp) ::  j1  !<
104    INTEGER(iwp) ::  j2  !<
[1]105
[1682]106    REAL(wp), DIMENSION(i1:i2,j1:j2) ::  array  !<
[1]107
108
109!
110!-- Open the file for data logging
111    CALL check_open( 20 )
112
113!
114!-- Write the message string
115    WRITE ( 20 )  log_message
116
117!
118!-- Write the simulated time and the array indices
119    WRITE ( 20 )  simulated_time, i1, i2, j1, j2
120
121!
122!-- Write the array
123    WRITE ( 20 )  array
124
125 END SUBROUTINE data_log_2d
126
127
128
129!------------------------------------------------------------------------------!
130! Description:
131! ------------
[1682]132!> Complete logging of data for 2d integer arrays
[1]133!------------------------------------------------------------------------------!
[1682]134 
135 SUBROUTINE data_log_2d_int( array, i1, i2, j1, j2)
136
[1320]137    USE control_parameters,                                                    &
138        ONLY:  log_message, simulated_time
139
140    USE kinds
141           
[1]142    USE pegrid
143
144    IMPLICIT NONE
145
[1682]146    INTEGER(iwp) ::  i1  !<
147    INTEGER(iwp) ::  i2  !<
148    INTEGER(iwp) ::  j1  !<
149    INTEGER(iwp) ::  j2  !<
[1]150
[1682]151    INTEGER(iwp), DIMENSION(i1:i2,j1:j2) ::  array  !<
[1]152
153
154!
155!-- Open the file for data logging
156    CALL check_open( 20 )
157
158!
159!-- Write the message string
160    WRITE ( 20 )  log_message
161
162!
163!-- Write the simulated time and the array indices
164    WRITE ( 20 )  simulated_time, i1, i2, j1, j2
165
166!
167!-- Write the array
168    WRITE ( 20 )  array
169
170 END SUBROUTINE data_log_2d_int
Note: See TracBrowser for help on using the repository browser.