Changeset 2395


Ignore:
Timestamp:
Nov 18, 2015, 1:25:35 PM (9 years ago)
Author:
Ehouarn Millour
Message:

Bug fix for aquaplanets: "rlat" and "rlon" were uninitialized when written to startphy.nc; phyredem should write "longitude_deg" and "latitude_deg" to the file. Overall "rlat" and "rlon" should not be used and "latitude_deg" and "longitude_deg" should be used instead in the physics. To be further cleaned up.
Some cleanup on that mater also made in phydev.
Note that this change will make bench test results different for longitudes and latitudes, because of roundoff effects.
EM

Location:
LMDZ5/trunk/libf
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dynlonlat_phylonlat/phydev/iniphysiq_mod.F90

    r2351 r2395  
    216216  CALL inifis(prad,pg,pr,pcpp)
    217217 
     218  ! Initialize dimphy module
     219  CALL Init_dimphy(klon_omp,nlayer)
     220
    218221  ! Initialize tracer names, numbers, etc. for physics
    219222  CALL init_infotrac_phy(nqtot,type_trac)
  • LMDZ5/trunk/libf/phy_common/geometry_mod.F90

    r2351 r2395  
    6868    IF (PRESENT(dy_)) dy(:) = dy_(:)
    6969   
    70     ! Ehouarn debug
    71     write(*,*) "init_geometry: cell_area(1)=",cell_area(1)
    7270  END SUBROUTINE init_geometry
    7371
  • LMDZ5/trunk/libf/phydev/phyaqua_mod.F90

    r2351 r2395  
    1515  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1616
    17   USE phys_state_var_mod, ONLY: rlat, rlon, phys_state_var_init
     17  USE phys_state_var_mod, ONLY: phys_state_var_init
    1818  USE mod_phys_lmdz_para, ONLY: klon_omp
    19   USE geometry_mod, ONLY: longitude_deg, latitude_deg
    2019  IMPLICIT NONE
    2120     
    2221  INTEGER,INTENT(IN) :: nlon,iflag_phys
    2322
    24   ! local variables
    25   REAL :: pi
    26 
    27   ! initializations:
    28   pi=2.*ASIN(1.)
    29 
    3023  CALL phys_state_var_init()
    31 
    32   rlat(1:klon_omp)=latitude_deg(1:klon_omp)
    33   rlon(1:klon_omp)=longitude_deg(1:klon_omp)
    3424
    3525
  • LMDZ5/trunk/libf/phydev/phyetat0.F90

    r1907 r2395  
    22! $Id $
    33!
    4 subroutine phyetat0(fichnom)
     4SUBROUTINE phyetat0(fichnom)
    55! Load initial state for the physics
    66! and do some resulting initializations
    77
    8 use iostart, only : open_startphy,get_field,close_startphy
    9 use iophy, only : init_iophy_new
    10 use phys_state_var_mod, only : rlat,rlon
     8  USE dimphy, only: klon
     9  USE iostart, ONLY : open_startphy,get_field,close_startphy
     10  USE iophy, ONLY : init_iophy_new
     11  USE geometry_mod, ONLY : longitude_deg, latitude_deg
    1112
    12 implicit none
     13  IMPLICIT NONE
    1314
    14 character(len=*),intent(in) :: fichnom ! input file name
     15  CHARACTER(len=*),INTENT(in) :: fichnom ! input file name
    1516
    16 ! open physics initial state file:
    17 call open_startphy(fichnom)
     17  REAL :: lon_startphy(klon), lat_startphy(klon)
     18  INTEGER :: i
    1819
    19 ! read latitudes
    20 call get_field("latitude",rlat)
     20  ! open physics initial state file:
     21  CALL open_startphy(fichnom)
    2122
    22 ! read longitudes
    23 call get_field("longitude",rlon)
     23  ! read latitudes and make a sanity check (because already known from dyn)
     24  CALL get_field("latitude",lat_startphy)
     25  DO i=1,klon
     26    IF (ABS(lat_startphy(i)-latitude_deg(i))>=1) THEN
     27      WRITE(*,*) "phyetat0: Error! Latitude discrepancy wrt startphy file:",&
     28                 " i=",i," lat_startphy(i)=",lat_startphy(i),&
     29                 " latitude_deg(i)=",latitude_deg(i)
     30      ! This is presumably serious enough to abort run
     31      CALL abort_physic("phyetat0","discrepancy in latitudes!",1)
     32    ENDIF
     33    IF (ABS(lat_startphy(i)-latitude_deg(i))>=0.0001) THEN
     34      WRITE(*,*) "phyetat0: Warning! Latitude discrepancy wrt startphy file:",&
     35                 " i=",i," lat_startphy(i)=",lat_startphy(i),&
     36                 " latitude_deg(i)=",latitude_deg(i)
     37    ENDIF
     38  ENDDO
    2439
    25 ! read in other variables here ...
     40  ! read longitudes and make a sanity check (because already known from dyn)
     41  CALL get_field("longitude",lon_startphy)
     42  DO i=1,klon
     43    IF (ABS(lon_startphy(i)-longitude_deg(i))>=1) THEN
     44      WRITE(*,*) "phyetat0: Error! Longitude discrepancy wrt startphy file:",&
     45                 " i=",i," lon_startphy(i)=",lon_startphy(i),&
     46                 " longitude_deg(i)=",longitude_deg(i)
     47      ! This is presumably serious enough to abort run
     48      CALL abort_physic("phyetat0","discrepancy in longitudes!",1)
     49    ENDIF
     50    IF (ABS(lon_startphy(i)-longitude_deg(i))>=0.0001) THEN
     51      WRITE(*,*) "phyetat0: Warning! Longitude discrepancy wrt startphy file:",&
     52                 " i=",i," lon_startphy(i)=",lon_startphy(i),&
     53                 " longitude_deg(i)=",longitude_deg(i)
     54    ENDIF
     55  ENDDO
    2656
    27 ! close file
    28 call close_startphy
     57  ! read in other variables here ...
    2958
    30 ! do some more initializations
    31 call init_iophy_new(rlat,rlon)
     59  ! close file
     60  CALL close_startphy
    3261
    33 end subroutine phyetat0
     62  ! do some more initializations
     63  CALL init_iophy_new(latitude_deg,longitude_deg)
     64
     65END SUBROUTINE phyetat0
  • LMDZ5/trunk/libf/phydev/phyredem.F90

    r1994 r2395  
    44SUBROUTINE phyredem (fichnom)
    55
     6  USE geometry_mod, ONLY : longitude_deg, latitude_deg
    67  USE iostart, ONLY: open_restartphy, close_restartphy, put_var, put_field
    7   USE phys_state_var_mod, ONLY: rlon, rlat
    88
    99  IMPLICIT NONE
     
    2727  ! coordinates
    2828
    29   CALL put_field("longitude", "Longitudes on physics grid", rlon)
     29  CALL put_field("longitude", "Longitudes on physics grid", longitude_deg)
    3030     
    31   CALL put_field("latitude", "Latitudes on physics grid", rlat)
     31  CALL put_field("latitude", "Latitudes on physics grid", latitude_deg)
    3232
    3333  ! close file
  • LMDZ5/trunk/libf/phydev/phys_state_var_mod.F90

    r1907 r2395  
    77!======================================================================
    88
    9 USE dimphy, only : klon
     9!USE dimphy, only : klon
    1010 
    1111
    12 REAL, ALLOCATABLE, SAVE :: rlat(:), rlon(:)
    13 !$OMP THREADPRIVATE(rlat,rlon)
     12!REAL, ALLOCATABLE, SAVE :: rlat(:), rlon(:)
     13!!$OMP THREADPRIVATE(rlat,rlon)
    1414
    1515CONTAINS
     
    1717!======================================================================
    1818  SUBROUTINE phys_state_var_init()
    19   use dimphy, only : klon
     19!  use dimphy, only : klon
    2020
    21   if (.not.allocated(rlat)) then
    22     ALLOCATE(rlat(klon),rlon(klon))
    23   else
    24     write(*,*) "phys_state_var_init: warning, rlat already allocated"
    25   endif
     21!  if (.not.allocated(rlat)) then
     22!    ALLOCATE(rlat(klon),rlon(klon))
     23!  else
     24!    write(*,*) "phys_state_var_init: warning, rlat already allocated"
     25!  endif
    2626 
    2727  END SUBROUTINE phys_state_var_init
     
    2929!======================================================================
    3030  SUBROUTINE phys_state_var_end
    31   use dimphy, only : klon
     31!  use dimphy, only : klon
    3232
    33   deallocate(rlat,rlon)
     33!  deallocate(rlat,rlon)
    3434
    3535  END SUBROUTINE phys_state_var_end
  • LMDZ5/trunk/libf/phylmd/phyredem.F90

    r2356 r2395  
    66! Purpose: Write restart state for physics.
    77!-------------------------------------------------------------------------------
    8   USE dimphy
    9   USE mod_grid_phy_lmdz
    10   USE mod_phys_lmdz_para
     8  USE dimphy, ONLY: klon, klev
    119  USE fonte_neige_mod,  ONLY : fonte_neige_final
    1210  USE pbl_surface_mod,  ONLY : pbl_surface_final
    13   USE phys_state_var_mod
    14   USE iostart
     11  USE phys_state_var_mod, ONLY: radpas, zmasq, pctsrf, ftsol, falb_dir, &
     12                                falb_dif, qsol, fevap, radsol, solsw, sollw, &
     13                                sollwdown, rain_fall, snow_fall, z0m, z0h, &
     14                                agesno, zmea, zstd, zsig, zgam, zthe, zpic, &
     15                                zval, rugoro, t_ancien, q_ancien, u_ancien, &
     16                                v_ancien, clwcon, rnebcon, ratqs, pbl_tke, &
     17                                wake_delta_pbl_tke, zmax0, f0, sig1, w01, &
     18                                wake_deltat, wake_deltaq, wake_s, wake_cstar, &
     19                                wake_pe, wake_fip, fm_therm, entr_therm, &
     20                                detr_therm, Ale_bl, Ale_bl_trig, Alp_bl, &
     21                                du_gwd_rando, du_gwd_front
     22  USE geometry_mod, ONLY : longitude_deg, latitude_deg
     23  USE iostart, ONLY: open_restartphy, close_restartphy, put_field, put_var
    1524  USE traclmdz_mod, ONLY : traclmdz_to_restart
    1625  USE infotrac_phy, ONLY: type_trac, niadv, tname, nbtr, nqo
    1726  USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
    18   USE indice_sol_mod
    19   USE surface_data
     27  USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic, epsfra
     28  USE surface_data, ONLY: type_ocean, version_ocean
    2029  USE ocean_slab_mod, ONLY : tslab, seaice, tice, fsic
    2130  USE time_phylmdz_mod, ONLY: annee_ref, day_end, itau_phy, pdtphys
     
    9099
    91100  CALL put_field("longitude", &
    92        "Longitudes de la grille physique", rlon)
    93 
    94   CALL put_field("latitude", "Latitudes de la grille physique", rlat)
     101       "Longitudes de la grille physique", longitude_deg)
     102
     103  CALL put_field("latitude", "Latitudes de la grille physique", latitude_deg)
    95104
    96105  ! PB ajout du masque terre/mer
Note: See TracChangeset for help on using the changeset viewer.