Ignore:
Timestamp:
Jun 18, 2009, 11:20:44 AM (15 years ago)
Author:
Ehouarn Millour
Message:

Cleanup around IOIPSL, so that LMDZ dynamics may be used without IOIPSL.

  • moved ersatz IOIPSL routines (ioipsl_* , taken from IOIPSLv2_1_8, so that 'getin' function may be used even if not using the IOIPSL library) from dyn3d/dyn3dpar to bibio.
  • enclosed 'use ioipsl' instruction with #ifdef CPP_IOIPSL cpp keys.

EM

Location:
LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar
Files:
2 deleted
11 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/bilan_dyn_p.F

    r985 r1186  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      SUBROUTINE bilan_dyn_p (ntrac,dt_app,dt_cum,
     
    1010c             vQ..A=Cp T + L * ...
    1111
     12#ifdef CPP_IOIPSL
    1213      USE IOIPSL
     14#endif
    1315      USE parallel
    1416      USE mod_hallo
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/diagedyn.F

    r1140 r1186  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44
     
    315315C
    316316#else
    317       write(lunout,*),'diagedyn: Needs Earth physics to function'
     317      write(lunout,*)'diagedyn: Needs Earth physics to function'
    318318#endif
    319319! #endif of #ifdef CPP_EARTH
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/dynredem.F

    r1114 r1186  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44c
    55      SUBROUTINE dynredem0(fichnom,iday_end,phis)
     6#ifdef CPP_IOIPSL
    67      USE IOIPSL
     8#endif
    79      USE infotrac
    810      IMPLICIT NONE
     
    5557
    5658c-----------------------------------------------------------------------
    57       modname='dynredem'
    58 
     59      modname='dynredem0'
     60
     61#ifdef CPP_IOIPSL
    5962      call ymds2ju(annee_ref, 1, iday_end, 0.0, zjulian)
    6063      call ju2ymds(zjulian, yyears0, mmois0, jjour0, hours)
    61        
     64#else
     65! set yyears0, mmois0, jjour0 to 0,1,1 (hours is not used)
     66      yyears0=0
     67      mmois0=1
     68      jjour0=1
     69#endif       
    6270
    6371      DO l=1,length
     
    457465      dims4(3) = idim_s
    458466      dims4(4) = idim_tim
    459 
     467      IF(nqtot.GE.1) THEN
    460468      DO iq=1,nqtot
    461469cIM 220306 BEG
     
    468476      ierr = NF_PUT_ATT_TEXT (nid, nvarid, "title", 12,ttext(iq))
    469477      ENDDO
     478      ENDIF
    470479c
    471480      dims4(1) = idim_rlonv
     
    631640      END IF
    632641
     642      IF(nqtot.GE.1) THEN
    633643      do iq=1,nqtot
    634644
     
    701711     
    702712      ENDDO
     713      ENDIF
    703714c
    704715      ierr = NF_INQ_VARID(nid, "masse", nvarid)
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/dynredem_p.F

    r1114 r1186  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44c
    55      SUBROUTINE dynredem0_p(fichnom,iday_end,phis)
     6#ifdef CPP_IOIPSL
    67      USE IOIPSL
     8#endif
    79      USE parallel
    810      USE infotrac
     
    5759      if (mpi_rank==0) then
    5860     
    59       modname='dynredem'
    60 
     61      modname='dynredem0_p'
     62
     63#ifdef CPP_IOIPSL
    6164      call ymds2ju(annee_ref, 1, iday_end, 0.0, zjulian)
    6265      call ju2ymds(zjulian, yyears0, mmois0, jjour0, hours)
    63        
     66#else
     67! set yyears0, mmois0, jjour0 to 0,1,1 (hours is not used)
     68      yyears0=0
     69      mmois0=1
     70      jjour0=1
     71#endif               
    6472
    6573      DO l=1,length
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/getparam.F90

    r774 r1186  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44MODULE getparam
     5#ifdef CPP_IOIPSL
    56   USE IOIPSL
     7#else
     8! if not using IOIPSL, we still need to use (a local version of) getin
     9   USE ioipsl_getincom
     10#endif
     11
    612   INTERFACE getpar
    713     MODULE PROCEDURE ini_getparam,fin_getparam,getparamr,getparami,getparaml
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/initdynav_p.F

    r1114 r1186  
    11!
    2 ! $Header$
     2! $Id$
    33!
    4 c
    5 c
    64      subroutine initdynav_p(infile,day0,anne0,tstep,t_ops,t_wrt,fileid)
    75
     6#ifdef CPP_IOIPSL
     7! This routine needs IOIPSL
    88       USE IOIPSL
     9#endif
    910       use parallel
    1011       use Write_field
     
    5051#include "description.h"
    5152#include "serre.h"
     53#include "iniprint.h"
    5254
    5355C   Arguments
     
    5759      real tstep, t_ops, t_wrt
    5860      integer fileid
     61
     62#ifdef CPP_IOIPSL
     63! This routine needs IOIPSL
     64C   Variables locales
     65C
    5966      integer thoriid, zvertiid
    60 
    61 C   Variables locales
    62 C
    6367      integer tau0
    6468      real zjulian
     
    193197C
    194198      call histend(fileid)
     199#else
     200      write(lunout,*)'initdynav_p: Needs IOIPSL to function'
     201#endif
     202! #endif of #ifdef CPP_IOIPSL
    195203      return
    196204      end
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/initfluxsto_p.F

    r1114 r1186  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      subroutine initfluxsto_p
     
    66     .                    fileid,filevid,filedid)
    77
     8#ifdef CPP_IOIPSL
     9! This routine needs IOIPSL
    810       USE IOIPSL
     11#endif
    912       use parallel
    1013       use Write_field
     
    5053#include "description.h"
    5154#include "serre.h"
     55#include "iniprint.h"
    5256
    5357C   Arguments
    5458C
    5559      character*(*) infile
    56       integer*4 itau
    5760      real tstep, t_ops, t_wrt
    5861      integer fileid, filevid,filedid
    59       integer ndex(1)
     62
     63#ifdef CPP_IOIPSL
     64! This routine needs IOIPSL
     65C   Variables locales
     66C
    6067      real nivd(1)
    61 
    62 C   Variables locales
    63 C
    6468      integer tau0
    6569      real zjulian
     
    285289      endif
    286290       
     291#else
     292      write(lunout,*)'initfluxsto_p: Needs IOIPSL to function'
     293#endif
     294! #endif of #ifdef CPP_IOIPSL
    287295      return
    288296      end
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/inithist_p.F

    r1114 r1186  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      subroutine inithist_p(infile,day0,anne0,tstep,t_ops,t_wrt,
    55     .                      fileid,filevid)
    66
     7#ifdef CPP_IOIPSL
     8! This routine needs IOIPSL
    79       USE IOIPSL
     10#endif
    811       use parallel
    912       use Write_field
     
    5053#include "description.h"
    5154#include "serre.h"
     55#include "iniprint.h"
    5256
    5357C   Arguments
     
    5862      integer fileid, filevid
    5963
     64#ifdef CPP_IOIPSL
     65! This routine needs IOIPSL
    6066C   Variables locales
    6167C
     
    244250      call histend(fileid)
    245251      call histend(filevid)
     252#else
     253      write(lunout,*)'inithist_p: Needs IOIPSL to function'
     254#endif
     255! #endif of #ifdef CPP_IOIPSL
    246256      return
    247257      end
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/mod_const_para.F90

    r1014 r1186  
     1!
     2! $Id$
     3!
    14MODULE mod_const_mpi
    25
     
    811
    912  SUBROUTINE Init_const_mpi
     13#ifdef CPP_IOIPSL
    1014    USE IOIPSL
     15#else
     16! if not using IOIPSL, we still need to use (a local version of) getin
     17    USE ioipsl_getincom
     18#endif
    1119
    1220    IMPLICIT NONE
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/writedynav_p.F

    r1118 r1186  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      subroutine writedynav_p( histid, time, vcov,
    55     ,                          ucov,teta,ppk,phi,q,masse,ps,phis)
    66
     7#ifdef CPP_IOIPSL
     8! This routine needs IOIPSL
    79      USE ioipsl
     10#endif
    811      USE parallel
    912      USE misc_mod
     
    4750#include "description.h"
    4851#include "serre.h"
     52#include "iniprint.h"
    4953
    5054C
     
    6165
    6266
     67#ifdef CPP_IOIPSL
     68! This routine needs IOIPSL
    6369C   Variables locales
    6470C
     
    156162C
    157163      if (ok_sync) call histsync(histid)
     164#else
     165      write(lunout,*)'writedynav_p: Needs IOIPSL to function'
     166#endif
     167! #endif of #ifdef CPP_IOIPSL
    158168      return
    159169      end
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/writehist_p.F

    r1114 r1186  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      subroutine writehist_p( histid, histvid, time, vcov,
    55     ,                          ucov,teta,phi,q,masse,ps,phis)
    66
     7#ifdef CPP_IOIPSL
     8! This routine needs IOIPSL
    79      USE ioipsl
     10#endif
    811      USE parallel
    912      USE misc_mod
     
    4851#include "description.h"
    4952#include "serre.h"
     53#include "iniprint.h"
    5054
    5155C
     
    6165      integer time
    6266
    63 
     67#ifdef CPP_IOIPSL
     68! This routine needs IOIPSL
    6469C   Variables locales
    6570C
     
    144149        call histsync(histvid)
    145150      endif
     151#else
     152      write(lunout,*)'writehist_p: Needs IOIPSL to function'
     153#endif
     154! #endif of #ifdef CPP_IOIPSL
    146155      return
    147156      end
Note: See TracChangeset for help on using the changeset viewer.