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

Last change on this file since 550 was 484, checked in by raasch, 14 years ago

typo in file headers removed

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