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

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

New:
---

Changed:


PALM can be generally installed on any kind of Linux-, IBM-AIX-, or NEC-SX-system by adding appropriate settings to the configuration file.

Scripts are also running under the public domain ksh.

All system relevant compile and link options as well as the host identifier (local_host) are specified in the configuration file.

Filetransfer by ftp removed (options -f removed from mrun and mbuild).

Call of (system-)FLUSH routine moved to new routine local_flush.

return_addres and return_username are read from ENVPAR-NAMELIST-file instead of using local_getenv.

Preprocessor strings for different linux clusters changed to "lc", some preprocessor directives renamed (new: intel_openmp_bug), preprocessor directives for old systems removed

advec_particles, check_open, cpu_log, cpu_statistics, data_output_dvrp, flow_statistics, header, init_dvrp, init_particles, init_1d_model, init_dvrp, init_pegrid, local_getenv, local_system, local_tremain, local_tremain_ini, modules, palm, parin, run_control

new:
local_flush

mbuild, mrun

Errors:


  • Property svn:keywords set to Id
File size: 1.5 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 83 2007-04-19 16:27:07Z letzel $
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.