source: palm/trunk/SOURCE/wrd_write_string.f90 @ 4540

Last change on this file since 4540 was 4489, checked in by raasch, 4 years ago

files re-formatted to follow the PALM coding standard

  • Property svn:keywords set to Id
File size: 1.9 KB
Line 
1!> @file wrd_write_string.f90
2!--------------------------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2020 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: wrd_write_string.f90 4489 2020-04-04 10:54:08Z raasch $
26! file re-formatted to follow the PALM coding standard
27!
28! 4360 2020-01-07 11:25:50Z suehring
29! Initial revision
30!
31!
32! Description:
33! ------------
34!> Calculates length of string and write the respective value together with the string into binary
35!  file(s) for restart runs
36!--------------------------------------------------------------------------------------------------!
37
38 SUBROUTINE wrd_write_string( string )
39
40
41    USE kinds
42
43
44    IMPLICIT NONE
45
46    CHARACTER(LEN=*), INTENT(IN) ::  string  !< for storing strings in case of writing/reading
47                                             !< restart data
48    INTEGER(iwp) ::  length  !< integer that specifies the length of a string in case of
49                             !< writing/reading restart data
50
51
52    length = LEN_TRIM( string )
53
54    WRITE ( 14 )  length
55    WRITE ( 14 )  string(1:length)
56
57
58 END SUBROUTINE wrd_write_string
Note: See TracBrowser for help on using the repository browser.