source: LMDZ6/branches/Amaury_dev/libf/phy_common/lmdz_writefield_phy.f90 @ 5160

Last change on this file since 5160 was 5133, checked in by abarral, 8 weeks ago

Fix 1D, rrtm & ecrad compilation

  • 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 907 bytes
Line 
1! $Id: lmdz_writefield_phy.f90 5133 2024-07-26 12:20:54Z abarral $
2
3MODULE lmdz_writefield_phy
4
5  ! Dump a field on the global (nbp_lon by nbp_lat) physics grid
6  IMPLICIT NONE; PRIVATE
7  PUBLIC writefield_phy
8
9CONTAINS
10
11  SUBROUTINE WriteField_phy(name, Field, ll)
12    USE lmdz_phys_para, ONLY: klon_omp, is_mpi_root, &
13            Gather
14    USE lmdz_grid_phy, ONLY: nbp_lon, nbp_lat, klon_glo, &
15            Grid1Dto2D_glo
16    USE lmdz_write_field, ONLY: WriteField
17
18    IMPLICIT NONE
19
20    CHARACTER(len = *), INTENT(IN) :: name
21    INTEGER, INTENT(IN) :: ll
22    REAL, INTENT(IN) :: Field(klon_omp, ll)
23
24    REAL, DIMENSION(klon_glo, ll) :: New_Field
25    REAL, DIMENSION(nbp_lon, nbp_lat, ll) :: Field_2d
26
27    CALL Gather(Field, New_Field)
28    !$OMP MASTER
29    IF (is_mpi_root) THEN
30      CALL Grid1Dto2D_glo(New_Field, Field_2D)
31      CALL WriteField(name, Field_2d)
32    ENDIF
33    !$OMP END MASTER
34
35  END SUBROUTINE WriteField_phy
36
37END MODULE lmdz_writefield_phy
Note: See TracBrowser for help on using the repository browser.