Ignore:
Timestamp:
Mar 23, 2015, 8:27:30 AM (10 years ago)
Author:
Ehouarn Millour
Message:

Reorganizing physics/dynamics interface:

  • what is related to dynamics-physics interface is now in a seperate directory: dynlmdz_phy* for physics in phy*
  • 1d model and related dependencies (including a couple from "dynamics", set up as symbolic links) is now in subdirectory "dyn1d" of phy*.
  • "bibio" directory is now "misc" and should only contain autonomous utilities.
  • "cosp" is now a subdirectory of phylmd.

EM

Location:
LMDZ5/trunk/libf/dynlmdz_phylmd
Files:
1 added
17 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dynlmdz_phylmd/calfis_loc.F

    r2233 r2239  
    3636      USE IOPHY
    3737#endif
     38#ifdef CPP_PARA
    3839      USE parallel_lmdz,ONLY:omp_chunk,using_mpi,jjb_u,jje_u,jjb_v,jje_v
    3940      USE Write_Field
    4041      Use Write_field_p
    4142      USE Times
     43#endif
    4244      USE infotrac, ONLY: nqtot, niadv, tname
    4345      USE control_mod, ONLY: planet_type, nsplit_phys
    4446
     47#ifdef CPP_PARA
    4548      IMPLICIT NONE
    4649c=======================================================================
     
    11861189#endif
    11871190! of #ifdef CPP_PHYS
    1188       RETURN
     1191#endif
     1192! of #ifdef CPP_PARA
    11891193      END
  • LMDZ5/trunk/libf/dynlmdz_phylmd/calfis_p.F

    r2233 r2239  
    3333      USE IOPHY
    3434#endif
     35#ifdef CPP_PARA
    3536      USE parallel_lmdz, ONLY : omp_chunk, using_mpi
    3637      USE Write_Field
    3738      Use Write_field_p
    3839      USE Times
     40#endif
    3941      USE infotrac, ONLY: nqtot, niadv, tname
    4042      USE control_mod, ONLY: planet_type, nsplit_phys
     
    140142      REAL,INTENT(OUT) :: pdpsfi(iip1,jjp1) ! tendency on surface pressure (Pa/s)
    141143
     144#ifdef CPP_PARA
    142145#ifdef CPP_PHYS
    143146! Ehouarn: for now calfis_p needs some informations from physics to compile
     
    11141117#endif
    11151118! of #ifdef CPP_PHYS
    1116       RETURN
     1119#endif
     1120! of #ifdef CPP_PARA
    11171121      END
  • LMDZ5/trunk/libf/dynlmdz_phylmd/gr_dyn_fi_p.F

    r2233 r2239  
    33!
    44      SUBROUTINE gr_dyn_fi_p(nfield,im,jm,ngrid,pdyn,pfi)
    5 #ifdef CPP_PHYS
     5#ifdef CPP_PARA
    66! Interface with parallel physics,
    77      USE mod_interface_dyn_phys
     
    4040c$OMP END DO NOWAIT
    4141#endif
    42 ! of #ifdef CPP_PHYS
     42! of #ifdef CPP_PARA
    4343      RETURN
    4444      END
  • LMDZ5/trunk/libf/dynlmdz_phylmd/gr_fi_dyn_p.F

    r2233 r2239  
    33!
    44      SUBROUTINE gr_fi_dyn_p(nfield,ngrid,im,jm,pfi,pdyn)
    5 #ifdef CPP_PHYS
     5#ifdef CPP_PARA
    66! Interface with parallel physics,
    77      USE mod_interface_dyn_phys
     
    5252c$OMP END DO NOWAIT
    5353#endif
    54 ! of #ifdef CPP_PHYS
     54! of #ifdef CPP_PARA
    5555      RETURN
    5656      END
  • LMDZ5/trunk/libf/dynlmdz_phylmd/iniphysiq.F90

    r2233 r2239  
    148148    WRITE (lunout, *) '  in the dynamics punjours=', punjours
    149149    WRITE (lunout, *) '   but in the physics RDAY=', rday
    150     IF (abs(rday-punjours)>0.01) THEN
     150    IF (abs(rday-punjours)>0.01*punjours) THEN
    151151        ! stop here if the relative difference is more than 1%
    152152      abort_message = 'length of day discrepancy'
     
    158158    WRITE (lunout, *) '     in the dynamics pg=', pg
    159159    WRITE (lunout, *) '  but in the physics RG=', rg
    160     IF (abs(rg-pg)>0.01) THEN
     160    IF (abs(rg-pg)>0.01*pg) THEN
    161161        ! stop here if the relative difference is more than 1%
    162162      abort_message = 'gravity discrepancy'
     
    168168    WRITE (lunout, *) '   in the dynamics prad=', prad
    169169    WRITE (lunout, *) '  but in the physics RA=', ra
    170     IF (abs(ra-prad)>0.01) THEN
     170    IF (abs(ra-prad)>0.01*prad) THEN
    171171        ! stop here if the relative difference is more than 1%
    172172      abort_message = 'planet radius discrepancy'
     
    178178    WRITE (lunout, *) '     in the dynamics pr=', pr
    179179    WRITE (lunout, *) '  but in the physics RD=', rd
    180     IF (abs(rd-pr)>0.01) THEN
     180    IF (abs(rd-pr)>0.01*pr) THEN
    181181        ! stop here if the relative difference is more than 1%
    182182      abort_message = 'reduced gas constant discrepancy'
     
    188188    WRITE (lunout, *) '     in the dynamics pcpp=', pcpp
    189189    WRITE (lunout, *) '  but in the physics RCPD=', rcpd
    190     IF (abs(rcpd-pcpp)>0.01) THEN
     190    IF (abs(rcpd-pcpp)>0.01*pcpp) THEN
    191191        ! stop here if the relative difference is more than 1%
    192192      abort_message = 'specific heat discrepancy'
  • LMDZ5/trunk/libf/dynlmdz_phylmd/mod_interface_dyn_phys.F90

    r2233 r2239  
    77 
    88 
    9 #ifdef CPP_PHYS
     9#ifdef CPP_PARA
    1010! Interface with parallel physics,
    1111CONTAINS
     
    5555  END SUBROUTINE Init_interface_dyn_phys
    5656#endif
    57 ! of #ifdef CPP_PHYS
     57! of #ifdef CPP_PARA
    5858END MODULE mod_interface_dyn_phys
Note: See TracChangeset for help on using the changeset viewer.