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 – 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
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5218_CNRS17_coupling/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r5370 r5376  
    110110 
    111111      ! make calls for heat fluxes before it is modified 
    112       IF( iom_use('qsr_oce') )   CALL iom_put( "qsr_oce" , qsr_oce(:,:) * pfrld(:,:) )                                   !     solar flux at ocean surface 
    113       IF( iom_use('qns_oce') )   CALL iom_put( "qns_oce" , qns_oce(:,:) * pfrld(:,:) + qemp_oce(:,:) )                   ! non-solar flux at ocean surface 
     112!!$      IF( iom_use('qsr_oce') )   CALL iom_put( "qsr_oce" , qsr_oce(:,:) * pfrld(:,:) )                                   !     solar flux at ocean surface 
     113!!$      IF( iom_use('qns_oce') )   CALL iom_put( "qns_oce" , qns_oce(:,:) * pfrld(:,:) + qemp_oce(:,:) )                   ! non-solar flux at ocean surface 
    114114      IF( iom_use('qsr_ice') )   CALL iom_put( "qsr_ice" , SUM( qsr_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) )                 !     solar flux at ice surface 
    115115      IF( iom_use('qns_ice') )   CALL iom_put( "qns_ice" , SUM( qns_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) + qemp_ice(:,:) ) ! non-solar flux at ice surface 
    116116      IF( iom_use('qtr_ice') )   CALL iom_put( "qtr_ice" , SUM( ftr_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) )                 !     solar flux transmitted thru ice 
    117       IF( iom_use('qt_oce' ) )   CALL iom_put( "qt_oce"  , ( qsr_oce(:,:) + qns_oce(:,:) ) * pfrld(:,:) + qemp_oce(:,:) )   
     117!!$      IF( iom_use('qt_oce' ) )   CALL iom_put( "qt_oce"  , ( qsr_oce(:,:) + qns_oce(:,:) ) * pfrld(:,:) + qemp_oce(:,:) )   
    118118      IF( iom_use('qt_ice' ) )   CALL iom_put( "qt_ice"  , SUM( ( qns_ice(:,:,:) + qsr_ice(:,:,:) )   & 
    119119         &                                                      * a_i_b(:,:,:), dim=3 ) + qemp_ice(:,:) ) 
  • branches/2015/dev_r5218_CNRS17_coupling/NEMOGCM/NEMO/OPA_SRC/LBC/lib_mpp.F90

    r4990 r5376  
    164164 
    165165 
    166    FUNCTION mynode( ldtxt, kumnam_ref , kumnam_cfg , kumond , kstop, localComm ) 
     166   FUNCTION mynode( ldtxt, ldname, kumnam_ref , kumnam_cfg , kumond , kstop, localComm ) 
    167167      !!---------------------------------------------------------------------- 
    168168      !!                  ***  routine mynode  *** 
     
    171171      !!---------------------------------------------------------------------- 
    172172      CHARACTER(len=*),DIMENSION(:), INTENT(  out) ::   ldtxt 
     173      CHARACTER(len=*)             , INTENT(in   ) ::   ldname 
    173174      INTEGER                      , INTENT(in   ) ::   kumnam_ref     ! logical unit for reference namelist 
    174175      INTEGER                      , INTENT(in   ) ::   kumnam_cfg     ! logical unit for configuration namelist 
     
    297298 
    298299      IF( mynode == 0 ) THEN 
    299         CALL ctl_opn( kumond, 'output.namelist.dyn', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. , 1 ) 
    300         WRITE(kumond, nammpp)       
     300         CALL ctl_opn( kumond, TRIM(ldname), 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. , 1 ) 
     301         WRITE(kumond, nammpp)       
    301302      ENDIF 
    302303      ! 
     
    31923193   END FUNCTION lib_mpp_alloc 
    31933194 
    3194    FUNCTION mynode( ldtxt, kumnam_ref, knumnam_cfg,  kumond , kstop, localComm ) RESULT (function_value) 
     3195   FUNCTION mynode( ldtxt, ldname, kumnam_ref, knumnam_cfg,  kumond , kstop, localComm ) RESULT (function_value) 
    31953196      INTEGER, OPTIONAL            , INTENT(in   ) ::   localComm 
    31963197      CHARACTER(len=*),DIMENSION(:) ::   ldtxt 
     3198      CHARACTER(len=*) ::   ldname 
    31973199      INTEGER ::   kumnam_ref, knumnam_cfg , kumond , kstop 
    31983200      IF( PRESENT( localComm ) .OR. .NOT.PRESENT( localComm ) )   function_value = 0 
    31993201      IF( .FALSE. )   ldtxt(:) = 'never done' 
    3200       CALL ctl_opn( kumond, 'output.namelist.dyn', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. , 1 ) 
     3202      CALL ctl_opn( kumond, TRIM(ldname), 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. , 1 ) 
    32013203   END FUNCTION mynode 
    32023204 
  • branches/2015/dev_r5218_CNRS17_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_core.F90

    r5357 r5376  
    405405      CALL iom_put( "qhc_oce",   qns-zqlw+zqsb+zqla )   ! output downward heat content of E-P over the ocean 
    406406      CALL iom_put( "qns_oce",   qns  )                 ! output downward non solar heat over the ocean 
     407      CALL iom_put( "qsr_oce",   qsr  )                 ! output downward solar heat over the ocean 
     408      CALL iom_put( "qt_oce" ,   qns+qsr )              ! output total downward heat over the ocean 
    407409      ! 
    408410      IF(ln_ctl) THEN 
     
    620622 
    621623      ! --- heat flux associated with emp --- ! 
    622       qemp_oce(:,:) = - pfrld(:,:) * zevap(:,:) * sst_m(:,:) * rcp                               & ! evap 
    623          &          + ( tprecip(:,:) - sprecip(:,:) ) * ( sf(jp_tair)%fnow(:,:,1) - rt0 ) * rcp  & ! liquid precip 
    624          &          +   sprecip(:,:) * ( 1._wp - zsnw ) *                                        & ! solid precip 
     624      qemp_oce(:,:) = - pfrld(:,:) * zevap(:,:) * sst_m(:,:) * rcp                               & ! evap at sst 
     625         &          + ( tprecip(:,:) - sprecip(:,:) ) * ( sf(jp_tair)%fnow(:,:,1) - rt0 ) * rcp  & ! liquid precip at Tair 
     626         &          +   sprecip(:,:) * ( 1._wp - zsnw ) *                                        & ! solid precip at min(Tair,Tsnow) 
    625627         &              ( ( MIN( sf(jp_tair)%fnow(:,:,1), rt0_snow ) - rt0 ) * cpic * tmask(:,:,1) - lfus ) 
    626628      qemp_ice(:,:) =   sprecip(:,:) * zsnw *                                                    & ! solid precip (only) 
  • branches/2015/dev_r5218_CNRS17_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r5357 r5376  
    3333   USE cpl_oasis3      ! OASIS3 coupling 
    3434   USE geo2ocean       !  
    35    USE oce   , ONLY : tsn, un, vn, sshn, ub, vb, tsb, sshb 
     35   USE oce   , ONLY : tsn, un, vn, sshn, ub, vb, sshb 
    3636   USE albedo          ! 
    3737   USE in_out_manager  ! I/O manager 
     
    4242   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    4343   USE eosbn2 
     44   USE traqsr   , ONLY : fraqsr_1lev 
    4445#if defined key_cpl_carbon_cycle 
    4546   USE p4zflx, ONLY : oce_co2 
     
    486487      IF( nn_components == jp_iam_opa ) THEN    ! OPA coupled to SAS via OASIS: force received field by OPA (sent by SAS) 
    487488         srcv(:)%laction = .FALSE.   ! force default definition in case of opa <-> sas coupling 
     489         srcv(:)%clgrid  = 'T'       ! force default definition in case of opa <-> sas coupling 
     490         srcv(:)%nsgn    = 1.        ! force default definition in case of opa <-> sas coupling 
    488491         srcv( (/jpr_qsroce, jpr_qnsoce, jpr_oemp, jpr_sflx, jpr_fice, jpr_otx1, jpr_oty1, jpr_taum/) )%laction = .TRUE. 
    489492         srcv(jpr_otx1)%clgrid = 'U'        ! oce components given at U-point 
     
    525528      IF( nn_components == jp_iam_sas ) THEN 
    526529         IF( .NOT. ln_cpl ) srcv(:)%laction = .FALSE.   ! force default definition in case of opa <-> sas coupling 
    527          srcv( (/jpr_toce, jpr_soce, jpr_ssh, jpr_e3t1st, jpr_fraqsr, jpr_ocx1, jpr_ocy1/) )%laction = .TRUE. 
     530         IF( .NOT. ln_cpl ) srcv(:)%clgrid  = 'T'       ! force default definition in case of opa <-> sas coupling 
     531         IF( .NOT. ln_cpl ) srcv(:)%nsgn    = 1.        ! force default definition in case of opa <-> sas coupling 
     532         srcv( (/jpr_toce, jpr_soce, jpr_ssh, jpr_fraqsr, jpr_ocx1, jpr_ocy1/) )%laction = .TRUE. 
     533         srcv( jpr_e3t1st )%laction = lk_vvl 
     534         srcv(jpr_ocx1)%clgrid = 'U'        ! oce components given at U-point 
     535         srcv(jpr_ocy1)%clgrid = 'V'        !           and           V-point 
    528536         ! Vectors: change of sign at north fold ONLY if on the local grid 
    529537         srcv(jpr_ocx1:jpr_ocy1)%nsgn = -1. 
     
    690698      IF( nn_components == jp_iam_opa ) THEN 
    691699         ssnd(:)%laction = .FALSE.   ! force default definition in case of opa <-> sas coupling 
    692          ssnd( (/jps_toce, jps_soce, jps_ssh, jps_e3t1st, jps_fraqsr, jps_ocx1, jps_ocy1/) )%laction = .TRUE. 
     700         ssnd( (/jps_toce, jps_soce, jps_ssh, jps_fraqsr, jps_ocx1, jps_ocy1/) )%laction = .TRUE. 
     701         ssnd( jps_e3t1st )%laction = lk_vvl 
    693702         ! vector definition: not used but cleaner... 
    694703         ssnd(jps_ocx1)%clgrid  = 'U'        ! oce components given at U-point 
     
    984993#endif 
    985994 
    986       !  Fields received by ice model when OASIS coupling 
     995      !  Fields received by SAS when OASIS coupling 
    987996      !  (arrays no more filled at sbcssm stage) 
    988997      !                                                      ! ================== ! 
     
    9911000      IF( srcv(jpr_soce)%laction ) THEN                      ! received by sas in case of opa <-> sas coupling 
    9921001         sss_m(:,:) = frcv(jpr_soce)%z3(:,:,1) 
    993          tsn(:,:,1,jp_sal) = sss_m(:,:) 
     1002         CALL iom_put( 'sss_m', sss_m ) 
    9941003      ENDIF 
    9951004      !                                                
     
    9991008      IF( srcv(jpr_toce)%laction ) THEN                      ! received by sas in case of opa <-> sas coupling 
    10001009         sst_m(:,:) = frcv(jpr_toce)%z3(:,:,1) 
    1001          tsn(:,:,1,jp_tem) = sst_m(:,:)                      ! keep the received (potential or conservative) temperature in tsn  
    10021010         IF( srcv(jpr_soce)%laction .AND. ln_useCT ) THEN    ! make sure that sst_m is the potential temperature 
    10031011            sst_m(:,:) = eos_pt_from_ct( sst_m(:,:), sss_m(:,:) ) 
     
    10091017      IF( srcv(jpr_ssh )%laction ) THEN                      ! received by sas in case of opa <-> sas coupling 
    10101018         ssh_m(:,:) = frcv(jpr_ssh )%z3(:,:,1) 
    1011          sshn( :,:) = ssh_m(:,:) 
     1019         CALL iom_put( 'ssh_m', ssh_m ) 
    10121020      ENDIF 
    10131021      !                                                      ! ================== ! 
     
    10161024      IF( srcv(jpr_ocx1)%laction ) THEN                      ! received by sas in case of opa <-> sas coupling 
    10171025         ssu_m(:,:) = frcv(jpr_ocx1)%z3(:,:,1) 
    1018          ub (:,:,1) = ssu_m(:,:) 
     1026         ub (:,:,1) = ssu_m(:,:)                             ! will be used in sbcice_lim in the call of lim_sbc_tau 
     1027         CALL iom_put( 'ssu_m', ssu_m ) 
    10191028      ENDIF 
    10201029      IF( srcv(jpr_ocy1)%laction ) THEN 
    10211030         ssv_m(:,:) = frcv(jpr_ocy1)%z3(:,:,1) 
    1022          vb (:,:,1) = ssv_m(:,:) 
     1031         vb (:,:,1) = ssv_m(:,:)                             ! will be used in sbcice_lim in the call of lim_sbc_tau 
     1032         CALL iom_put( 'ssv_m', ssv_m ) 
    10231033      ENDIF 
    10241034      !                                                      ! ======================== ! 
     
    10261036      !                                                      ! ======================== ! 
    10271037      IF( srcv(jpr_e3t1st )%laction ) THEN                   ! received by sas in case of opa <-> sas coupling 
    1028          fse3t_m(:,:) = frcv(jpr_e3t1st )%z3(:,:,1) 
     1038         e3t_m(:,:) = frcv(jpr_e3t1st )%z3(:,:,1) 
     1039         CALL iom_put( 'e3t_m', e3t_m(:,:) ) 
    10291040      ENDIF 
    10301041      !                                                      ! ================================ ! 
     
    10331044      IF( srcv(jpr_fraqsr)%laction ) THEN                    ! received by sas in case of opa <-> sas coupling 
    10341045         frq_m(:,:) = frcv(jpr_fraqsr)%z3(:,:,1) 
     1046         CALL iom_put( 'frq_m', frq_m ) 
    10351047      ENDIF 
    10361048       
     
    19371949      ! 
    19381950      ! 
    1939       !  Fields sent to SAS by OPA when doing OPA<->SAS coupling 
     1951      !  Fields sent by OPA to SAS when doing OPA<->SAS coupling 
    19401952      !                                                        ! SSH 
    19411953      IF( ssnd(jps_ssh )%laction )  THEN 
     
    19581970      !                                                        ! Qsr fraction 
    19591971      IF( ssnd(jps_fraqsr)%laction )  THEN 
    1960          CALL cpl_snd( jps_fraqsr, isec, RESHAPE ( frq_m            , (/jpi,jpj,1/) ), info ) 
    1961       ENDIF 
    1962       ! 
    1963       !  Fields sent to ocean by ice model when OASIS coupling 
     1972         CALL cpl_snd( jps_fraqsr, isec, RESHAPE ( fraqsr_1lev(:,:) , (/jpi,jpj,1/) ), info ) 
     1973      ENDIF 
     1974      ! 
     1975      !  Fields sent by SAS to OPA when OASIS coupling 
    19641976      !                                                        ! Solar heat flux 
    19651977      IF( ssnd(jps_qsroce)%laction )  CALL cpl_snd( jps_qsroce, isec, RESHAPE ( qsr , (/jpi,jpj,1/) ), info ) 
  • branches/2015/dev_r5218_CNRS17_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r5357 r5376  
    308308         &   CALL ctl_warn( 'diurnal cycle for qsr: the sampling of the diurnal cycle is too small...' ) 
    309309 
    310  
    311       IF( nn_components /= jp_iam_sas )   & 
    312          &                     CALL sbc_ssm_init               ! Sea-surface mean fields initialisation 
     310                               CALL sbc_ssm_init               ! Sea-surface mean fields initialisation 
    313311      ! 
    314312      IF( ln_ssr           )   CALL sbc_ssr_init               ! Sea-Surface Restoring initialisation 
  • branches/2015/dev_r5218_CNRS17_coupling/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r5220 r5376  
    281281         ENDIF 
    282282      ENDIF 
    283       narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )   ! Nodes selection 
     283      ! Nodes selection (control print return in cltxt) 
     284      narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop, ilocal_comm ) 
    284285#else 
    285286      IF( lk_oasis ) THEN 
     
    287288            CALL cpl_init( "oceanx", ilocal_comm )                      ! nemo local communicator given by oasis 
    288289         ENDIF 
    289          narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )   ! Nodes selection (control print return in cltxt) 
     290         ! Nodes selection (control print return in cltxt) 
     291         narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop, ilocal_comm ) 
    290292      ELSE 
    291293         ilocal_comm = 0 
    292          narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop )                ! Nodes selection (control print return in cltxt) 
     294         ! Nodes selection (control print return in cltxt) 
     295         narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop ) 
    293296      ENDIF 
    294297#endif 
  • 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.