Ignore:
Timestamp:
Aug 25, 2015, 5:14:59 PM (9 years ago)
Author:
Ehouarn Millour
Message:

More on physics/dynamics separation and cleanup:

  • Set things up so that all physics-related initializations are done via iniphysiq.
  • Created a "geometry_mod.F90" module in phy_common to store information on the loacl grid (i.e. replaces comgeomphy) and moreover give these variables more obvious names (e.g.: rlond => longitude, rlatd => latitude, airephy => cell_area).
  • removed obsolete comgeomphy.h and comgeomphy.F90

EM

Location:
LMDZ5/trunk/libf/phymar
Files:
2 deleted
1 edited
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phymar/phyaqua_mod.F90

    r2348 r2351  
    22! $Id: $
    33!
     4MODULE phyaqua_mod
    45
    5       subroutine iniaqua(nlon,latfi,lonfi,iflag_phys)
     6  IMPLICIT NONE
    67
    7 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    8 !  Create an initial state (startphy.nc) for the physics
    9 !  Usefull for idealised cases (e.g. aquaplanets or testcases)
    10 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     8CONTAINS
    119
    12       use phys_state_var_mod, only : rlat,rlon,
    13      &                               phys_state_var_init
    14       use mod_phys_lmdz_para, only : klon_omp
    15       use comgeomphy, only : rlond,rlatd
    16       implicit none
     10  SUBROUTINE iniaqua(nlon, iflag_phys)
     11
     12  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     13  !  Create an initial state (startphy.nc) for the physics
     14  !  Usefull for idealised cases (e.g. aquaplanets or testcases)
     15  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     16
     17  USE phys_state_var_mod, ONLY: rlat, rlon, phys_state_var_init
     18  USE mod_phys_lmdz_para, ONLY: klon_omp
     19  USE geometry_mod, ONLY: longitude_deg, latitude_deg
     20  IMPLICIT NONE
    1721     
    18       integer,intent(in) :: nlon,iflag_phys
    19       real,intent(in) :: lonfi(nlon),latfi(nlon)
     22  INTEGER,INTENT(IN) :: nlon,iflag_phys
    2023
    21 ! local variables
    22       real :: pi
     24  ! local variables
     25  REAL :: pi
    2326
    24 ! initializations:
    25       pi=2.*asin(1.)
     27  ! initializations:
     28  pi=2.*ASIN(1.)
    2629
    27       call phys_state_var_init()
     30  CALL phys_state_var_init()
    2831
    29       rlat(1:klon_omp)=rlatd(1:klon_omp)*180./pi
    30       rlon(1:klon_omp)=rlond(1:klon_omp)*180./pi
     32  rlat(1:klon_omp)=latitude_deg(1:klon_omp)
     33  rlon(1:klon_omp)=longitude_deg(1:klon_omp)
    3134
    3235
    33 ! Here you could create an initial condition for the physics
    34 ! ...
    35 ! ... fill in the fields...
    36 ! ...
    37 ! ... and create a "startphy.nc" file
     36  ! Here you could create an initial condition for the physics
     37  ! ...
     38  ! ... fill in the fields...
     39  ! ...
     40  ! ... and create a "startphy.nc" file
    3841      CALL phyredem ("startphy.nc")
    3942
    40       end
     43  END SUBROUTINE iniaqua
    4144
     45END MODULE phyaqua_mod
  • LMDZ5/trunk/libf/phymar/physiq.F90

    r2320 r2351  
    1111     &            debut,lafin,jD_cur, jH_cur,pdtphys, &
    1212     &            paprs,pplay,pphi,pphis,ppresnivs, &
    13      &            u,v,t,qx, &
     13     &            u,v,rot,t,qx, &
    1414     &            flxmass_w, &
    1515     &            d_u, d_v, d_t, d_qx, d_ps &
     
    1818      USE dimphy, only : klon,klev,klevp1
    1919      USE infotrac_phy, only : nqtot
    20       USE comgeomphy, only : rlatd,rlond,airephy
     20      USE geometry_mod, only : latitude,longitude,cell_area
    2121      !USE comcstphy, only : rg
    2222      USE iophy, only : histbeg_phy,histwrite_phy
     
    498498
    499499DO i=1,klon
    500   IF (rlond(i) .LT. 0) THEN
    501     lonh_HOST(i)=rlond(i)*12./rpi+24. ! from radians to hours
     500  IF (longitude(i) .LT. 0) THEN
     501    lonh_HOST(i)=longitude(i)*12./rpi+24. ! from radians to hours
    502502   ELSE
    503     lonh_HOST(i)=rlond(i)*12./rpi ! from radians to hours
     503    lonh_HOST(i)=longitude(i)*12./rpi ! from radians to hours
    504504  ENDIF
    505505ENDDO
    506 latr_HOST(:)=rlatd(:) ! from radians to radians
     506latr_HOST(:)=latitude(:) ! from radians to radians
    507507
    508508!PRINT*, 'lonh_HOST(:)=',lonh_HOST(:)
     
    689689PRINT*, 'Initialisation de la temperature de surface avec les SST aquaplanète'
    690690          DO i = 1,klon
    691             Ts___HOST(i)=273.+27.*(1-sin(1.5*rlatd(i))**2)
    692             IF ((rlatd(i).GT.1.0471975).OR.(rlatd(i).LT.-1.0471975)) THEN
     691            Ts___HOST(i)=273.+27.*(1-sin(1.5*latitude(i))**2)
     692            IF ((latitude(i).GT.1.0471975).OR.(latitude(i).LT.-1.0471975)) THEN
    693693              Ts___HOST(i)=273.
    694694            ENDIF
     
    791791DO k = 1, klev
    792792  i=klev+1-k
    793   !omega(i,k) = RG*flxmass_w(i,k) / airephy(i) ! omega en Pa/s
    794   Wa___HOST(:,i)=flxmass_w(:,k) / airephy(:) * (gZam_HOST(:,i+1) - gZam_HOST(:,i))/(paprs(:,k+1)-paprs(:,k)) ! Equilibre hydrostatique
     793  !omega(i,k) = RG*flxmass_w(i,k) / cell_area(i) ! omega en Pa/s
     794  Wa___HOST(:,i)=flxmass_w(:,k) / cell_area(:) * (gZam_HOST(:,i+1) - gZam_HOST(:,i))/(paprs(:,k+1)-paprs(:,k)) ! Equilibre hydrostatique
    795795END DO
    796796Wa___HOST(:,klev)=0 ! Vitesse nulle à la surface.
     
    853853!IF (debut) THEN
    854854  DO i=1,klon
    855     sst__HOST(i)=273.+27.*(1-sin(1.5*rlatd(i))**2)
    856     IF ((rlatd(i).GT.1.0471975).OR.(rlatd(i).LT.-1.0471975)) THEN
     855    sst__HOST(i)=273.+27.*(1-sin(1.5*latitude(i))**2)
     856    IF ((latitude(i).GT.1.0471975).OR.(latitude(i).LT.-1.0471975)) THEN
    857857      sst__HOST(i)=273.
    858858    ENDIF
     
    908908      ikl0 = i
    909909      PRINT*,'Attention : NaN at'
    910       PRINT*,'longitude=',rlond(i)*180/rpi
    911       PRINT*,'latitude=',rlatd(i)*180/rpi
     910      PRINT*,'longitude=',longitude(i)*180/rpi
     911      PRINT*,'latitude=',latitude(i)*180/rpi
    912912    ENDIF
    913913  ENDDO
Note: See TracChangeset for help on using the changeset viewer.