Ignore:
Timestamp:
Dec 20, 2013, 4:04:56 PM (11 years ago)
Author:
emillour
Message:

Mars GCM:
Series of changes to enable running in parallel (using LMDZ.COMMON dynamics);
Current LMDZ.MARS can still notheless be compiled and run in serial mode
"as previously".
Summary of main changes:

  • Main programs (newstart, start2archive, xvik) that used to be in dyn3d have been moved to phymars.
  • dyn3d/control.h is now module control_mod.F90
  • rearanged input/outputs routines everywhere to handle serial/MPI cases. physdem.F => phyredem.F90 , phyetat0.F => phyetat0.F90 ; all read/write routines for startfi files are gathered in module iostart.F90
  • added parallelism related routines init_phys_lmdz.F90, comgeomphy.F90, dimphy.F90, iniphysiq.F90, mod_grid_phy_lmdz.F90, mod_phys_lmdz_mpi_data.F90, mod_phys_lmdz_mpi_transfert.F90, mod_phys_lmdz_omp_data.F90, mod_phys_lmdz_omp_transfert.F90, mod_phys_lmdz_para.F90, mod_phys_lmdz_transfert_para.F90 in phymars and mod_const_mpi.F90 in dyn3d (for compliance with parallel case)
  • created generic routines 'planetwide_maxval' and 'planetwide_minval', in module "planetwide_mod", that enable obtaining the min and max of a field over the whole planet.

EM

Location:
trunk/LMDZ.MARS/libf/dyn3d
Files:
2 added
1 deleted
12 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/dyn3d/calfis.F

    r1036 r1130  
    7171#include "comvert.h"
    7272#include "comgeom2.h"
    73 #include "control.h"
     73!#include "control.h"
    7474
    7575c    Arguments :
     
    167167
    168168c
    169       IF (firstcal) THEN
    170          latfi(1)=rlatu(1)
    171          lonfi(1)=0.
    172          DO j=2,jjm
    173             DO i=1,iim
    174                latfi((j-2)*iim+1+i)= rlatu(j)
    175                lonfi((j-2)*iim+1+i)= rlonv(i)
    176             ENDDO
    177          ENDDO
    178          latfi(ngridmx)= rlatu(jjp1)
    179          lonfi(ngridmx)= 0.
    180          
    181          ! build airefi(), mesh area on physics grid
    182          CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi)
    183          ! Poles are single points on physics grid
    184          airefi(1)=airefi(1)*iim
    185          airefi(ngridmx)=airefi(ngridmx)*iim
    186 
    187          CALL inifis(ngridmx,llm,nq,day_ini,daysec,dtphys,
    188      .                latfi,lonfi,airefi,rad,g,r,cpp)
    189       ENDIF
     169!      IF (firstcal) THEN
     170!         latfi(1)=rlatu(1)
     171!         lonfi(1)=0.
     172!         DO j=2,jjm
     173!            DO i=1,iim
     174!               latfi((j-2)*iim+1+i)= rlatu(j)
     175!               lonfi((j-2)*iim+1+i)= rlonv(i)
     176!            ENDDO
     177!         ENDDO
     178!         latfi(ngridmx)= rlatu(jjp1)
     179!         lonfi(ngridmx)= 0.
     180!         
     181!         ! build airefi(), mesh area on physics grid
     182!         CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi)
     183!         ! Poles are single points on physics grid
     184!         airefi(1)=airefi(1)*iim
     185!         airefi(ngridmx)=airefi(ngridmx)*iim
     186!
     187!         CALL inifis(ngridmx,llm,nq,day_ini,daysec,dtphys,
     188!     .                latfi,lonfi,airefi,rad,g,r,cpp)
     189!      ENDIF
    190190
    191191c
  • trunk/LMDZ.MARS/libf/dyn3d/defrun_new.F

    r999 r1130  
    3636c   --------------
    3737! to use  'getin'
    38       USE ioipsl_getincom
     38      use ioipsl_getincom, only: getin
     39      use control_mod, only: ndynstep, day_step, iperiod, iconser,
     40     &                       idissip, iphysiq, anneeref, ecritphy,
     41     &                       ecritstart, timestart, nday_r
    3942      IMPLICIT NONE
    4043
    4144#include "dimensions.h"
    4245#include "paramet.h"
    43 #include "control.h"
     46!#include "control.h"
    4447#include "logic.h"
    4548#include "serre.h"
     
    8386!le modele martien et ne sont donc plus lues dans "run.def"
    8487
    85         anneeref=0
    86         ! Note: anneref is a common in 'control.h'
     88      anneeref=0
    8789
    8890      OPEN(tapedef,file='run.def',status='old',form='formatted'
  • trunk/LMDZ.MARS/libf/dyn3d/dynetat0.F

    r1036 r1130  
    33     
    44      use netcdf
    5       use infotrac, only: tnom
     5      use infotrac, only: tname
     6      use control_mod, only: timestart
    67     
    78      IMPLICIT NONE
     
    3940#include "logic.h"
    4041!#include "advtrac.h"
    41 #include "control.h"
     42!#include "control.h"
    4243
    4344c   Arguments:
     
    381382!           WRITE(str3(2:3),'(i2.2)') iq
    382383!           ierr =  NF_INQ_VARID (nid, str3, nvarid)
    383 ! NB: tracers are now read in using their name ('tnom' from infotrac)
    384 !           write(*,*) "  loading tracer:",trim(tnom(iq))
    385            ierr=nf90_inq_varid(nid,tnom(iq),nvarid)
     384! NB: tracers are now read in using their name ('tname' from infotrac)
     385!           write(*,*) "  loading tracer:",trim(tname(iq))
     386           ierr=nf90_inq_varid(nid,tname(iq),nvarid)
    386387           IF (ierr .NE. nf90_noerr) THEN
    387388!              PRINT*, "dynetat0: Le champ <"//str3//"> est absent"
    388               PRINT*, "dynetat0: Le champ <"//trim(tnom(iq))//
     389              PRINT*, "dynetat0: Le champ <"//trim(tname(iq))//
    389390     &                "> est absent"
    390391              PRINT*, "          Il est donc initialise a zero"
     
    396397             IF (ierr .NE. nf90_noerr) THEN
    397398!                 PRINT*, "dynetat0: Lecture echouee pour "//str3
    398                PRINT*, "dynetat0: Lecture echouee pour "//trim(tnom(iq))
     399               PRINT*,"dynetat0: Lecture echouee pour "//trim(tname(iq))
    399400               CALL abort
    400401             ENDIF
  • trunk/LMDZ.MARS/libf/dyn3d/dynredem.F

    r1106 r1130  
    11      SUBROUTINE dynredem0(fichnom,idayref,anneeref,phis,nq)
    2       use infotrac, only: tnom
     2      use infotrac, only: tname
    33      IMPLICIT NONE
    44c=======================================================================
     
    912912!               ierr = NF_PUT_ATT_TEXT (nid, nvarid, "title", 12,
    913913!     .                          "Traceurs "//str3)
    914              txt="Traceur "//trim(tnom(iq))
    915 #ifdef NC_DOUBLE
    916                ierr=NF_DEF_VAR(nid,tnom(iq),NF_DOUBLE,4,dims4,nvarid)
    917 #else
    918                ierr=NF_DEF_VAR(nid,tnom(iq),NF_FLOAT,4,dims4,nvarid)
     914             txt="Traceur "//trim(tname(iq))
     915#ifdef NC_DOUBLE
     916               ierr=NF_DEF_VAR(nid,tname(iq),NF_DOUBLE,4,dims4,nvarid)
     917#else
     918               ierr=NF_DEF_VAR(nid,tname(iq),NF_FLOAT,4,dims4,nvarid)
    919919#endif
    920920               ierr=NF_PUT_ATT_TEXT(nid,nvarid,"title",
     
    964964      SUBROUTINE dynredem1(fichnom,time,
    965965     .                     vcov,ucov,teta,q,nq,masse,ps)
    966       use infotrac, only: nqtot, tnom
     966      use infotrac, only: nqtot, tname
    967967      IMPLICIT NONE
    968968c=================================================================
     
    11051105!            WRITE(str3(2:3),'(i2.2)') iq
    11061106!            ierr = NF_INQ_VARID(nid, str3, nvarid)
    1107             ierr=NF_INQ_VARID(nid,tnom(iq),nvarid)
     1107            ierr=NF_INQ_VARID(nid,tname(iq),nvarid)
    11081108            IF (ierr .NE. NF_NOERR) THEN
    11091109!               PRINT*, "Variable "//str3//" n est pas definie"
    1110               PRINT*, "Variable "//trim(tnom(iq))//" n est pas definie"
     1110              PRINT*, "Variable "//trim(tname(iq))//" n est pas definie"
    11111111              CALL abort
    11121112            ENDIF
  • trunk/LMDZ.MARS/libf/dyn3d/gcm.F

    r1036 r1130  
    22
    33      use infotrac, only: iniadvtrac, nqtot, iadv
     4      use control_mod, only: day_step, iperiod, iphysiq, ndynstep,
     5     &                       nday_r, idissip, iconser, ecritstart,
     6     &                       ecritphy
     7      use comgeomphy, only: initcomgeomphy
    48      IMPLICIT NONE
    59
     
    4246#include "logic.h"
    4347#include "temps.h"
    44 #include "control.h"
     48!#include "control.h"
    4549#include "ener.h"
    4650#include "netcdf.inc"
     
    135139      logical callgroupeun
    136140      parameter (callgroupeun = .false.)
     141
     142c-----------------------------------------------------------------------
     143c    variables pour l'initialisation de la physique :
     144c    ------------------------------------------------
     145      INTEGER ngridmx
     146      PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
     147      REAL zcufi(ngridmx),zcvfi(ngridmx)
     148      REAL latfi(ngridmx),lonfi(ngridmx)
     149      REAL airefi(ngridmx)
     150      SAVE latfi, lonfi, airefi
     151      INTEGER i,j
     152
    137153c-----------------------------------------------------------------------
    138154c   Initialisations:
     
    145161c-----------------------------------------------------------------------
    146162      CALL defrun_new( 99, .TRUE. )
     163
     164!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     165! FH 2008/05/02
     166! A nettoyer. On ne veut qu'une ou deux routines d'interface
     167! dynamique -> physique pour l'initialisation
     168!#ifdef CPP_PHYS
     169      CALL init_phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
     170      call initcomgeomphy
     171!#endif
     172!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    147173
    148174! Initialize tracers
     
    196222c
    197223
     224c-----------------------------------------------------------------------
     225c   Initialisation de la physique :
     226c   -------------------------------
     227
     228!      IF (call_iniphys.and.(iflag_phys==1.or.iflag_phys>=100)) THEN
     229         latfi(1)=rlatu(1)
     230         lonfi(1)=0.
     231         zcufi(1) = cu(1)
     232         zcvfi(1) = cv(1)
     233         DO j=2,jjm
     234            DO i=1,iim
     235               latfi((j-2)*iim+1+i)= rlatu(j)
     236               lonfi((j-2)*iim+1+i)= rlonv(i)
     237               zcufi((j-2)*iim+1+i) = cu((j-1)*iip1+i)
     238               zcvfi((j-2)*iim+1+i) = cv((j-1)*iip1+i)
     239            ENDDO
     240         ENDDO
     241         latfi(ngridmx)= rlatu(jjp1)
     242         lonfi(ngridmx)= 0.
     243         zcufi(ngridmx) = cu(ip1jm+1)
     244         zcvfi(ngridmx) = cv(ip1jm-iim)
     245
     246         ! build airefi(), mesh area on physics grid
     247         CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi)
     248         ! Poles are single points on physics grid
     249         airefi(1)=airefi(1)*iim
     250         airefi(ngridmx)=airefi(ngridmx)*iim
     251
     252! Initialisation de la physique: pose probleme quand on tourne
     253! SANS physique, car iniphysiq.F est dans le repertoire phy[]...
     254! Il faut une cle CPP_PHYS
     255!#ifdef CPP_PHYS
     256!         CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys,
     257         CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys,
     258     &                latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp,
     259     &                1)
     260!     &                iflag_phys)
     261!#endif
     262!         call_iniphys=.false.
     263!      ENDIF ! of IF (call_iniphys.and.(iflag_phys.eq.1))
     264!        call inifis(ngridmx,llm,nqtot,day_ini,daysec,dtphys,
     265!     .                latfi,lonfi,airefi,rad,g,r,cpp)
    198266
    199267      call dump2d(iip1,jjp1,ps,'PRESSION SURFACE')
  • trunk/LMDZ.MARS/libf/dyn3d/infotrac.F90

    r1036 r1130  
    55  INTEGER, SAVE :: nqtot
    66  INTEGER,allocatable :: iadv(:)   ! tracer advection scheme number
    7   CHARACTER(len=20),allocatable ::  tnom(:) ! tracer name
     7  CHARACTER(len=20),allocatable ::  tname(:) ! tracer name
    88
    99CONTAINS
     
    1818      IMPLICIT NONE
    1919
    20 #include "dimensions.h"
     20!#include "dimensions.h"
    2121!#include "advtrac.h"
    22 #include "control.h"
     22!#include "control.h"
    2323
    2424! routine arguments:
     
    4747        ! allocate arrays:
    4848        allocate(iadv(nq))
    49         allocate(tnom(nq))
     49        allocate(tname(nq))
    5050       
    5151        ! initialize advection schemes to Van-Leer for all tracers
     
    5656        do iq=1,nq
    5757        ! minimal version, just read in the tracer names, 1 per line
    58           read(90,*,iostat=ierr) tnom(iq)
     58          read(90,*,iostat=ierr) tname(iq)
    5959          if (ierr.ne.0) then
    6060            write(*,*) 'iniadvtrac: error reading tracer names...'
  • trunk/LMDZ.MARS/libf/dyn3d/ini_archive.F

    r1047 r1130  
    4848#include "description.h"
    4949#include "serre.h"
    50 #include "control.h"
     50!#include "control.h"
    5151!#include"comsoil.h"
    5252
  • trunk/LMDZ.MARS/libf/dyn3d/iniconst.F

    r38 r1130  
    11      SUBROUTINE iniconst
    22
     3      use control_mod, only: iphysiq, idissip
    34      IMPLICIT NONE
    45c
     
    1314#include "comconst.h"
    1415#include "temps.h"
    15 #include "control.h"
     16!#include "control.h"
    1617#include "comvert.h"
    1718
  • trunk/LMDZ.MARS/libf/dyn3d/inidissip.F

    r758 r1130  
    88c   -------------
    99
     10      use control_mod, only: idissip, iperiod
    1011      IMPLICIT NONE
    1112#include "dimensions.h"
     
    1415#include "comconst.h"
    1516#include "comvert.h"
    16 #include "control.h"
     17!#include "control.h"
    1718
    1819      LOGICAL lstardis
  • trunk/LMDZ.MARS/libf/dyn3d/lect_start_archive.F

    r1047 r1130  
    1717c
    1818c=======================================================================
    19       use infotrac, only: tnom
     19      use infotrac, only: tname
    2020      use comsoil_h, only: nsoilmx, layer, mlayer, volcapa, inertiedat
    2121      implicit none
     
    3232#include "comvert.h"
    3333#include "comgeom2.h"
    34 #include "control.h"
     34!#include "control.h"
    3535#include "logic.h"
    3636#include "description.h"
    3737#include "ener.h"
    3838#include "temps.h"
    39 #include "lmdstd.h"
     39!#include "lmdstd.h"
    4040#include "netcdf.inc"
    4141!#include "tracer.h"
     
    760760          write(txt,'(a5,i2.2)')'qsurf',iq
    761761        ELSE
    762           txt=trim(tnom(iq))//"_surf"
     762          txt=trim(tname(iq))//"_surf"
    763763          if (txt.eq."h2o_vap") then
    764764            ! There is no surface tracer for h2o_vap;
     
    948948          write(txt,'(a1,i2.2)')'q',iq
    949949        ELSE
    950           txt=tnom(iq)
     950          txt=tname(iq)
    951951        ENDIF
    952952        write(*,*)"lect_start_archive: loading tracer ",trim(txt)
  • trunk/LMDZ.MARS/libf/dyn3d/write_archive.F

    r1047 r1130  
    3838#include "dimphys.h"
    3939#include "paramet.h"
    40 #include "control.h"
     40!#include "control.h"
    4141#include "comvert.h"
    4242#include "comgeom.h"
  • trunk/LMDZ.MARS/libf/dyn3d/writediagdyn.F90

    r410 r1130  
    1212! NB: the rate a which outputs are made can be changed (see parameter isample)
    1313!
     14use control_mod, only: iphysiq, day_step
    1415implicit none
    1516
    1617#include"dimensions.h"
    1718#include"paramet.h"
    18 #include"control.h"
     19!#include"control.h"
    1920#include"netcdf.inc"
    2021
Note: See TracChangeset for help on using the changeset viewer.