Ignore:
Timestamp:
Dec 17, 2008, 2:30:13 PM (16 years ago)
Author:
Laurent Fairhead
Message:
  • Modifications lie au premier niveau du modele pour la diffusion turbulent

du vent.

  • Preparation pour un couplage des courrant oceaniques.

JG

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk/libf/phylmd/cpl_mod.F90

    r1010 r1067  
    1 !
    2 ! $Header$
    31!
    42MODULE cpl_mod
     
    6765  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: read_alb_sic ! albedo at sea ice
    6866  !$OMP THREADPRIVATE(read_alb_sic)
     67  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: read_u0, read_v0 ! ocean surface current
     68  !$OMP THREADPRIVATE(read_u0,read_v0)
    6969 
    7070  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: unity
     
    177177    sum_error = sum_error + error
    178178    ALLOCATE(read_alb_sic(iim, jj_nb), stat = error)
     179    sum_error = sum_error + error
     180
     181    ALLOCATE(read_u0(iim, jj_nb), stat = error)
     182    sum_error = sum_error + error
     183    ALLOCATE(read_v0(iim, jj_nb), stat = error)
    179184    sum_error = sum_error + error
    180185
     
    272277! are stored in this module.
    273278    USE surface_data
     279    USE phys_state_var_mod, ONLY : rlon, rlat
     280    USE Write_Field
    274281
    275282    INCLUDE "indicesol.h"
     
    296303    REAL, DIMENSION(iim,jj_nb,jpfldo2a)     :: tab_read_flds
    297304    REAL, DIMENSION(klon,nbsrf)             :: pctsrf_old
     305    REAL, DIMENSION(klon_mpi)               :: rlon_mpi, rlat_mpi
     306    REAL, DIMENSION(iim, jj_nb)             :: tmp_lon, tmp_lat
     307    REAL, DIMENSION(iim, jj_nb)             :: tmp_r0
    298308
    299309!*************************************************************************************
     
    311321       time_sec=(itime-1)*dtime
    312322#ifdef CPP_COUPLE
    313     time_sec=(itime-1)*dtime
    314323!$OMP MASTER
    315324    CALL fromcpl(time_sec, tab_read_flds)
     
    342351!$OMP END MASTER
    343352
     353       IF (cpl_current) THEN
     354
     355! Transform the longitudes and latitudes on 2D arrays
     356          CALL gather_omp(rlon,rlon_mpi)
     357          CALL gather_omp(rlat,rlat_mpi)
     358!$OMP MASTER
     359          CALL Grid1DTo2D_mpi(rlon_mpi,tmp_lon)
     360          CALL Grid1DTo2D_mpi(rlat_mpi,tmp_lat)
     361
     362! Transform the currents from cartesian to spheric coordinates
     363! tmp_r0 should be zero
     364          CALL geo2atm(iim, jj_nb, tab_read_flds(:,:,5), tab_read_flds(:,:,6), tab_read_flds(:,:,7), &
     365               tmp_lon, tmp_lat, &
     366               read_u0(:,:), read_v0(:,:), tmp_r0(:,:))
     367!$OMP END MASTER
     368          CALL WriteField('read_u0',read_u0)
     369          CALL WriteField('read_v0',read_v0)
     370          CALL WriteField('read_r0',tmp_r0)
     371       ELSE
     372          read_u0(:,:) = 0.
     373          read_v0(:,:) = 0.
     374       ENDIF
     375
    344376!*************************************************************************************
    345377!  Transform seaice fraction (read_sic : ocean-seaice mask) into global
     
    368400!
    369401
    370   SUBROUTINE cpl_receive_ocean_fields(knon, knindex, tsurf_new)
     402  SUBROUTINE cpl_receive_ocean_fields(knon, knindex, tsurf_new, u0_new, v0_new)
    371403!
    372404! This routine returns the field for the ocean that has been read from the coupler
     
    384416!*************************************************************************************
    385417    REAL, DIMENSION(klon), INTENT(OUT)      :: tsurf_new
     418    REAL, DIMENSION(klon), INTENT(OUT)      :: u0_new
     419    REAL, DIMENSION(klon), INTENT(OUT)      :: v0_new
    386420
    387421! Local variables
     
    396430    CALL cpl2gath(read_sst, tsurf_new, knon, knindex)
    397431    CALL cpl2gath(read_sic, sic_new, knon, knindex)
     432    CALL cpl2gath(read_u0, u0_new, knon, knindex)
     433    CALL cpl2gath(read_v0, v0_new, knon, knindex)
    398434
    399435!*************************************************************************************
     
    11201156    ENDIF
    11211157
    1122 ! Transform the wind from local atmospheric 2D coordinates to geocentric
    1123 ! 3D coordinates
     1158! Transform the wind from spherical atmospheric 2D coordinates to geocentric
     1159! cartesian 3D coordinates
    11241160!$OMP MASTER
    11251161    CALL atm2geo (iim, jj_nb, tmp_taux, tmp_tauy, tmp_lon, tmp_lat, &
     
    11651201    time_sec=(itime-1)*dtime
    11661202#ifdef CPP_COUPLE
    1167     time_sec=(itime-1)*dtime
    11681203!$OMP MASTER
    11691204    CALL intocpl(time_sec, lafin, tab_flds(:,:,:))
Note: See TracChangeset for help on using the changeset viewer.