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

Last change on this file since 1682 was 1682, checked in by knoop, 9 years ago

Code annotations made doxygen readable

  • Property svn:keywords set to Id
File size: 4.4 KB
Line 
1!> @file data_log.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2014 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21! Code annotations made doxygen readable
22!
23! Former revisions:
24! -----------------
25! $Id: data_log.f90 1682 2015-10-07 23:56:08Z knoop $
26!
27! 1320 2014-03-20 08:40:49Z raasch
28! ONLY-attribute added to USE-statements,
29! kind-parameters added to all INTEGER and REAL declaration statements,
30! kinds are defined in new module kinds,
31! revision history before 2012 removed,
32! comment fields (!:) to be used for variable explanations added to
33! all variable declaration statements
34!
35! 1036 2012-10-22 13:43:42Z raasch
36! code put under GPL (PALM 3.9)
37!
38! RCS Log replace by Id keyword, revision history cleaned up
39!
40! Revision 1.1  2006/02/23 10:09:29  raasch
41! Initial revision
42!
43!
44! Description:
45! ------------
46!> Complete logging of data
47!------------------------------------------------------------------------------!
48 SUBROUTINE data_log( array, i1, i2, j1, j2, k1, k2 )
49 
50#if defined( __logging )
51
52    USE control_parameters,                                                    &
53        ONLY:  log_message, simulated_time
54       
55    USE kinds
56       
57    USE pegrid
58
59    IMPLICIT NONE
60
61    INTEGER(iwp) ::  i1  !<
62    INTEGER(iwp) ::  i2  !<
63    INTEGER(iwp) ::  j1  !<
64    INTEGER(iwp) ::  j2  !<
65    INTEGER(iwp) ::  k1  !<
66    INTEGER(iwp) ::  k2  !<
67
68    REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2) ::  array  !<
69
70
71!
72!-- Open the file for data logging
73    CALL check_open( 20 )
74
75!
76!-- Write the message string
77    WRITE ( 20 )  log_message
78
79!
80!-- Write the simulated time and the array indices
81    WRITE ( 20 )  simulated_time, i1, i2, j1, j2, k1, k2
82
83!
84!-- Write the array
85    WRITE ( 20 )  array
86
87#endif
88 END SUBROUTINE data_log
89
90
91
92!------------------------------------------------------------------------------!
93! Description:
94! ------------
95!> Complete logging of data for 2d arrays
96!------------------------------------------------------------------------------!
97 
98 SUBROUTINE data_log_2d( array, i1, i2, j1, j2)
99
100#if defined( __logging )
101
102    USE control_parameters,                                                    &
103        ONLY:  log_message, simulated_time
104
105    USE kinds
106           
107    USE pegrid
108
109    IMPLICIT NONE
110
111    INTEGER(iwp) ::  i1  !<
112    INTEGER(iwp) ::  i2  !<
113    INTEGER(iwp) ::  j1  !<
114    INTEGER(iwp) ::  j2  !<
115
116    REAL(wp), DIMENSION(i1:i2,j1:j2) ::  array  !<
117
118
119!
120!-- Open the file for data logging
121    CALL check_open( 20 )
122
123!
124!-- Write the message string
125    WRITE ( 20 )  log_message
126
127!
128!-- Write the simulated time and the array indices
129    WRITE ( 20 )  simulated_time, i1, i2, j1, j2
130
131!
132!-- Write the array
133    WRITE ( 20 )  array
134
135#endif
136 END SUBROUTINE data_log_2d
137
138
139
140!------------------------------------------------------------------------------!
141! Description:
142! ------------
143!> Complete logging of data for 2d integer arrays
144!------------------------------------------------------------------------------!
145 
146 SUBROUTINE data_log_2d_int( array, i1, i2, j1, j2)
147
148#if defined( __logging )
149
150    USE control_parameters,                                                    &
151        ONLY:  log_message, simulated_time
152
153    USE kinds
154           
155    USE pegrid
156
157    IMPLICIT NONE
158
159    INTEGER(iwp) ::  i1  !<
160    INTEGER(iwp) ::  i2  !<
161    INTEGER(iwp) ::  j1  !<
162    INTEGER(iwp) ::  j2  !<
163
164    INTEGER(iwp), DIMENSION(i1:i2,j1:j2) ::  array  !<
165
166
167!
168!-- Open the file for data logging
169    CALL check_open( 20 )
170
171!
172!-- Write the message string
173    WRITE ( 20 )  log_message
174
175!
176!-- Write the simulated time and the array indices
177    WRITE ( 20 )  simulated_time, i1, i2, j1, j2
178
179!
180!-- Write the array
181    WRITE ( 20 )  array
182
183#endif
184 END SUBROUTINE data_log_2d_int
Note: See TracBrowser for help on using the repository browser.