Ignore:
Timestamp:
Jul 22, 2002, 10:50:58 AM (22 years ago)
Author:
lmdzadmin
Message:

Champs supplementaire dans le coupleur (calving) + dependance des routines
"couplees" aux include
LF

Location:
LMDZ.3.3/branches/rel-LF/libf/phylmd
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • LMDZ.3.3/branches/rel-LF/libf/phylmd/interface_surf.F90

    r394 r397  
    4343  real, allocatable, dimension(:),save    :: coastalflow, riverflow
    4444!!$PB
    45   REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: tmp_rriv, tmp_rcoa
     45!!  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: tmp_rriv, tmp_rcoa
    4646!! pour simuler la fonte des glaciers antarctiques
    4747  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: coeff_iceberg
     
    276276      endif
    277277!!$PB
    278       ALLOCATE (tmp_rriv(iim,jjm+1), stat=error)
    279       if (error /= 0) then
    280         abort_message='Pb allocation tmp_rriv'
    281         call abort_gcm(modname,abort_message,1)
    282       endif
    283       ALLOCATE (tmp_rcoa(iim,jjm+1), stat=error)
    284       if (error /= 0) then
    285         abort_message='Pb allocation tmp_rcoa'
    286         call abort_gcm(modname,abort_message,1)
    287       endif
     278!!      ALLOCATE (tmp_rriv(iim,jjm+1), stat=error)
     279! !     if (error /= 0) then
     280!!        abort_message='Pb allocation tmp_rriv'
     281 !!       call abort_gcm(modname,abort_message,1)
     282!!      endif
     283!!      ALLOCATE (tmp_rcoa(iim,jjm+1), stat=error)
     284!!      if (error /= 0) then
     285!!        abort_message='Pb allocation tmp_rcoa'
     286!!        call abort_gcm(modname,abort_message,1)
     287!!      endif
    288288!!$
    289289    else if (size(coastalflow) /= knon) then
     
    793793  real, dimension(klon) :: cdrag
    794794
    795   include 'temps.inc'
     795#include "temps.inc"
    796796
    797797  if (check) write(*,*)'Entree ', modname
     
    10221022    bidule=0.
    10231023    bidule(1:knon)=riverflow(1:knon)
    1024     call gath2cpl(bidule, tmp_rriv, klon, knon,iim,jjm,ktindex)
     1024!    call gath2cpl(bidule, tmp_rriv, klon, knon,iim,jjm,ktindex)
    10251025    bidule=0.
    10261026    bidule(1:knon)=coastalflow(1:knon)
    1027     call gath2cpl(bidule, tmp_rcoa, klon, knon,iim,jjm,ktindex)
     1027!    call gath2cpl(bidule, tmp_rcoa, klon, knon,iim,jjm,ktindex)
    10281028    alb_new(1:knon) = albedo_out(1:knon,1)
    10291029    alblw(1:knon) = albedo_out(1:knon,2)
     
    11441144  real, allocatable, dimension(:,:,:),save :: tmp_snow, tmp_evap, tmp_tsol
    11451145  real, allocatable, dimension(:,:,:),save :: tmp_fder, tmp_albe, tmp_taux
    1146 !!$  real, allocatable, dimension(:,:,:),save :: tmp_tauy, tmp_rriv, tmp_rcoa
    1147   REAL, ALLOCATABLE, DIMENSION(:,:,:),SAVE :: tmp_tauy
     1146  real, allocatable, dimension(:,:,:),save :: tmp_tauy, tmp_rriv, tmp_rcoa
     1147!!  REAL, ALLOCATABLE, DIMENSION(:,:,:),SAVE :: tmp_tauy
    11481148! variables a passer au coupleur
    11491149  real, dimension(iim, jjm+1) :: wri_sol_ice, wri_sol_sea, wri_nsol_ice
     
    11811181  REAL :: zx_lon(iim,jjm+1), zx_lat(iim,jjm+1), zjulian
    11821182  integer :: idayref, itau_w
    1183   include 'param_cou.h'
    1184   include 'inc_cpl.h'
    1185   include 'temps.inc'
     1183#include "param_cou.h"
     1184#include "inc_cpl.h"
     1185#include "temps.inc"
    11861186!
    11871187! Initialisation
     
    13361336      cpl_tauy(ig,cpl_index) = cpl_tauy(ig,cpl_index) &
    13371337       &                          + tauy(ig)        / FLOAT(nexca)
    1338 !!$      cpl_rriv(ig,cpl_index) = cpl_rriv(ig,cpl_index) &
    1339 !!$       &                          + riverflow(ig)   / FLOAT(nexca)/dtime
    1340 !!$      cpl_rcoa(ig,cpl_index) = cpl_rcoa(ig,cpl_index) &
    1341 !!$       &                          + coastalflow(ig) / FLOAT(nexca)/dtime
     1338      cpl_rriv(ig,cpl_index) = cpl_rriv(ig,cpl_index) &
     1339       &                          + riverflow(ig)   / FLOAT(nexca)/dtime
     1340      cpl_rcoa(ig,cpl_index) = cpl_rcoa(ig,cpl_index) &
     1341       &                          + coastalflow(ig) / FLOAT(nexca)/dtime
    13421342    enddo
    1343     IF (cpl_index .EQ. 1) THEN
    1344         cpl_rriv(:,:) = cpl_rriv(:,:) + tmp_rriv(:,:) / FLOAT(nexca)
    1345         cpl_rcoa(:,:) = cpl_rcoa(:,:) + tmp_rcoa(:,:) / FLOAT(nexca)
    1346     ENDIF
     1343!    IF (cpl_index .EQ. 1) THEN
     1344!        cpl_rriv(:,:) = cpl_rriv(:,:) + tmp_rriv(:,:) / FLOAT(nexca)
     1345!       cpl_rcoa(:,:) = cpl_rcoa(:,:) + tmp_rcoa(:,:) / FLOAT(nexca)
     1346!    ENDIF
    13471347  endif
    13481348
     
    14421442      allocate(tmp_taux(iim,jjm+1,2), stat=error); sum_error = sum_error + error
    14431443      allocate(tmp_tauy(iim,jjm+1,2), stat=error); sum_error = sum_error + error
    1444 !!$      allocate(tmp_rriv(iim,jjm+1,2), stat=error); sum_error = sum_error + error
    1445 !!$      allocate(tmp_rcoa(iim,jjm+1,2), stat=error); sum_error = sum_error + error
     1444      allocate(tmp_rriv(iim,jjm+1,2), stat=error); sum_error = sum_error + error
     1445      allocate(tmp_rcoa(iim,jjm+1,2), stat=error); sum_error = sum_error + error
    14461446      if (sum_error /= 0) then
    14471447        abort_message='Pb allocation variables couplees pour l''ecriture'
     
    14651465    call gath2cpl(cpl_taux(1,cpl_index), tmp_taux(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
    14661466    call gath2cpl(cpl_tauy(1,cpl_index), tmp_tauy(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
    1467 !!$    call gath2cpl(cpl_rriv(1,cpl_index), tmp_rriv(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
    1468 !!$    call gath2cpl(cpl_rcoa(1,cpl_index), tmp_rcoa(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
     1467    call gath2cpl(cpl_rriv(1,cpl_index), tmp_rriv(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
     1468    call gath2cpl(cpl_rcoa(1,cpl_index), tmp_rcoa(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
    14691469
    14701470!
     
    14951495      &            tmp_snow(:,:,2) * tamp_srf(:,:,2) / deno
    14961496!!$PB
    1497 !!$        wri_rriv = tmp_rriv(:,:,1) * tamp_srf(:,:,1) / deno +    &
    1498 !!$      &            tmp_rriv(:,:,2) * tamp_srf(:,:,2) / deno
    1499 !!$        wri_rcoa = tmp_rcoa(:,:,1) * tamp_srf(:,:,1) / deno +    &
    1500 !!$      &            tmp_rcoa(:,:,2) * tamp_srf(:,:,2) / deno
     1497        wri_rriv = tmp_rriv(:,:,1) * tamp_srf(:,:,1) / deno +    &
     1498      &            tmp_rriv(:,:,2) * tamp_srf(:,:,2) / deno
     1499        wri_rcoa = tmp_rcoa(:,:,1) * tamp_srf(:,:,1) / deno +    &
     1500      &            tmp_rcoa(:,:,2) * tamp_srf(:,:,2) / deno
    15011501        wri_taux = tmp_taux(:,:,1) * tamp_srf(:,:,1) / deno +    &
    15021502      &            tmp_taux(:,:,2) * tamp_srf(:,:,2) / deno
     
    15831583      deallocate(tmp_tauy, stat=error); sum_error = sum_error + error
    15841584!!$PB
    1585 !!$      deallocate(tmp_rriv, stat=error); sum_error = sum_error + error
    1586 !!$      deallocate(tmp_rcoa, stat=error); sum_error = sum_error + error
     1585      deallocate(tmp_rriv, stat=error); sum_error = sum_error + error
     1586      deallocate(tmp_rcoa, stat=error); sum_error = sum_error + error
    15871587      if (sum_error /= 0) then
    15881588        abort_message='Pb deallocation variables couplees'
  • LMDZ.3.3/branches/rel-LF/libf/phylmd/oasis.F

    r394 r397  
    1515      SUBROUTINE inicma(kastp,kexch,kstep,imjm)
    1616c
    17 c     INCLUDE 'param.h'
     17c     INCLUDE "param.h"
    1818c
    1919      INTEGER kastp, kexch, kstep,imjm
     
    2121      INTEGER ifcpl, idt, info, imxtag, istep, jf
    2222c
    23       INCLUDE 'param_cou.h'
    24       INCLUDE 'inc_cpl.h'
     23#include "param_cou.h"
     24#include "inc_cpl.h"
    2525      CHARACTER*3 cljobnam      ! experiment name
    2626      CHARACTER*6 clmodnam      ! model name
     
    3737      PARAMETER (nuout = 6)
    3838c
    39       INCLUDE 'clim.h'
    40       INCLUDE 'mpiclim.h'
    41 c
    42       INCLUDE 'oasis.h' ! contains the name of communication technique. Here
     39#include "clim.h"
     40#include "mpiclim.h"
     41c
     42#include "oasis.h"      ! contains the name of communication technique. Here
    4343                        ! cchan=CLIM only is possible.
    4444c                       ! ctype=MPI2
     
    268268      INTEGER info, jf
    269269c
    270       INCLUDE 'clim.h'
    271 c
    272       INCLUDE 'oasis.h'
    273       INCLUDE 'param_cou.h'
    274 c
    275       INCLUDE 'inc_cpl.h'
     270#include "clim.h"
     271c
     272#include "oasis.h"
     273#include "param_cou.h"
     274c
     275#include "inc_cpl.h"
    276276c
    277277c
     
    346346      PARAMETER (nuout = 6)
    347347c
    348       INCLUDE 'clim.h'
    349       INCLUDE 'param_cou.h'
    350       INCLUDE 'inc_cpl.h'
     348#include "clim.h"
     349#include "param_cou.h"
     350#include "inc_cpl.h"
    351351c
    352352      CHARACTER*8 file_name(jpmaxfld)
     
    358358      LOGICAL trouve
    359359c
    360       INCLUDE 'oasis.h'
     360#include "oasis.h"
    361361c
    362362      icstep=kt
     
    554554      END
    555555
    556       SUBROUTINE halte
    557       print *, 'Attention dans oasis.F, halte est non defini'
    558       RETURN
    559       END
    560 
    561       SUBROUTINE locread
    562       print *, 'Attention dans oasis.F, locread est non defini'
    563       RETURN
    564       END
    565 
    566       SUBROUTINE locwrite
    567       print *, 'Attention dans oasis.F, locwrite est non defini'
    568       RETURN
    569       END
    570 
    571556      SUBROUTINE pipe_model_define
    572557      print*,'Attention dans oasis.F, pipe_model_define est non defini'
     
    589574      END
    590575
    591       SUBROUTINE clim_stepi
    592       print *, 'Attention dans oasis.F, clim_stepi est non defini'
    593       RETURN
    594       END
    595 
    596       SUBROUTINE clim_start
    597       print *, 'Attention dans oasis.F, clim_start est non defini'
    598       RETURN
    599       END
    600 
    601       SUBROUTINE clim_import
    602       print *, 'Attention dans oasis.F, clim_import est non defini'
    603       RETURN
    604       END
    605 
    606       SUBROUTINE clim_export
    607       print *, 'Attention dans oasis.F, clim_export est non defini'
    608       RETURN
    609       END
    610 
    611       SUBROUTINE clim_init
    612       print *, 'Attention dans oasis.F, clim_init est non defini'
    613       RETURN
    614       END
    615 
    616       SUBROUTINE clim_define
    617       print *, 'Attention dans oasis.F, clim_define est non defini'
    618       RETURN
    619       END
    620 
    621       SUBROUTINE clim_quit
    622       print *, 'Attention dans oasis.F, clim_quit est non defini'
    623       RETURN
    624       END
    625 
    626       SUBROUTINE svipc_write
    627       print *, 'Attention dans oasis.F, svipc_write est non defini'
    628       RETURN
    629       END
    630 
    631       SUBROUTINE svipc_close
    632       print *, 'Attention dans oasis.F, svipc_close est non defini'
    633       RETURN
    634       END
    635 
    636       SUBROUTINE svipc_read
    637       print *, 'Attention dans oasis.F, svipc_read est non defini'
    638       RETURN
    639       END
    640 
    641576      SUBROUTINE quitcpl
    642577      print *, 'Attention dans oasis.F, quitcpl est non defini'
  • LMDZ.3.3/branches/rel-LF/libf/phylmd/oasis.true

    r394 r397  
    1515      SUBROUTINE inicma(kastp,kexch,kstep,imjm)
    1616c
    17 c     INCLUDE 'param.h'
     17c     INCLUDE "param.h"
    1818c
    1919      INTEGER kastp, kexch, kstep,imjm
     
    2121      INTEGER ifcpl, idt, info, imxtag, istep, jf
    2222c
    23       INCLUDE 'param_cou.h'
    24       INCLUDE 'inc_cpl.h'
     23#include "param_cou.h"
     24#include "inc_cpl.h"
    2525      CHARACTER*3 cljobnam      ! experiment name
    2626      CHARACTER*6 clmodnam      ! model name
     
    3737      PARAMETER (nuout = 6)
    3838c
    39       INCLUDE 'clim.h'
    40       INCLUDE 'mpiclim.h'
    41 c
    42       INCLUDE 'oasis.h' ! contains the name of communication technique. Here
     39#include "clim.h"
     40#include "mpiclim.h"
     41c
     42#include "oasis.h"      ! contains the name of communication technique. Here
    4343                        ! cchan=CLIM only is possible.
    4444c                       ! ctype=MPI2
     
    268268      INTEGER info, jf
    269269c
    270       INCLUDE 'clim.h'
    271 c
    272       INCLUDE 'oasis.h'
    273       INCLUDE 'param_cou.h'
    274 c
    275       INCLUDE 'inc_cpl.h'
     270#include "clim.h"
     271c
     272#include "oasis.h"
     273#include "param_cou.h"
     274c
     275#include "inc_cpl.h"
    276276c
    277277c
     
    346346      PARAMETER (nuout = 6)
    347347c
    348       INCLUDE 'clim.h'
    349       INCLUDE 'param_cou.h'
    350       INCLUDE 'inc_cpl.h'
     348#include "clim.h"
     349#include "param_cou.h"
     350#include "inc_cpl.h"
    351351c
    352352      CHARACTER*8 file_name(jpmaxfld)
     
    358358      LOGICAL trouve
    359359c
    360       INCLUDE 'oasis.h'
     360#include "oasis.h"
    361361c
    362362      icstep=kt
  • LMDZ.3.3/branches/rel-LF/libf/phylmd/param_cou.h

    r179 r397  
    77                                        ! between ocean and atmosphere
    88        INTEGER jpflda2o1
    9         PARAMETER(jpflda2o1 = 11)         ! Number of fields exchanged from
     9        PARAMETER(jpflda2o1 = 12)         ! Number of fields exchanged from
    1010                                         ! atmosphere to ocean via flx.F
    1111        INTEGER jpflda2o2
Note: See TracChangeset for help on using the changeset viewer.