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

Last change on this file since 2000 was 2000, checked in by knoop, 8 years ago

Forced header and separation lines into 80 columns

  • Property svn:keywords set to Id
File size: 4.5 KB
RevLine 
[1682]1!> @file data_log.f90
[2000]2!------------------------------------------------------------------------------!
[1036]3! This file is part of PALM.
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!
[1818]17! Copyright 1997-2016 Leibniz Universitaet Hannover
[2000]18!------------------------------------------------------------------------------!
[1036]19!
[484]20! Current revisions:
[1]21! -----------------
[2000]22! Forced header and separation lines into 80 columns
[1683]23!
[1321]24! Former revisions:
25! -----------------
26! $Id: data_log.f90 2000 2016-08-20 18:09:15Z knoop $
27!
[1683]28! 1682 2015-10-07 23:56:08Z knoop
29! Code annotations made doxygen readable
30!
[1321]31! 1320 2014-03-20 08:40:49Z raasch
[1320]32! ONLY-attribute added to USE-statements,
33! kind-parameters added to all INTEGER and REAL declaration statements,
34! kinds are defined in new module kinds,
35! revision history before 2012 removed,
36! comment fields (!:) to be used for variable explanations added to
37! all variable declaration statements
[1]38!
[1037]39! 1036 2012-10-22 13:43:42Z raasch
40! code put under GPL (PALM 3.9)
41!
[3]42! RCS Log replace by Id keyword, revision history cleaned up
43!
[1]44! Revision 1.1  2006/02/23 10:09:29  raasch
45! Initial revision
46!
47!
48! Description:
49! ------------
[1682]50!> Complete logging of data
[1]51!------------------------------------------------------------------------------!
[1682]52 SUBROUTINE data_log( array, i1, i2, j1, j2, k1, k2 )
53 
[1]54#if defined( __logging )
55
[1320]56    USE control_parameters,                                                    &
57        ONLY:  log_message, simulated_time
58       
59    USE kinds
60       
[1]61    USE pegrid
62
63    IMPLICIT NONE
64
[1682]65    INTEGER(iwp) ::  i1  !<
66    INTEGER(iwp) ::  i2  !<
67    INTEGER(iwp) ::  j1  !<
68    INTEGER(iwp) ::  j2  !<
69    INTEGER(iwp) ::  k1  !<
70    INTEGER(iwp) ::  k2  !<
[1]71
[1682]72    REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2) ::  array  !<
[1]73
74
75!
76!-- Open the file for data logging
77    CALL check_open( 20 )
78
79!
80!-- Write the message string
81    WRITE ( 20 )  log_message
82
83!
84!-- Write the simulated time and the array indices
85    WRITE ( 20 )  simulated_time, i1, i2, j1, j2, k1, k2
86
87!
88!-- Write the array
89    WRITE ( 20 )  array
90
91#endif
92 END SUBROUTINE data_log
93
94
95
96!------------------------------------------------------------------------------!
97! Description:
98! ------------
[1682]99!> Complete logging of data for 2d arrays
[1]100!------------------------------------------------------------------------------!
[1682]101 
102 SUBROUTINE data_log_2d( array, i1, i2, j1, j2)
103
[1]104#if defined( __logging )
105
[1320]106    USE control_parameters,                                                    &
107        ONLY:  log_message, simulated_time
108
109    USE kinds
110           
[1]111    USE pegrid
112
113    IMPLICIT NONE
114
[1682]115    INTEGER(iwp) ::  i1  !<
116    INTEGER(iwp) ::  i2  !<
117    INTEGER(iwp) ::  j1  !<
118    INTEGER(iwp) ::  j2  !<
[1]119
[1682]120    REAL(wp), DIMENSION(i1:i2,j1:j2) ::  array  !<
[1]121
122
123!
124!-- Open the file for data logging
125    CALL check_open( 20 )
126
127!
128!-- Write the message string
129    WRITE ( 20 )  log_message
130
131!
132!-- Write the simulated time and the array indices
133    WRITE ( 20 )  simulated_time, i1, i2, j1, j2
134
135!
136!-- Write the array
137    WRITE ( 20 )  array
138
139#endif
140 END SUBROUTINE data_log_2d
141
142
143
144!------------------------------------------------------------------------------!
145! Description:
146! ------------
[1682]147!> Complete logging of data for 2d integer arrays
[1]148!------------------------------------------------------------------------------!
[1682]149 
150 SUBROUTINE data_log_2d_int( array, i1, i2, j1, j2)
151
[1]152#if defined( __logging )
153
[1320]154    USE control_parameters,                                                    &
155        ONLY:  log_message, simulated_time
156
157    USE kinds
158           
[1]159    USE pegrid
160
161    IMPLICIT NONE
162
[1682]163    INTEGER(iwp) ::  i1  !<
164    INTEGER(iwp) ::  i2  !<
165    INTEGER(iwp) ::  j1  !<
166    INTEGER(iwp) ::  j2  !<
[1]167
[1682]168    INTEGER(iwp), DIMENSION(i1:i2,j1:j2) ::  array  !<
[1]169
170
171!
172!-- Open the file for data logging
173    CALL check_open( 20 )
174
175!
176!-- Write the message string
177    WRITE ( 20 )  log_message
178
179!
180!-- Write the simulated time and the array indices
181    WRITE ( 20 )  simulated_time, i1, i2, j1, j2
182
183!
184!-- Write the array
185    WRITE ( 20 )  array
186
187#endif
188 END SUBROUTINE data_log_2d_int
Note: See TracBrowser for help on using the repository browser.