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

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

code has been put under the GNU General Public License (v3)

  • Property svn:keywords set to Id
File size: 3.2 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 1036 2012-10-22 13:43:42Z raasch $
27! RCS Log replace by Id keyword, revision history cleaned up
28!
29! Revision 1.1  2006/02/23 10:09:29  raasch
30! Initial revision
31!
32!
33! Description:
34! ------------
35! Complete logging of data
36!------------------------------------------------------------------------------!
37#if defined( __logging )
38
39    USE control_parameters
40    USE pegrid
41
42    IMPLICIT NONE
43
44    INTEGER ::  i1, i2, j1, j2, k1, k2
45
46    REAL, DIMENSION(i1:i2,j1:j2,k1:k2) ::  array
47
48
49!
50!-- Open the file for data logging
51    CALL check_open( 20 )
52
53!
54!-- Write the message string
55    WRITE ( 20 )  log_message
56
57!
58!-- Write the simulated time and the array indices
59    WRITE ( 20 )  simulated_time, i1, i2, j1, j2, k1, k2
60
61!
62!-- Write the array
63    WRITE ( 20 )  array
64
65#endif
66 END SUBROUTINE data_log
67
68
69
70 SUBROUTINE data_log_2d( array, i1, i2, j1, j2)
71
72!------------------------------------------------------------------------------!
73! Description:
74! ------------
75! Same as above, for 2d arrays
76!------------------------------------------------------------------------------!
77#if defined( __logging )
78
79    USE control_parameters
80    USE pegrid
81
82    IMPLICIT NONE
83
84    INTEGER ::  i1, i2, j1, j2
85
86    REAL, DIMENSION(i1:i2,j1:j2) ::  array
87
88
89!
90!-- Open the file for data logging
91    CALL check_open( 20 )
92
93!
94!-- Write the message string
95    WRITE ( 20 )  log_message
96
97!
98!-- Write the simulated time and the array indices
99    WRITE ( 20 )  simulated_time, i1, i2, j1, j2
100
101!
102!-- Write the array
103    WRITE ( 20 )  array
104
105#endif
106 END SUBROUTINE data_log_2d
107
108
109
110 SUBROUTINE data_log_2d_int( array, i1, i2, j1, j2)
111
112!------------------------------------------------------------------------------!
113! Description:
114! ------------
115! Same as above, for 2d integer arrays
116!------------------------------------------------------------------------------!
117#if defined( __logging )
118
119    USE control_parameters
120    USE pegrid
121
122    IMPLICIT NONE
123
124    INTEGER ::  i1, i2, j1, j2
125
126    INTEGER, DIMENSION(i1:i2,j1:j2) ::  array
127
128
129!
130!-- Open the file for data logging
131    CALL check_open( 20 )
132
133!
134!-- Write the message string
135    WRITE ( 20 )  log_message
136
137!
138!-- Write the simulated time and the array indices
139    WRITE ( 20 )  simulated_time, i1, i2, j1, j2
140
141!
142!-- Write the array
143    WRITE ( 20 )  array
144
145#endif
146 END SUBROUTINE data_log_2d_int
Note: See TracBrowser for help on using the repository browser.