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

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

Id keyword set as property for all *.f90 files

  • Property svn:keywords set to Id
File size: 1.7 KB
Line 
1 SUBROUTINE local_getenv( var, ivar, value, ivalue )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: local_getenv.f90 4 2007-02-13 11:33:16Z raasch $
11! RCS Log replace by Id keyword, revision history cleaned up
12!
13! Revision 1.5  2003/05/09 14:37:07  raasch
14! On the MUK cluster, only PE0 is able to read environment variables.
15! Therefore, they have to be communicated via broadcast to the other PEs.
16!
17! Revision 1.1  1997/08/11 06:21:01  raasch
18! Initial revision
19!
20!
21! Description:
22! ------------
23! Getting the values of environment-variabls (for different operating-systems)
24!------------------------------------------------------------------------------!
25
26#if defined( __lcmuk )
27    USE pegrid
28#endif
29    CHARACTER (LEN=*) ::  var, value
30    INTEGER           ::  ivalue, ivar
31#if defined( __t3eb ) || defined( __t3eh ) || defined( __t3ej2 ) || defined( __t3ej5 )
32    INTEGER           ::  dummy
33#endif
34#if defined( __lcmuk )
35    INTEGER            ::  i, ia(20)
36#endif
37
38#if defined( __t3eb ) || defined( __t3eh ) || defined( __t3ej2 ) || defined( __t3ej5 )
39    CALL PXFGETENV( var(1:ivar), ivar, value, ivalue, dummy )
40    IF ( ivalue == 0 )  value = ''
41#else
42    CALL GETENV( var(1:ivar), value )
43    ivalue = LEN_TRIM( value )
44#endif
45
46#if defined( __lcmuk )  &&  defined( __parallel )
47    ia = IACHAR( ' ' )
48    IF ( myid == 0 )  THEN
49       DO  i = 1, ivalue
50          ia(i) = IACHAR( value(i:i) )
51       ENDDO
52    ENDIF
53    CALL MPI_BCAST( ia(1), 20, MPI_INTEGER, 0, comm2d, ierr )
54    DO  i = 1, 20
55       IF ( ACHAR( ia(i) ) /= ' ' )  value(i:i) = ACHAR( ia(i) )
56    ENDDO
57    ivalue = LEN_TRIM( value )
58#endif
59 END SUBROUTINE local_getenv   
Note: See TracBrowser for help on using the repository browser.