source: palm/tags/release-3.10/SOURCE/local_getenv.f90 @ 3901

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

last commit documented

  • Property svn:keywords set to Id
File size: 2.3 KB
Line 
1 SUBROUTINE local_getenv( var, ivar, value, ivalue )
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: local_getenv.f90 1037 2012-10-22 14:10:22Z suehring $
27!
28! 1036 2012-10-22 13:43:42Z raasch
29! code put under GPL (PALM 3.9)
30!
31! 82 2007-04-16 15:40:52Z raasch
32! Preprocessor directives for old systems removed
33!
34! RCS Log replace by Id keyword, revision history cleaned up
35!
36! Revision 1.5  2003/05/09 14:37:07  raasch
37! On the MUK cluster, only PE0 is able to read environment variables.
38! Therefore, they have to be communicated via broadcast to the other PEs.
39!
40! Revision 1.1  1997/08/11 06:21:01  raasch
41! Initial revision
42!
43!
44! Description:
45! ------------
46! Getting the values of environment-variabls (for different operating-systems)
47!------------------------------------------------------------------------------!
48
49#if defined( __lcmuk )
50    USE pegrid
51#endif
52    CHARACTER (LEN=*) ::  var, value
53    INTEGER           ::  ivalue, ivar
54#if defined( __lcmuk )
55    INTEGER            ::  i, ia(20)
56#endif
57
58    CALL GETENV( var(1:ivar), value )
59    ivalue = LEN_TRIM( value )
60
61#if defined( __lcmuk )  &&  defined( __parallel )
62    ia = IACHAR( ' ' )
63    IF ( myid == 0 )  THEN
64       DO  i = 1, ivalue
65          ia(i) = IACHAR( value(i:i) )
66       ENDDO
67    ENDIF
68    CALL MPI_BCAST( ia(1), 20, MPI_INTEGER, 0, comm2d, ierr )
69    DO  i = 1, 20
70       IF ( ACHAR( ia(i) ) /= ' ' )  value(i:i) = ACHAR( ia(i) )
71    ENDDO
72    ivalue = LEN_TRIM( value )
73#endif
74 END SUBROUTINE local_getenv   
Note: See TracBrowser for help on using the repository browser.