source: LMDZ6/branches/Amaury_dev/libf/phylmd/read_map2D.F90 @ 5136

Last change on this file since 5136 was 5112, checked in by abarral, 2 months ago

Rename modules in phy_common from *_mod > lmdz_*

  • 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.9 KB
RevLine 
[1227]1SUBROUTINE read_map2D(filename, varname, timestep, inverse, varout)
[5111]2  ! Open file and read one variable for one timestep.
3  ! Return variable for the given timestep.
[1227]4  USE dimphy
[5111]5  USE netcdf, ONLY: nf90_open, nf90_close, nf90_nowrite, nf90_noerr, nf90_get_var, nf90_inq_varid
[5110]6  USE lmdz_grid_phy
7  USE lmdz_phys_para
[5112]8  USE lmdz_print_control, ONLY: lunout
[1227]9
10  IMPLICIT NONE
11
[5111]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
[1227]18  REAL, DIMENSION(klon), INTENT(OUT) :: varout  ! The variable read from file for the given timestep
19
[5111]20  ! Local variables
[1227]21  INTEGER :: j
22  INTEGER :: nid, nvarid, ierr
23  INTEGER, DIMENSION(3) :: start, count
[5111]24  CHARACTER(len = 20) :: modname = 'read_map2D'
[1227]25
[5111]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
[1227]29
[5111]30  ! Read variable from file. Done by master process MPI and master thread OpenMP
[1227]31  IF (is_mpi_root .AND. is_omp_root) THEN
[5111]32    ierr = nf90_open(trim(filename), nf90_nowrite, nid)
33    IF (ierr /= nf90_noerr) CALL write_err_mess('Problem in opening file')
[1227]34
[5111]35    ierr = nf90_inq_varid(nid, trim(varname), nvarid)
36    IF (ierr /= nf90_noerr) CALL write_err_mess('The variable is absent in file')
[1227]37
[5111]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')
[1454]42
[5111]43    ierr = nf90_close(nid)
44    IF (ierr /= nf90_noerr) CALL write_err_mess('Problem in closing file')
[1227]45
[5111]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
[1227]53
[5111]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
[1227]60  ENDIF
61
[5111]62  ! Scatter gloabl 1D variable to all processes
[1227]63  CALL scatter(var_glo1D, varout)
64
[5111]65CONTAINS
66  SUBROUTINE write_err_mess(err_mess)
[5112]67    USE lmdz_print_control, ONLY: lunout
[5111]68    USE lmdz_abort_physic, ONLY: abort_physic
69    IMPLICIT NONE
70    CHARACTER(len = *), INTENT(IN) :: err_mess
[1454]71
[5111]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
[1454]75
[5111]76    CALL abort_physic(modname, err_mess, 1)
[1454]77
[5111]78  END SUBROUTINE write_err_mess
79
[1227]80END SUBROUTINE read_map2D
Note: See TracBrowser for help on using the repository browser.