Ignore:
Timestamp:
Aug 7, 2009, 1:48:33 PM (16 years ago)
Author:
Ehouarn Millour
Message:

Changes and cleanups to enable compiling without physics
and without ioipsl.

IOIPSL related cleanups:

  • bibio/writehist.F encapsulate the routine (which needs IOIPSL to function)

with #ifdef IOIPSL flag.

  • dyn3d/abort_gcm.F, dyn3dpar/abort_gcm.F and dyn3dpar/getparam.F90: use ioipsl_getincom module when not compiling with IOIPSL library, in order to always be able to use getin() routine.
  • removed unused "use IOIPSL" in dyn3dpar/guide_p_mod.F90
  • calendar related issue: Initialize day_ref and annee_ref in iniacademic.F (i.e. when they are not read from start.nc file)

Earth-specific programs/routines/modules:
create_etat0.F, fluxstokenc.F, limit_netcdf.F, startvar.F
(versions in dyn3d and dyn3dpar)
These routines and modules, which by design and porpose are made to function with
Earth physics are encapsulated with #CPP_EARTH cpp flag.

Earth-specific instructions:

  • calls to qminimum (specific treatment of first 2 tracers, i.e. water) in dyn3d/caladvtrac.F, dyn3d/integrd.F, dyn3dpar/caladvtrac_p.F, dyn3dpar/integrd_p.F only if (planet_type == 'earth')

Interaction with parallel physics:

  • routine dyn3dpar/parallel.F90 uses "surface_data" module (which is in the physics ...) to know value of "type_ocean" . Encapsulated that with #ifdef CPP_EARTH and set to a default type_ocean="dummy" otherwise.
  • So far, only Earth physics are parallelized, so all the interaction between parallel dynamics and parallel physics are encapsulated with #ifdef CCP_EARTH (this way we can run parallel without any physics). The (dyn3dpar) routines which contains such interaction are: bands.F90, gr_dyn_fi_p.F, gr_fi_dyn_p.F, mod_interface_dyn_phys.F90 This should later (when improving dyn/phys interface) be encapsulated with a more general and appropriate #ifdef CPP_PHYS cpp flag.

I checked that these changes do not alter results (on the simple
32x24x11 bench) on Ciclad (seq & mpi), Brodie (seq, mpi & omp) and
Vargas (seq, mpi & omp).

EM

Location:
LMDZ4/branches/LMDZ4-dev/libf/dyn3d
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/abort_gcm.F

    r1200 r1222  
    88#ifdef CPP_IOIPSL
    99      USE IOIPSL
     10#else
     11! if not using IOIPSL, we still need to use (a local version of) getin_dump
     12      USE ioipsl_getincom
    1013#endif
    1114#include "iniprint.h"
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/caladvtrac.F

    r1114 r1222  
    7676           ENDDO
    7777          ENDDO
    78 
    79           CALL qminimum( q, 2, finmasse )
     78         
     79          if (planet_type.eq."earth") then
     80! Earth-specific treatment of first 2 tracers (water)
     81            CALL qminimum( q, 2, finmasse )
     82          endif
    8083
    8184          CALL SCOPY   ( ip1jmp1*llm, masse, 1, finmasse,       1 )
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/calfis.F

    r1201 r1222  
    177177c    --------------------
    178178c
    179 
    180       IF (ngridmx.NE.2+(jjm-1)*iim) THEN
     179c
     180      IF ( firstcal )  THEN
     181        debut = .TRUE.
     182        IF (ngridmx.NE.2+(jjm-1)*iim) THEN
    181183         PRINT*,'STOP dans calfis'
    182184         PRINT*,'La dimension ngridmx doit etre egale a 2 + (jjm-1)*iim'
     
    184186         PRINT*,ngridmx,jjm,iim
    185187         STOP
    186       ENDIF
    187 
    188 c-----------------------------------------------------------------------
    189 c   latitude, longitude et aires des mailles pour la physique:
    190 c   ----------------------------------------------------------
    191 
    192 c
    193       IF ( firstcal )  THEN
    194           debut = .TRUE.
     188        ENDIF
    195189      ELSE
    196           debut = .FALSE.
    197       ENDIF
     190        debut = .FALSE.
     191      ENDIF ! of IF (firstcal)
    198192
    199193c
     
    290284
    291285c   convergence dynamique pour les traceurs "EAU"
    292 
    293       DO iq=1,2
     286! Earth-specific treatment of first 2 tracers (water)
     287       if (planet_type=="earth") then
     288        DO iq=1,2
    294289         DO l=1,llm
    295290            pcvgq(1,l,iq)= pdq(1,1,l,iq) / pmasse(1,1,l)
     
    303298            pcvgq(ig0,l,iq)= pdq(1,jjp1,l,iq) / pmasse(1,jjp1,l)
    304299         ENDDO
    305       ENDDO
     300        ENDDO
     301       endif ! of if (planet_type=="earth")
    306302
    307303
     
    428424      ENDDO
    429425c
     426      if (planet_type=="earth") then
     427#ifdef CPP_EARTH
    430428cIM calcul PV a teta=350, 380, 405K
    431429      CALL PVtheta(ngridmx,llm,pucov,pvcov,pteta,
    432430     $           ztfi,zplay,zplev,
    433431     $           ntetaSTD,rtetaSTD,PVteta)
     432#endif
     433      endif
    434434c
    435435c On change de grille, dynamique vers physiq, pour le flux de masse verticale
     
    441441
    442442
     443      if (planet_type=="earth") then
     444#ifdef CPP_EARTH
    443445      CALL physiq (ngridmx,
    444446     .             llm,
     
    467469     .             pducov,
    468470     .             PVteta)
     471#endif
     472      endif !of if (planet_type=="earth")
    469473
    470474500   CONTINUE
     
    502506c   62. humidite specifique
    503507c   ---------------------
    504 
    505       DO iq=1,nqtot
    506          DO l=1,llm
    507             DO i=1,iip1
    508                pdqfi(i,1,l,iq)    = zdqfi(1,l,iq)
    509                pdqfi(i,jjp1,l,iq) = zdqfi(ngridmx,l,iq)
    510             ENDDO
    511             DO j=2,jjm
    512                ig0=1+(j-2)*iim
    513                DO i=1,iim
    514                   pdqfi(i,j,l,iq) = zdqfi(ig0+i,l,iq)
    515                ENDDO
    516                pdqfi(iip1,j,l,iq) = pdqfi(1,j,l,iq)
    517             ENDDO
    518          ENDDO
    519       ENDDO
     508! Ehouarn: removed this useless bit: was overwritten at step 63 anyways
     509!      DO iq=1,nqtot
     510!         DO l=1,llm
     511!            DO i=1,iip1
     512!               pdqfi(i,1,l,iq)    = zdqfi(1,l,iq)
     513!               pdqfi(i,jjp1,l,iq) = zdqfi(ngridmx,l,iq)
     514!            ENDDO
     515!            DO j=2,jjm
     516!               ig0=1+(j-2)*iim
     517!               DO i=1,iim
     518!                  pdqfi(i,j,l,iq) = zdqfi(ig0+i,l,iq)
     519!               ENDDO
     520!               pdqfi(iip1,j,l,iq) = pdqfi(1,j,l,iq)
     521!            ENDDO
     522!         ENDDO
     523!      ENDDO
    520524
    521525c   63. traceurs
    522526c   ------------
    523527C     initialisation des tendances
    524       pdqfi=0.
     528      pdqfi(:,:,:,:)=0.
    525529C
    526530      DO iq=1,nqtot
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/create_etat0_limit.F

    r1220 r1222  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44       PROGRAM create_etat0_limit
     5#ifdef CPP_EARTH
     6! This prog. is designed to work for Earth
    57       USE dimphy
    68       USE comgeomphy
     
    67691     FORMAT(//)
    6870
     71#endif
     72! of #ifdef CPP_EARTH
    6973      STOP
    7074      END
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/fluxstokenc.F

    r1114 r1222  
     1!
     2! $Id$
     3!
    14      SUBROUTINE fluxstokenc(pbaru,pbarv,masse,teta,phi,phis,
    25     . time_step,itau )
     6#ifdef CPP_EARTH
     7! This routine is designed to work for Earth and with ioipsl
    38
    49       USE IOIPSL
     
    1823#include "tracstoke.h"
    1924#include "temps.h"
     25#include "iniprint.h"
    2026
    2127      REAL time_step,t_wrt, t_ops
     
    159165      ENDIF ! if iadvtr.EQ.istdyn
    160166
     167#else
     168      write(lunout,*)
     169     & 'fluxstokenc: Needs Earth physics (and ioipsl) to function'
     170#endif
     171! of #ifdef CPP_EARTH
    161172      RETURN
    162173      END
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/gcm.F

    r1220 r1222  
    307307     .  ' restart ne correspondent pas a celles lues dans '
    308308        write(lunout,*)' gcm.def'
     309        write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
     310        write(lunout,*)' day_ref=',day_ref," dayref=",dayref
    309311        if (raz_date .ne. 1) then
    310312          write(lunout,*)
     
    324326      endif
    325327
     328#ifdef CPP_IOIPSL
    326329      mois = 1
    327330      heure = 0.
     
    330333      jD_ref = int(jD_ref)
    331334
    332 #ifdef CPP_IOIPSL
    333335      call ioconf_startdate(annee_ref,1,day_ref, 0.)
    334 #endif
    335336
    336337      write(lunout,*)'DEBUG'
     
    340341      write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
    341342      write(lunout,*)jD_ref+jH_ref,an, mois, jour, heure
     343#else
     344! Ehouarn: we still need to define JD_ref and JH_ref
     345! and since we don't know how many days there are in a year
     346! we set JD_ref to 0 (this should be improved ...)
     347      jD_ref=0
     348      jH_ref=0
     349#endif
    342350
    343351c  nombre d'etats dans les fichiers demarrage et histoire
     
    413421      WRITE(lunout,300)day_ini,day_end
    414422 300  FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
     423
     424#ifdef CPP_IOIPSL
    415425      call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
    416426      write (lunout,301)jour, mois, an
     
    419429 301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
    420430 302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
     431#endif
    421432
    422433      if (planet_type.eq."earth") then
    423 #ifdef CPP_EARTH
    424       CALL dynredem0("restart.nc", day_end, phis)
    425 #endif
     434        CALL dynredem0("restart.nc", day_end, phis)
    426435      endif
    427436
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/iniacademic.F

    r1140 r1222  
    8383c
    8484        time_0=0.
     85        day_ref=0
     86        annee_ref=0
    8587
    8688        im         = iim
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/integrd.F

    r1114 r1222  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      SUBROUTINE integrd
     
    3232#include "temps.h"
    3333#include "serre.h"
     34#include "control.h"
    3435
    3536c   Arguments:
     
    183184c$$$      ENDIF
    184185
    185          DO l = 1, llm
    186           DO ij = 1, ip1jmp1
    187            deltap(ij,l) =  p(ij,l) - p(ij,l+1)
     186         if (planet_type.eq."earth") then
     187! Earth-specific treatment of first 2 tracers (water)
     188          DO l = 1, llm
     189           DO ij = 1, ip1jmp1
     190            deltap(ij,l) =  p(ij,l) - p(ij,l+1)
     191           ENDDO
    188192          ENDDO
    189          ENDDO
    190 
    191          CALL qminimum( q, nq, deltap )
     193
     194          CALL qminimum( q, nq, deltap )
     195         endif ! of if (planet_type.eq."earth")
     196
    192197c
    193198c    .....  Calcul de la valeur moyenne, unique  aux poles pour  q .....
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/leapfrog.F

    r1220 r1222  
    597597
    598598              if (planet_type.eq."earth") then
    599 #ifdef CPP_EARTH
    600599! Write an Earth-format restart file
    601600                CALL dynredem1("restart.nc",0.0,
    602601     &                         vcov,ucov,teta,q,masse,ps)
    603 #endif
    604602              endif ! of if (planet_type.eq."earth")
    605603
     
    704702              IF(itau.EQ.itaufin) THEN
    705703                if (planet_type.eq."earth") then
    706 #ifdef CPP_EARTH
    707704                  CALL dynredem1("restart.nc",0.0,
    708705     &                           vcov,ucov,teta,q,masse,ps)
    709 #endif
    710706                endif ! of if (planet_type.eq."earth")
    711707              ENDIF ! of IF(itau.EQ.itaufin)
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/limit_netcdf.F

    r997 r1222  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44C
    55C
    66      SUBROUTINE limit_netcdf(interbar, extrap, oldice, masque)
     7#ifdef CPP_EARTH
     8! This routine is designed to work for Earth
    79      USE dimphy
    810      use phys_state_var_mod , ONLY : pctsrf
     
    3335cy#include "dimphy.h"
    3436#include "indicesol.h"
     37#include "iniprint.h"
    3538c
    3639c-----------------------------------------------------------------------
     
    13231326      ierr = NF_CLOSE(nid)
    13241327c
     1328#else
     1329      WRITE(lunout,*)
     1330     & 'limit_netcdf: Earth-specific routine, needs Earth physics'
     1331#endif
     1332! of #ifdef CPP_EARTH
    13251333      STOP
    13261334      END
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/startvar.F

    r677 r1222  
    11!
    2 ! $Header$
     2! $Id$
    33!
    4 C
    5 C
    64      MODULE startvar
     5#ifdef CPP_EARTH
     6! This module is designed to work for Earth (and with ioipsl)
    77    !
    88    !
     
    11891189      END SUBROUTINE start_inter_3d
    11901190    !
     1191#endif
     1192! of #ifdef CPP_EARTH
    11911193      END MODULE startvar
Note: See TracChangeset for help on using the changeset viewer.