New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 1242 – NEMO

Changeset 1242


Ignore:
Timestamp:
2009-01-06T11:21:38+01:00 (16 years ago)
Author:
rblod
Message:

Fix runtime issues with AGRIF on NEC and add the ability to run without sea-ice on the fine grid hierarchy

Location:
trunk
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • trunk/CONFIG/ORCA2_LIM/EXP00/1_namelist

    r1241 r1242  
    107107   ln_blk_core = .false.   !  CORE bulk formulation  (T => fill namsbc_core)  
    108108   ln_cpl      = .false.   !  Coupled formulation    (T => fill namsbc_cpl ) 
    109    nn_ice      = 2         !  =0 no ice boundary condition   , 
     109   nn_ice      = 0         !  =0 no ice boundary condition   , 
    110110                           !  =1 use observed ice-cover      , 
    111111                           !  =2 ice-model used                             ("key_lim3" or "key_lim2) 
  • trunk/NEMO/OPA_SRC/SBC/sbcblk_clio.F90

    r1207 r1242  
    215215 
    216216      IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN 
    217           CALL blk_oce_clio( sst_m )                  ! compute the surface ocean fluxes using CLIO bulk formulea 
    218       ENDIF                                           !  
     217          CALL blk_oce_clio( sf, sst_m )                  ! compute the surface ocean fluxes using CLIO bulk formulea 
     218      ENDIF                                               !  
    219219      ! 
    220220   END SUBROUTINE sbc_blk_clio 
    221221 
    222222 
    223    SUBROUTINE blk_oce_clio( pst ) 
     223   SUBROUTINE blk_oce_clio( sf, pst ) 
    224224      !!--------------------------------------------------------------------------- 
    225225      !!                     ***  ROUTINE blk_oce_clio  *** 
     
    242242      !!               - qns, qsr    non-slor and solar heat flux 
    243243      !!               - emp, emps   evaporation minus precipitation 
     244      !!  ** Nota    :   sf has to be a dummy argument for AGRIF on NEC 
    244245      !!---------------------------------------------------------------------- 
    245       REAL(wp), INTENT(in), DIMENSION(jpi,jpj) ::   pst   ! surface temperature                      [Celcius] 
     246      TYPE(fld), INTENT(in), DIMENSION(:)       ::   sf    ! input data 
     247      REAL(wp) , INTENT(in), DIMENSION(jpi,jpj) ::   pst   ! surface temperature                      [Celcius] 
    246248      !! 
    247249      INTEGER  ::   ji, jj   ! dummy loop indices 
     
    284286         END DO 
    285287      END DO 
    286  
    287288 
    288289      !------------------------------------------------! 
  • trunk/NEMO/OPA_SRC/SBC/sbcblk_core.F90

    r1234 r1242  
    166166 
    167167 
    168       CALL fld_read( kt, nn_fsbc, sf )                ! input fields provided at the current time-step 
     168      CALL fld_read( kt, nn_fsbc, sf )                   ! input fields provided at the current time-step 
    169169 
    170170#if defined key_lim3 
     
    173173 
    174174      IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN 
    175           CALL blk_oce_core( sst_m, ssu_m, ssv_m )    ! compute the surface ocean fluxes using CLIO bulk formulea 
     175          CALL blk_oce_core( sf, sst_m, ssu_m, ssv_m )   ! compute the surface ocean fluxes using CLIO bulk formulea 
    176176      ENDIF 
    177       !                                               ! using CORE bulk formulea 
     177      !                                                  ! using CORE bulk formulea 
    178178   END SUBROUTINE sbc_blk_core 
    179179    
    180180    
    181    SUBROUTINE blk_oce_core( pst, pu, pv ) 
     181   SUBROUTINE blk_oce_core( sf, pst, pu, pv ) 
    182182      !!--------------------------------------------------------------------- 
    183183      !!                     ***  ROUTINE blk_core  *** 
     
    196196      !!              - tprecip : Total precipitation                   (Kg/m2/s) 
    197197      !!              - sprecip : Solid precipitation                   (Kg/m2/s) 
     198      !! 
     199      !!  ** Nota  :   sf has to be a dummy argument for AGRIF on NEC 
    198200      !!--------------------------------------------------------------------- 
    199       REAL(wp), INTENT(in), DIMENSION(jpi,jpj) ::   pst   ! surface temperature                      [Celcius] 
    200       REAL(wp), INTENT(in), DIMENSION(jpi,jpj) ::   pu    ! surface current at U-point (i-component) [m/s] 
    201       REAL(wp), INTENT(in), DIMENSION(jpi,jpj) ::   pv    ! surface current at V-point (j-component) [m/s] 
     201      TYPE(fld), INTENT(in), DIMENSION(:)       ::   sf    ! input data 
     202      REAL(wp),  INTENT(in), DIMENSION(jpi,jpj) ::   pst   ! surface temperature                      [Celcius] 
     203      REAL(wp),  INTENT(in), DIMENSION(jpi,jpj) ::   pu    ! surface current at U-point (i-component) [m/s] 
     204      REAL(wp),  INTENT(in), DIMENSION(jpi,jpj) ::   pv    ! surface current at V-point (j-component) [m/s] 
    202205 
    203206      INTEGER  ::   ji, jj     ! dummy loop indices 
  • trunk/NEMO/OPA_SRC/SBC/sbcmod.F90

    r1226 r1242  
    8585!!gm here no overwrite, test all option via namelist change: require more incore memory 
    8686!!gm  IF( lk_sbc_cpl       ) THEN   ;   ln_cpl      = .TRUE.   ;   ELSE   ;   ln_cpl      = .FALSE.   ;   ENDIF 
    87       IF( lk_lim2 )            nn_ice      = 2 
    88       IF( lk_lim3 )            nn_ice      = 3 
     87#if defined key_agrif 
     88      IF ( Agrif_Root() ) THEN 
     89#endif 
     90        IF( lk_lim2 )            nn_ice      = 2 
     91        IF( lk_lim3 )            nn_ice      = 3 
     92#if defined key_agrif 
     93      ENDIF 
     94#endif 
    8995      IF( cp_cfg == 'gyre' ) THEN 
    9096          ln_ana      = .TRUE.    
  • trunk/NEMO/OPA_SRC/SBC/sbcrnf.F90

    r1200 r1242  
    6666      ! 
    6767      INTEGER  ::   ji, jj   ! dummy loop indices 
     68      INTEGER  ::   ierror   ! temporary integer 
    6869      !!---------------------------------------------------------------------- 
    6970      !                                    
    70       IF( kt == nit000 )   CALL sbc_rnf_init 
     71      IF( kt == nit000 ) THEN   
     72         IF( .NOT. ln_rnf_emp ) THEN 
     73            ALLOCATE( sf_rnf(1), STAT=ierror ) 
     74            IF( ierror > 0 ) THEN 
     75               CALL ctl_stop( 'sbc_rnf: unable to allocate sf_rnf structure' )   ;   RETURN 
     76            ENDIF 
     77            ALLOCATE( sf_rnf(1)%fnow(jpi,jpj) ) 
     78            ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,2) ) 
     79         ENDIF 
     80         CALL sbc_rnf_init(sf_rnf) 
     81      ENDIF 
    7182 
    7283      !                                                   !-------------------! 
     
    97108 
    98109 
    99    SUBROUTINE sbc_rnf_init 
     110   SUBROUTINE sbc_rnf_init( sf_rnf ) 
    100111      !!---------------------------------------------------------------------- 
    101112      !!                  ***  ROUTINE sbc_rnf_init  *** 
     
    107118      !! ** Action  : - read parameters 
    108119      !!---------------------------------------------------------------------- 
    109       INTEGER  ::   ierror   ! temporary integer 
     120      TYPE(FLD), INTENT(inout), DIMENSION(:) :: sf_rnf   ! input data 
    110121      !! 
    111122      NAMELIST/namsbc_rnf/ cn_dir, ln_rnf_emp, sn_rnf, sn_cnf, ln_rnf_mouth,   & 
     
    148159      ELSE                                      ! runoffs read in a file : set sf_rnf structure  
    149160         ! 
    150          ALLOCATE( sf_rnf(1), STAT=ierror ) 
    151          IF( ierror > 0 ) THEN 
    152             CALL ctl_stop( 'sbc_rnf: unable to allocate sf_rnf structure' )   ;   RETURN 
    153          ENDIF 
    154          ALLOCATE( sf_rnf(1)%fnow(jpi,jpj) ) 
    155          ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,2) ) 
    156  
     161         ! sf_rnf already allocated in main routine 
    157162         ! fill sf_rnf with sn_rnf and control print 
    158163         CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf' ) 
Note: See TracChangeset for help on using the changeset viewer.