Ignore:
Timestamp:
01/02/13 18:50:00 (12 years ago)
Author:
smasson
Message:

bugfix for agrf, obc and xios

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/SBC/cpl_oasis3.F90

    r37 r65  
    2525   !!   cpl_prism_finalize : finalize the coupled mode communication 
    2626   !!---------------------------------------------------------------------- 
     27#if defined key_oasis_mct 
     28   USE mod_prism 
     29#else 
    2730   USE mod_prism_proto              ! OASIS3 prism module 
    2831   USE mod_prism_def_partition_proto! OASIS3 prism module for partitioning 
     
    3033   USE mod_prism_get_proto          ! OASIS3 prism module for receiving 
    3134   USE mod_comprism_proto           ! OASIS3 prism module to get coupling frequency 
     35#endif 
    3236   USE par_oce                      ! ocean parameters 
    3337   USE dom_oce                      ! ocean space and time domain 
     
    5155   INTEGER                    ::   nerror            ! return error code 
    5256 
    53    INTEGER, PARAMETER ::   nmaxfld=40    ! Maximum number of coupling fields 
     57   INTEGER, PUBLIC, PARAMETER ::   nmaxfld=40    ! Maximum number of coupling fields 
    5458    
    5559   TYPE, PUBLIC ::   FLD_CPL               !: Type for coupling field information 
     
    6266   END TYPE FLD_CPL 
    6367 
    64    TYPE(FLD_CPL), DIMENSION(nmaxfld), PUBLIC ::   srcv, ssnd   !: Coupling fields 
     68   TYPE(FLD_CPL), DIMENSION(:), ALLOCATABLE, PUBLIC ::   srcv, ssnd   !: Coupling fields 
    6569 
    6670   REAL(wp), DIMENSION(:,:), ALLOCATABLE ::   exfld   ! Temporary buffer for receiving 
     
    8791      ! WARNING: No write in numout in this routine 
    8892      !============================================ 
    89  
    9093      !------------------------------------------------------------------ 
    9194      ! 1st Initialize the PRISM system for the application 
     
    194197                  zclname=srcv(ji)%clname 
    195198               ENDIF 
     199#if defined key_agrif 
     200               IF( agrif_fixed() /= 0 ) THEN  
     201                  zclname=TRIM(Agrif_CFixed())//zclname(2:8) 
     202               END IF 
     203#endif 
    196204               IF( ln_ctl ) WRITE(numout,*) "Define",ji,jc,zclname," for",PRISM_In 
    197205               CALL prism_def_var_proto ( srcv(ji)%nid(jc), zclname, id_part, (/ 2, 0/),   & 
     
    208216      ! End of definition phase 
    209217      !------------------------------------------------------------------ 
    210        
    211       CALL prism_enddef_proto(nerror) 
    212       IF( nerror /= PRISM_Ok )   CALL prism_abort_proto ( ncomp_id, 'cpl_prism_define', 'Failure in prism_enddef') 
    213       ! 
     218#if defined key_agrif 
     219!!$      IF( agrif_fixed() == agrif_nb_fixed_grids() ) THEN  
     220      IF( .NOT. Agrif_Root() ) THEN 
     221#endif 
     222         WRITE(numout,*) 'before prism_enddef_proto' 
     223         CALL FLUSH(numout) 
     224 
     225         CALL prism_enddef_proto(nerror) 
     226         IF( nerror /= PRISM_Ok )   CALL prism_abort_proto ( ncomp_id, 'cpl_prism_define', 'Failure in prism_enddef') 
     227      ! 
     228         WRITE(numout,*) 'after prism_enddef_proto' 
     229         CALL FLUSH(numout) 
     230#if defined key_agrif 
     231      ENDIF 
     232#endif 
     233 
    214234   END SUBROUTINE cpl_prism_define 
    215235    
     
    322342      INTEGER,INTENT(in) ::   kid   ! variable index  
    323343      !!---------------------------------------------------------------------- 
    324       cpl_prism_freq = ig_def_freq( kid ) 
     344!EM OASIS-MCT info not yet available on official distrib 
     345!      cpl_prism_freq = ig_def_freq( kid ) 
     346      cpl_prism_freq = 300 
    325347      ! 
    326348   END FUNCTION cpl_prism_freq 
Note: See TracChangeset for help on using the changeset viewer.