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

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

vorlaeufige Standalone-Version fuer Linux-Cluster

  • Property svn:keywords set to Id
File size: 1.4 KB
RevLine 
[1]1 SUBROUTINE local_getenv( var, ivar, value, ivalue )
2
[3]3!------------------------------------------------------------------------------!
[1]4! Actual revisions:
5! -----------------
[82]6! Preprocessor directives for old systems removed
[1]7!
8! Former revisions:
9! -----------------
[3]10! $Id: local_getenv.f90 82 2007-04-16 15:40:52Z raasch $
11! RCS Log replace by Id keyword, revision history cleaned up
12!
[1]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)
[3]24!------------------------------------------------------------------------------!
[1]25
26#if defined( __lcmuk )
27    USE pegrid
28#endif
29    CHARACTER (LEN=*) ::  var, value
30    INTEGER           ::  ivalue, ivar
31#if defined( __lcmuk )
32    INTEGER            ::  i, ia(20)
33#endif
34
35    CALL GETENV( var(1:ivar), value )
36    ivalue = LEN_TRIM( value )
37
38#if defined( __lcmuk )  &&  defined( __parallel )
39    ia = IACHAR( ' ' )
40    IF ( myid == 0 )  THEN
41       DO  i = 1, ivalue
42          ia(i) = IACHAR( value(i:i) )
43       ENDDO
44    ENDIF
45    CALL MPI_BCAST( ia(1), 20, MPI_INTEGER, 0, comm2d, ierr )
46    DO  i = 1, 20
47       IF ( ACHAR( ia(i) ) /= ' ' )  value(i:i) = ACHAR( ia(i) )
48    ENDDO
49    ivalue = LEN_TRIM( value )
50#endif
51 END SUBROUTINE local_getenv   
Note: See TracBrowser for help on using the repository browser.