source: palm/trunk/SOURCE/local_getenv.f90 @ 1

Last change on this file since 1 was 1, checked in by raasch, 17 years ago

Initial repository layout and content

File size: 1.9 KB
Line 
1 SUBROUTINE local_getenv( var, ivar, value, ivalue )
2
3!-------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: local_getenv.f90,v $
11! Revision 1.5  2003/05/09 14:37:07  raasch
12! On the MUK cluster, only PE0 is able to read environment variables.
13! Therefore, they have to be communicated via broadcast to the other PEs.
14!
15! Revision 1.4  2003/03/16 09:40:22  raasch
16! Two underscores (_) are placed in front of all define-strings
17!
18! Revision 1.3  2001/01/22 07:23:55  raasch
19! Comments translated into English
20!
21! Revision 1.2  1998/07/16 06:50:50  raasch
22! cpp-Direktiven fuer t3ej2 und t3ej5 erweitert
23!
24! Revision 1.1  1997/08/11 06:21:01  raasch
25! Initial revision
26!
27!
28! Description:
29! ------------
30! Getting the values of environment-variabls (for different operating-systems)
31!-------------------------------------------------------------------------------!
32
33#if defined( __lcmuk )
34    USE pegrid
35#endif
36    CHARACTER (LEN=*) ::  var, value
37    INTEGER           ::  ivalue, ivar
38#if defined( __t3eb ) || defined( __t3eh ) || defined( __t3ej2 ) || defined( __t3ej5 )
39    INTEGER           ::  dummy
40#endif
41#if defined( __lcmuk )
42    INTEGER            ::  i, ia(20)
43#endif
44
45#if defined( __t3eb ) || defined( __t3eh ) || defined( __t3ej2 ) || defined( __t3ej5 )
46    CALL PXFGETENV( var(1:ivar), ivar, value, ivalue, dummy )
47    IF ( ivalue == 0 )  value = ''
48#else
49    CALL GETENV( var(1:ivar), value )
50    ivalue = LEN_TRIM( value )
51#endif
52
53#if defined( __lcmuk )  &&  defined( __parallel )
54    ia = IACHAR( ' ' )
55    IF ( myid == 0 )  THEN
56       DO  i = 1, ivalue
57          ia(i) = IACHAR( value(i:i) )
58       ENDDO
59    ENDIF
60    CALL MPI_BCAST( ia(1), 20, MPI_INTEGER, 0, comm2d, ierr )
61    DO  i = 1, 20
62       IF ( ACHAR( ia(i) ) /= ' ' )  value(i:i) = ACHAR( ia(i) )
63    ENDDO
64    ivalue = LEN_TRIM( value )
65#endif
66 END SUBROUTINE local_getenv   
Note: See TracBrowser for help on using the repository browser.