source: trunk/LMDZ.EARTH/libf/phylmd/read_map2D.F90 @ 816

Last change on this file since 816 was 66, checked in by emillour, 14 years ago

EM: Mise a niveau par rapport a la version terrestre (LMDZ5V2.0-dev, rev 1487)

  • Mise a jour des scripts (terrestres) 'makegcm' et 'create_make_gcm'
  • Ajout du script 'makelmdz' (version "amelioree", en Bash, de makegcm)
  • Mise a jour des routines dans phylmd (sauf regr_lat_time_climoz_m.F)
  • disvert (dans dyn3d et dyn3dpar): passage au Fortran 90
  • parallel.F90 (dyn3dpar): correction bug
  • etat0_netcdf.F90 (dyn3d et dyn3dpar) : mise a jour mineure
  • ce0l.F90 (dyn3dpar) : correction bug
  • abort_gcm.F (dyn3dpar) : correction bug
  • ugeostr.F90 (dyn3d et dyn3dpar) : passage au Fortran 90
  • fluxstokenc_p.F (dyn3dpar) : correction bug
  • iniacademic.F90 (dyn3d et dyn3dpar) : passage au Fortran 90
  • friction_p.F (dyn3dpar) : correction bug
  • infotrac.F90 (dyn3d et dyn3dpar) : correction bug mineur sur lecture traceurs
  • caladvtrac.F (dyn3d) : modifications cosmetiques
File size: 2.7 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=*), 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  INCLUDE "iniprint.h"
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(trim(filename), NF90_NOWRITE, nid)
34     IF (ierr /= NF90_NOERR) CALL write_err_mess('Problem in opening file')
35
36     ierr = NF90_INQ_VARID(nid, trim(varname), nvarid)
37     IF (ierr /= NF90_NOERR) CALL write_err_mess('The variable is absent in file')
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 write_err_mess('Problem in reading varaiable')
43
44     ierr = NF90_CLOSE(nid)
45     IF (ierr /= NF90_NOERR) CALL write_err_mess('Problem in closing file')
46
47     ! Inverse latitude order
48     IF (inverse) THEN
49        var_glo2D_tmp(:,:) = var_glo2D(:,:)
50        DO j=1, nbp_lat
51           var_glo2D(:,j) = var_glo2D_tmp(:,nbp_lat-j+1)
52        END DO
53     END IF
54
55     ! Transform the global field from 2D to 1D
56     CALL grid2Dto1D_glo(var_glo2D,var_glo1D)
57
58     WRITE(lunout,*) 'in read_map2D, filename = ', trim(filename)
59     WRITE(lunout,*) 'in read_map2D, varname  = ', trim(varname)
60     WRITE(lunout,*) 'in read_map2D, timestep = ', timestep
61  ENDIF
62
63! Scatter gloabl 1D variable to all processes
64  CALL scatter(var_glo1D, varout)
65
66  CONTAINS
67    SUBROUTINE write_err_mess(err_mess)
68
69      CHARACTER(len=*), INTENT(IN) :: err_mess
70      INCLUDE "iniprint.h"
71     
72      WRITE(lunout,*) 'Error in read_map2D, filename = ', trim(filename)
73      WRITE(lunout,*) 'Error in read_map2D, varname  = ', trim(varname)
74      WRITE(lunout,*) 'Error in read_map2D, timestep = ', timestep
75
76      CALL abort_gcm(modname, err_mess, 1)
77
78    END SUBROUTINE write_err_mess
79
80END SUBROUTINE read_map2D
Note: See TracBrowser for help on using the repository browser.