LMDZ
read_map2D.F90
Go to the documentation of this file.
1 SUBROUTINE 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
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)
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 
79 END SUBROUTINE read_map2d
subroutine read_map2d(filename, varname, timestep, inverse, varout)
Definition: read_map2D.F90:2
subroutine write_err_mess(err_mess)
Definition: read_map2D.F90:67
subroutine abort_physic(modname, message, ierr)
Definition: abort_physic.F90:3
Definition: dimphy.F90:1
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout
Definition: iniprint.h:7