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 5376 for branches/2015/dev_r5218_CNRS17_coupling/NEMOGCM/NEMO/SAS_SRC – NEMO

Ignore:
Timestamp:
2015-06-08T15:13:26+02:00 (9 years ago)
Author:
smasson
Message:

dev_r5218_CNRS17_coupling: bugfix for SAS-OPA coupling

Location:
branches/2015/dev_r5218_CNRS17_coupling/NEMOGCM/NEMO/SAS_SRC
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5218_CNRS17_coupling/NEMOGCM/NEMO/SAS_SRC/nemogcm.F90

    r5352 r5376  
    175175      INTEGER ::   ios 
    176176      CHARACTER(len=80), DIMENSION(16) ::   cltxt 
     177      CHARACTER(len=80) ::   clname 
    177178      ! 
    178179      NAMELIST/namctl/ ln_ctl  , nn_print, nn_ictls, nn_ictle,   & 
     
    190191         CALL ctl_opn( numnam_cfg, 'namelist_sas_cfg', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
    191192         cxios_context = 'sas' 
     193         clname = 'output.namelist_sas.dyn' 
    192194      ELSE 
    193195         CALL ctl_opn( numnam_ref, 'namelist_ref', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
    194196         CALL ctl_opn( numnam_cfg, 'namelist_cfg', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
    195197         cxios_context = 'nemo' 
     198         clname = 'output.namelist.dyn' 
    196199   ENDIF 
    197200      ! 
     
    244247         ENDIF 
    245248      ENDIF 
    246       narea = mynode ( cltxt, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )  ! Nodes selection 
     249      narea = mynode ( cltxt, clname, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )  ! Nodes selection 
    247250#else 
    248251      IF( lk_oasis ) THEN 
     
    250253            CALL cpl_init( "sas", ilocal_comm )                          ! nemo local communicator given by oasis 
    251254         ENDIF 
    252          narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )   ! Nodes selection (control print return in cltxt) 
     255         narea = mynode( cltxt, clname, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )   ! Nodes selection (control print return in cltxt) 
    253256      ELSE 
    254257         ilocal_comm = 0 
    255          narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop )                ! Nodes selection (control print return in cltxt) 
     258         narea = mynode( cltxt, clname, numnam_ref, numnam_cfg, numond , nstop )                ! Nodes selection (control print return in cltxt) 
    256259      ENDIF 
    257260#endif 
  • branches/2015/dev_r5218_CNRS17_coupling/NEMOGCM/NEMO/SAS_SRC/sbcssm.F90

    r5352 r5376  
    3939   LOGICAL              ::   ln_3d_uve     !: specify whether input velocity data is 3D 
    4040   LOGICAL              ::   ln_read_frq   !: specify whether we must read frq or not 
     41   LOGICAL              ::   l_initdone = .false. 
    4142   INTEGER     ::   nfld_3d 
    4243   INTEGER     ::   nfld_2d 
     
    99100      IF( ln_read_frq )   frq_m(:,:) = sf_ssm_2d(jf_frq)%fnow(:,:,1) * tmask(:,:,1)    ! sea surface height 
    100101      ! 
    101       tsn(:,:,1,jp_tem) = sst_m(:,:) 
    102       tsn(:,:,1,jp_sal) = sss_m(:,:) 
    103102      IF ( nn_ice == 1 ) THEN 
     103         tsn(:,:,1,jp_tem) = sst_m(:,:) 
     104         tsn(:,:,1,jp_sal) = sss_m(:,:) 
    104105         tsb(:,:,1,jp_tem) = sst_m(:,:) 
    105106         tsb(:,:,1,jp_sal) = sss_m(:,:) 
     
    118119      ENDIF 
    119120      ! 
     121      IF( l_initdone ) THEN          !   Mean value at each nn_fsbc time-step   ! 
     122         CALL iom_put( 'ssu_m', ssu_m ) 
     123         CALL iom_put( 'ssv_m', ssv_m ) 
     124         CALL iom_put( 'sst_m', sst_m ) 
     125         CALL iom_put( 'sss_m', sss_m ) 
     126         CALL iom_put( 'ssh_m', ssh_m ) 
     127         IF( lk_vvl      )   CALL iom_put( 'e3t_m', e3t_m ) 
     128         IF( ln_read_frq )   CALL iom_put( 'frq_m', frq_m ) 
     129      ENDIF 
     130      ! 
    120131      IF( nn_timing == 1 )  CALL timing_stop( 'sbc_ssm') 
    121132      ! 
     
    146157      NAMELIST/namsbc_sas/cn_dir, ln_3d_uve, ln_read_frq, sn_tem, sn_sal, sn_usp, sn_vsp, sn_ssh, sn_e3t, sn_frq 
    147158      !!---------------------------------------------------------------------- 
     159       
     160      IF( ln_rstart .AND. nn_components == jp_iam_sas ) RETURN 
    148161       
    149162      REWIND( numnam_ref )              ! Namelist namsbc_sas in reference namelist : Input fields 
     
    167180         WRITE(numout,*) 
    168181      ENDIF 
    169        
    170       ! 
    171       !! switch off stuff that isn't sensible with a standalone module 
    172       !! note that we need sbc_ssm called first in sbc 
    173       ! 
    174       IF( ln_apr_dyn ) THEN 
    175          IF( lwp ) WRITE(numout,*) 'No atmospheric gradient needed with StandAlone Surface scheme' 
    176          ln_apr_dyn = .FALSE. 
    177       ENDIF 
    178       IF( ln_dm2dc ) THEN 
    179          IF( lwp ) WRITE(numout,*) 'No diurnal cycle needed with StandAlone Surface scheme' 
    180          ln_dm2dc = .FALSE. 
    181       ENDIF 
    182       IF( ln_rnf ) THEN 
    183          IF( lwp ) WRITE(numout,*) 'No runoff needed with StandAlone Surface scheme' 
    184          ln_rnf = .FALSE. 
    185       ENDIF 
    186       IF( ln_ssr ) THEN 
    187          IF( lwp ) WRITE(numout,*) 'No surface relaxation needed with StandAlone Surface scheme' 
    188          ln_ssr = .FALSE. 
    189       ENDIF 
    190       IF( nn_fwb > 0 ) THEN 
    191          IF( lwp ) WRITE(numout,*) 'No freshwater budget adjustment needed with StandAlone Surface scheme' 
    192          nn_fwb = 0 
    193       ENDIF 
    194       IF( nn_closea > 0 ) THEN 
    195          IF( lwp ) WRITE(numout,*) 'No closed seas adjustment needed with StandAlone Surface scheme' 
    196          nn_closea = 0 
    197       ENDIF 
    198  
     182 
     183      IF( nn_components /= jp_iam_sas ) THEN  
     184         ! 
     185         !! switch off stuff that isn't sensible with a standalone module 
     186         !! note that we need sbc_ssm called first in sbc 
     187         ! 
     188         IF( ln_apr_dyn ) THEN 
     189            IF( lwp ) WRITE(numout,*) 'No atmospheric gradient needed with StandAlone Surface scheme' 
     190            ln_apr_dyn = .FALSE. 
     191         ENDIF 
     192         IF( ln_dm2dc ) THEN 
     193            IF( lwp ) WRITE(numout,*) 'No diurnal cycle needed with StandAlone Surface scheme' 
     194            ln_dm2dc = .FALSE. 
     195         ENDIF 
     196         IF( ln_rnf ) THEN 
     197            IF( lwp ) WRITE(numout,*) 'No runoff needed with StandAlone Surface scheme' 
     198            ln_rnf = .FALSE. 
     199         ENDIF 
     200         IF( ln_ssr ) THEN 
     201            IF( lwp ) WRITE(numout,*) 'No surface relaxation needed with StandAlone Surface scheme' 
     202            ln_ssr = .FALSE. 
     203         ENDIF 
     204         IF( nn_fwb > 0 ) THEN 
     205            IF( lwp ) WRITE(numout,*) 'No freshwater budget adjustment needed with StandAlone Surface scheme' 
     206            nn_fwb = 0 
     207         ENDIF 
     208         IF( nn_closea > 0 ) THEN 
     209            IF( lwp ) WRITE(numout,*) 'No closed seas adjustment needed with StandAlone Surface scheme' 
     210            nn_closea = 0 
     211         ENDIF 
     212          
     213      ENDIF 
    199214      !  
    200215      !! following code is a bit messy, but distinguishes between when u,v are 3d arrays and 
     
    280295      CALL sbc_ssm( nit000 )   ! need to define ss?_m arrays used in limistate 
    281296      IF( .NOT. ln_read_frq )   frq_m(:,:) = 1. 
     297      l_initdone = .TRUE. 
    282298      ! 
    283299   END SUBROUTINE sbc_ssm_init 
Note: See TracChangeset for help on using the changeset viewer.