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

Last change on this file since 1305 was 1037, checked in by raasch, 11 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 3.3 KB
Line 
1 SUBROUTINE data_log( array, i1, i2, j1, j2, k1, k2 )
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
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!
17! Copyright 1997-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: data_log.f90 1037 2012-10-22 14:10:22Z raasch $
27!
28! 1036 2012-10-22 13:43:42Z raasch
29! code put under GPL (PALM 3.9)
30!
31! RCS Log replace by Id keyword, revision history cleaned up
32!
33! Revision 1.1  2006/02/23 10:09:29  raasch
34! Initial revision
35!
36!
37! Description:
38! ------------
39! Complete logging of data
40!------------------------------------------------------------------------------!
41#if defined( __logging )
42
43    USE control_parameters
44    USE pegrid
45
46    IMPLICIT NONE
47
48    INTEGER ::  i1, i2, j1, j2, k1, k2
49
50    REAL, DIMENSION(i1:i2,j1:j2,k1:k2) ::  array
51
52
53!
54!-- Open the file for data logging
55    CALL check_open( 20 )
56
57!
58!-- Write the message string
59    WRITE ( 20 )  log_message
60
61!
62!-- Write the simulated time and the array indices
63    WRITE ( 20 )  simulated_time, i1, i2, j1, j2, k1, k2
64
65!
66!-- Write the array
67    WRITE ( 20 )  array
68
69#endif
70 END SUBROUTINE data_log
71
72
73
74 SUBROUTINE data_log_2d( array, i1, i2, j1, j2)
75
76!------------------------------------------------------------------------------!
77! Description:
78! ------------
79! Same as above, for 2d arrays
80!------------------------------------------------------------------------------!
81#if defined( __logging )
82
83    USE control_parameters
84    USE pegrid
85
86    IMPLICIT NONE
87
88    INTEGER ::  i1, i2, j1, j2
89
90    REAL, DIMENSION(i1:i2,j1:j2) ::  array
91
92
93!
94!-- Open the file for data logging
95    CALL check_open( 20 )
96
97!
98!-- Write the message string
99    WRITE ( 20 )  log_message
100
101!
102!-- Write the simulated time and the array indices
103    WRITE ( 20 )  simulated_time, i1, i2, j1, j2
104
105!
106!-- Write the array
107    WRITE ( 20 )  array
108
109#endif
110 END SUBROUTINE data_log_2d
111
112
113
114 SUBROUTINE data_log_2d_int( array, i1, i2, j1, j2)
115
116!------------------------------------------------------------------------------!
117! Description:
118! ------------
119! Same as above, for 2d integer arrays
120!------------------------------------------------------------------------------!
121#if defined( __logging )
122
123    USE control_parameters
124    USE pegrid
125
126    IMPLICIT NONE
127
128    INTEGER ::  i1, i2, j1, j2
129
130    INTEGER, DIMENSION(i1:i2,j1:j2) ::  array
131
132
133!
134!-- Open the file for data logging
135    CALL check_open( 20 )
136
137!
138!-- Write the message string
139    WRITE ( 20 )  log_message
140
141!
142!-- Write the simulated time and the array indices
143    WRITE ( 20 )  simulated_time, i1, i2, j1, j2
144
145!
146!-- Write the array
147    WRITE ( 20 )  array
148
149#endif
150 END SUBROUTINE data_log_2d_int
Note: See TracBrowser for help on using the repository browser.