source: LMDZ4/trunk/libf/phylmd/read_map2D.F90 @ 1411

Last change on this file since 1411 was 1279, checked in by Laurent Fairhead, 14 years ago

Merged LMDZ4-dev branch changes r1241:1278 into the trunk
Running trunk and LMDZ4-dev in LMDZOR configuration on local
machine (sequential) and SX8 (4-proc) yields identical results
(restart and restartphy are identical binarily)
Log history from r1241 to r1278 is available by switching to
source:LMDZ4/branches/LMDZ4-dev-20091210

File size: 2.1 KB
Line 
1SUBROUTINE read_map2D(filename, varname, timestep, inverse, varout)
2! Open file and read one variable for one timestep.
3! Return variable for the given timestep.
4  USE dimphy
5  USE netcdf
6  USE mod_grid_phy_lmdz
7  USE mod_phys_lmdz_para
8
9
10  IMPLICIT NONE
11
12! Input arguments
13  CHARACTER(len=20), INTENT(IN) :: filename     ! name of file to read
14  CHARACTER(len=20), INTENT(IN) :: varname      ! name of variable in file
15  INTEGER, INTENT(IN)           :: timestep     ! actual timestep
16  LOGICAL, INTENT(IN)           :: inverse      ! TRUE if latitude needs to be inversed
17! Output argument
18  REAL, DIMENSION(klon), INTENT(OUT) :: varout  ! The variable read from file for the given timestep
19
20! Local variables
21  INTEGER :: j
22  INTEGER :: nid, nvarid, ierr
23  INTEGER, DIMENSION(3) :: start, count
24  CHARACTER(len=20)     :: modname='read_map2D'
25
26  REAL, DIMENSION(nbp_lon,nbp_lat) :: var_glo2D     ! 2D global
27  REAL, DIMENSION(nbp_lon,nbp_lat) :: var_glo2D_tmp ! 2D global
28  REAL, DIMENSION(klon_glo)        :: var_glo1D     ! 1D global
29
30
31! Read variable from file. Done by master process MPI and master thread OpenMP
32  IF (is_mpi_root .AND. is_omp_root) THEN
33     ierr = NF90_OPEN (filename, NF90_NOWRITE, nid)
34     IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Problem in opening file '//filename,1)
35
36     ierr = NF90_INQ_VARID(nid, varname, nvarid)
37     IF (ierr /= NF90_NOERR) CALL abort_gcm(modname, 'The variable '//varname//' is absent in file',1)
38     
39     start=(/1,1,timestep/)
40     count=(/nbp_lon,nbp_lat,1/)
41     ierr = NF90_GET_VAR(nid, nvarid, var_glo2D,start,count)
42     IF (ierr /= NF90_NOERR) CALL abort_gcm(modname, 'Problem in reading varaiable '//varname,1)
43
44     ! Inverse latitude order
45     IF (inverse) THEN
46        var_glo2D_tmp(:,:) = var_glo2D(:,:)
47        DO j=1, nbp_lat
48           var_glo2D(:,j) = var_glo2D_tmp(:,nbp_lat-j+1)
49        END DO
50     END IF
51
52     ! Transform the global field from 2D to 1D
53     CALL grid2Dto1D_glo(var_glo2D,var_glo1D)
54
55  ENDIF
56
57! Scatter gloabl 1D variable to all processes
58  CALL scatter(var_glo1D, varout)
59
60END SUBROUTINE read_map2D
Note: See TracBrowser for help on using the repository browser.