source: LMDZ6/trunk/libf/phylmd/read_map2D.F90 @ 5207

Last change on this file since 5207 was 5084, checked in by Laurent Fairhead, 12 months ago

Reverting to r4065. Updating fortran standard broke too much stuff. Will do it by smaller chunks
AB, LF

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 2.8 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  USE print_control_mod, ONLY: lunout
9
10  IMPLICIT NONE
11
12! Input arguments
13  CHARACTER(len=*), INTENT(IN)  :: filename     ! name of file to read
14  CHARACTER(len=*), 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! Read variable from file. Done by master process MPI and master thread OpenMP
31  IF (is_mpi_root .AND. is_omp_root) THEN
32     ierr = NF90_OPEN(trim(filename), NF90_NOWRITE, nid)
33     IF (ierr /= NF90_NOERR) CALL write_err_mess('Problem in opening file')
34
35     ierr = NF90_INQ_VARID(nid, trim(varname), nvarid)
36     IF (ierr /= NF90_NOERR) CALL write_err_mess('The variable is absent in file')
37     
38     start=(/1,1,timestep/)
39     count=(/nbp_lon,nbp_lat,1/)
40     ierr = NF90_GET_VAR(nid, nvarid, var_glo2D,start,count)
41     IF (ierr /= NF90_NOERR) CALL write_err_mess('Problem in reading varaiable')
42
43     ierr = NF90_CLOSE(nid)
44     IF (ierr /= NF90_NOERR) CALL write_err_mess('Problem in closing file')
45
46     ! Inverse latitude order
47     IF (inverse) THEN
48        var_glo2D_tmp(:,:) = var_glo2D(:,:)
49        DO j=1, nbp_lat
50           var_glo2D(:,j) = var_glo2D_tmp(:,nbp_lat-j+1)
51        END DO
52     END IF
53
54     ! Transform the global field from 2D to 1D
55     CALL grid2Dto1D_glo(var_glo2D,var_glo1D)
56
57     WRITE(lunout,*) 'in read_map2D, filename = ', trim(filename)
58     WRITE(lunout,*) 'in read_map2D, varname  = ', trim(varname)
59     WRITE(lunout,*) 'in read_map2D, timestep = ', timestep
60  ENDIF
61
62! Scatter gloabl 1D variable to all processes
63  CALL scatter(var_glo1D, varout)
64
65  CONTAINS
66    SUBROUTINE write_err_mess(err_mess)
67      USE print_control_mod, ONLY: lunout
68      IMPLICIT NONE
69      CHARACTER(len=*), INTENT(IN) :: err_mess
70     
71      WRITE(lunout,*) 'Error in read_map2D, filename = ', trim(filename)
72      WRITE(lunout,*) 'Error in read_map2D, varname  = ', trim(varname)
73      WRITE(lunout,*) 'Error in read_map2D, timestep = ', timestep
74
75      CALL abort_physic(modname, err_mess, 1)
76
77    END SUBROUTINE write_err_mess
78
79END SUBROUTINE read_map2D
Note: See TracBrowser for help on using the repository browser.