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 2292 – NEMO

Changeset 2292


Ignore:
Timestamp:
2010-10-19T12:15:40+02:00 (14 years ago)
Author:
smasson
Message:

update DEV_r1879_FCM for additional tests...

Location:
branches/DEV_r1879_FCM/NEMOGCM
Files:
5 added
2 deleted
14 edited

Legend:

Unmodified
Added
Removed
  • branches/DEV_r1879_FCM/NEMOGCM/ARCH/arch-SX8_MERCURE.fcm

    r2143 r2292  
    1515 
    1616 
    17 %NCDF_INC        -I/usr/local/SX8/soft/netcdf/include 
    18 %NCDF_LIB        -L/usr/local/SX8/soft/netcdf/lib -lnetcdf 
     17%NCDF_INC        -I/ccc/applications/sx8/netcdf-3.6.1/include 
     18%NCDF_LIB        -L/ccc/applications/sx8/netcdf-3.6.1/lib -lnetcdf 
    1919%FC              sxmpif90 
    20 %FCFLAGS         -f2003 nocbind -P stack -dW -Wf,-pvctl res=whole,-A idbl4,-ptr byte -EP -R5 -float0 -size_t64 -dw -Wf,"-pvctl loopcnt=999999 fullmsg noassume"  -Wf"-init heap=zero" 
     20%FCFLAGS         -f2003 nocbind -size_t64 -dW -Wf,"-A idbl4", -sx8 -C vopt -P stack -Wf"-init stack=nan" -Wl"-f nan" -Wf"-P nh -O overlap" -Wf"-P nh" -Wf,-pvctl noassume loopcnt=10000 shape=10000000 -L transform 
    2121%FFLAGS          %FCFLAGS 
    2222%LD              sxmpif90 
    23 %LDFLAGS 
     23%LDFLAGS         -size_t64 
    2424%FPPFLAGS        -P -C -traditional 
    2525%AR              sxar 
    2626%ARFLAGS         rs 
    27 %MK              gmake 
     27%MK              sxgmake 
    2828%USER_INC        %NCDF_INC 
    2929%USER_LIB        %NCDF_LIB 
  • branches/DEV_r1879_FCM/NEMOGCM/CONFIG/makenemo

    r2158 r2292  
    5757# :: 
    5858# 
    59 #  $ ./makenemo -t ifort_osx - j3 -n ORCA2_LIM 
     59#  $ ./makenemo -m ifort_osx - j3 -n ORCA2_LIM 
    6060# 
    6161# 
     
    7979#- Local variables --- 
    8080b_n=$(basename ${0}) 
    81 export MAIN_DIR=${PWD%/NEMOGCM*}/NEMOGCM 
     81export MAIN_DIR=${PWD%/CONFIG*} 
    8282export CONFIG_DIR=${MAIN_DIR}/CONFIG 
    8383export TOOLS_DIR=${MAIN_DIR}/TOOLS 
     
    8585export NEMO_DIR=${MAIN_DIR}/NEMO 
    8686export AGRIFUSE=10 
     87 
    8788declare -a TAB 
    8889#- 
  • branches/DEV_r1879_FCM/NEMOGCM/EXTERNAL/XMLIO_SERVER/src/IOSERVER/mod_mpi_buffer_server.f90

    r1897 r2292  
    157157   
    158158  SUBROUTINE Fill_request(n,pos,message_size) 
    159   USE mpi 
     159  USE mpi_mod 
    160160  IMPLICIT NONE 
    161161    INTEGER :: n 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/DOM/phycst.F90

    r2160 r2292  
    4848#endif 
    4949 
    50    REAL(wp), PUBLIC ::   rau0     = 1020._wp      !: reference volumic mass (density)  (kg/m3) 
     50   REAL(wp), PUBLIC ::   rau0     = 1035._wp      !: reference volumic mass (density)  (kg/m3) 
    5151   REAL(wp), PUBLIC ::   rau0r                    !: reference specific volume         (m3/kg) 
    5252   REAL(wp), PUBLIC ::   rcp      =    4.e+3_wp   !: ocean specific heat 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/OBC/obcfla.F90

    r2097 r2292  
    8787               &            - sshfoe(jj) )  ) * uemsk(jj,1) 
    8888         END DO 
    89       END DO 
    90       DO ji = nie0p1, nie1p1 
    9189         DO jj = 1, jpj 
    9290            sshfoe_b(ji,jj) = sshfoe_b(ji,jj) + sqrt( grav*hur(ji,jj) )     & 
     
    156154               &                - sshfon(ji) ) ) * vnmsk(ji,1) 
    157155         END DO 
    158       END DO 
    159       DO jj = njn0p1, njn1p1 
    160156         DO ji = 1, jpi 
    161157            sshfon_b(ji,jj) = sshfon_b(ji,jj) + sqrt( grav * hvr(ji,jj) )  & 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/OBC/obcini.F90

    r2204 r2292  
    7070 
    7171      ! convert DOCTOR namelist name into the OLD names 
    72       nbobc    = 0 
    7372      nobc_dta = nn_obcdta 
    7473      cffile   = cn_obcdta 
     
    430429         END DO 
    431430      END IF 
     431 
    432432      IF( lp_obc_west ) THEN ! ... West open boundary lateral surface 
    433433         DO ji = niw0, niw1 
     
    437437         END DO 
    438438      END IF 
     439 
    439440      IF( lp_obc_north ) THEN ! ... North open boundary lateral surface 
    440441         DO jj = njn0, njn1 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/SBC/cpl_oasis3.F90

    r2160 r2292  
    2929   USE mod_prism_put_proto          ! OASIS3 prism module for snding 
    3030   USE mod_prism_get_proto          ! OASIS3 prism module for receiving 
     31   USE mod_comprism_proto           ! OASIS3 prism module to get coupling frequency 
    3132   USE par_oce                      ! ocean parameters 
    3233   USE dom_oce                      ! ocean space and time domain 
     
    6162   PUBLIC cpl_prism_snd 
    6263   PUBLIC cpl_prism_rcv 
     64   PUBLIC cpl_prism_freq 
    6365   PUBLIC cpl_prism_finalize 
    6466 
     
    210212      !! * Arguments 
    211213      !! 
    212       INTEGER,                      INTENT( IN    )   :: kid       ! variable intex in the array 
     214      INTEGER,                      INTENT( IN    )   :: kid       ! variable index in the array 
    213215      INTEGER,                      INTENT(   OUT )   :: kinfo     ! OASIS3 info argument 
    214216      INTEGER,                      INTENT( IN    )   :: kstep     ! ocean time-step in seconds 
     
    247249      !!      like stresses and fluxes from the coupler or remote application. 
    248250      !!---------------------------------------------------------------------- 
    249       INTEGER,                      INTENT( IN    )   :: kid       ! variable intex in the array 
     251      INTEGER,                      INTENT( IN    )   :: kid       ! variable index in the array 
    250252      INTEGER,                      INTENT( IN    )   :: kstep     ! ocean time-step in seconds 
    251253      REAL(wp), DIMENSION(jpi,jpj), INTENT( INOUT )   :: pdata     ! IN to keep the value if nothing is done 
     
    293295 
    294296 
     297   FUNCTION cpl_prism_freq( kid )   
     298 
     299      !!--------------------------------------------------------------------- 
     300      !!              ***  ROUTINE cpl_prism_freq  *** 
     301      !! 
     302      !! ** Purpose : - send back the coupling frequency for a particular field 
     303      !!---------------------------------------------------------------------- 
     304      INTEGER,INTENT( IN )   :: kid              ! variable index  
     305      INTEGER                :: cpl_prism_freq   ! coupling frequency 
     306      cpl_prism_freq = ig_def_freq( kid ) 
     307 
     308   END FUNCTION cpl_prism_freq 
     309 
     310 
    295311   SUBROUTINE cpl_prism_finalize 
    296312 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_core.F90

    r2160 r2292  
    2626   USE fldread         ! read input fields 
    2727   USE sbc_oce         ! Surface boundary condition: ocean fields 
     28   USE sbcdcy          ! surface boundary condition: diurnal cycle 
    2829   USE iom             ! I/O manager library 
    2930   USE in_out_manager  ! I/O manager 
     
    6162   REAL(wp), PARAMETER ::   Stef =    5.67e-8     ! Stefan Boltzmann constant 
    6263   REAL(wp), PARAMETER ::   Cice =    1.63e-3     ! transfer coefficient over ice 
     64   REAL(wp), PARAMETER ::   albo =    0.066       ! ocean albedo assumed to be contant 
    6365 
    6466   !                                !!* Namelist namsbc_core : CORE bulk parameters 
     
    146148         REWIND( numnam )                    ! ... read in namlist namsbc_core 
    147149         READ  ( numnam, namsbc_core ) 
    148          ! 
    149          ! store namelist information in an array 
     150         !                                         ! check: do we plan to use ln_dm2dc with non-daily forcing? 
     151         IF( ln_dm2dc .AND. sn_qsr%nfreqh /= 24 )   &  
     152            &   CALL ctl_stop( 'sbc_blk_core: ln_dm2dc can be activated only with daily short-wave forcing' )  
     153         IF( ln_dm2dc .AND. sn_qsr%ln_tint ) THEN 
     154            CALL ctl_warn( 'sbc_blk_core: ln_dm2dc is taking care of the temporal interpolation of daily qsr',   & 
     155                 &         '              ==> We force time interpolation = .false. for qsr' ) 
     156            sn_qsr%ln_tint = .false. 
     157         ENDIF 
     158         !                                         ! store namelist information in an array 
    150159         slf_i(jp_wndi) = sn_wndi   ;   slf_i(jp_wndj) = sn_wndj 
    151160         slf_i(jp_qsr ) = sn_qsr    ;   slf_i(jp_qlw ) = sn_qlw 
     
    260269      ! ----------------------------------------------------------------------------- ! 
    261270     
    262       ! ocean albedo assumed to be 0.066 
    263 !CDIR COLLAPSE 
    264       qsr (:,:) = ( 1. - 0.066 ) * sf(jp_qsr)%fnow(:,:) * tmask(:,:,1)                                 ! Short Wave 
     271      ! ocean albedo assumed to be constant + modify now Qsr to include the diurnal cycle                  ! Short Wave 
     272      zztmp = 1. - albo 
     273      IF( ln_dm2dc ) THEN   ;   qsr(:,:) = zztmp * sbc_dcy( sf(jp_qsr)%fnow(:,:) ) * tmask(:,:,1) 
     274      ELSE                  ;   qsr(:,:) = zztmp *          sf(jp_qsr)%fnow(:,:)   * tmask(:,:,1) 
     275      ENDIF 
    265276!CDIR COLLAPSE 
    266277      zqlw(:,:) = (  sf(jp_qlw)%fnow(:,:) - Stef * zst(:,:)*zst(:,:)*zst(:,:)*zst(:,:)  ) * tmask(:,:,1)   ! Long  Wave 
     
    414425      REAL(wp) ::   zst2, zst3 
    415426      REAL(wp) ::   zcoef_wnorm, zcoef_wnorm2, zcoef_dqlw, zcoef_dqla, zcoef_dqsb 
     427      REAL(wp) ::   zztmp                                        ! temporary variable 
    416428      REAL(wp) ::   zcoef_frca                                   ! fractional cloud amount 
    417429      REAL(wp) ::   zwnorm_f, zwndi_f , zwndj_f                  ! relative wind module and components at F-point 
     
    501513      END SELECT 
    502514 
     515      zztmp = 1. / ( 1. - albo ) 
    503516      !                                     ! ========================== ! 
    504517      DO jl = 1, ijpl                       !  Loop over ice categories  ! 
     
    515528               zst3 = pst(ji,jj,jl) * zst2 
    516529               ! Short Wave (sw) 
    517                p_qsr(ji,jj,jl) = ( 1. - palb(ji,jj,jl) ) * sf(jp_qsr)%fnow(ji,jj) * tmask(ji,jj,1) 
     530               p_qsr(ji,jj,jl) = zztmp * ( 1. - palb(ji,jj,jl) ) * qsr(ji,jj) 
    518531               ! Long  Wave (lw) 
    519532               z_qlw(ji,jj,jl) = 0.95 * (  sf(jp_qlw)%fnow(ji,jj)       &                          
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r2160 r2292  
    2323   USE sbc_oce         ! Surface boundary condition: ocean fields 
    2424   USE sbc_ice         ! Surface boundary condition: ice fields 
     25   USE sbcdcy          ! surface boundary condition: diurnal cycle 
    2526   USE phycst          ! physical constants 
    2627#if defined key_lim3 
     
    527528      CALL cpl_prism_define(jprcv, jpsnd)             
    528529      ! 
     530      IF( ln_dm2dc .AND. ( cpl_prism_freq( jpr_qsroce ) + cpl_prism_freq( jpr_qsrmix ) /= 86400 ) )   & 
     531         &   CALL ctl_stop( 'sbc_cpl_init: diurnal cycle reconstruction (ln_dm2dc) needs daily couping for solar radiation' ) 
     532 
    529533   END SUBROUTINE sbc_cpl_init 
    530534 
     
    728732         IF( srcv(jpr_qsroce)%laction )   qsr(:,:) = frcv(:,:,jpr_qsroce)  
    729733         IF( srcv(jpr_qsrmix)%laction )   qsr(:,:) = frcv(:,:,jpr_qsrmix) 
     734         IF( ln_dm2dc )   qsr(:,:) = sbc_dcy( qsr )                           ! modify qsr to include the diurnal cycle 
    730735         ! 
    731736         !                                                       ! total freshwater fluxes over the ocean (emp, emps) 
     
    11591164            &                     + palbi         (:,:,1) * zicefr(:,:,1) ) ) 
    11601165      END SELECT 
     1166      IF( ln_dm2dc ) THEN   ! modify qsr to include the diurnal cycle 
     1167         pqsr_tot(:,:  ) = sbc_dcy( pqsr_tot(:,:  ) ) 
     1168         pqsr_ice(:,:,1) = sbc_dcy( pqsr_ice(:,:,1) ) 
     1169      ENDIF 
    11611170 
    11621171      SELECT CASE( TRIM( cn_rcv_dqnsdt ) ) 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/SBC/sbcflx.F90

    r2160 r2292  
    2727   USE oce             ! ocean dynamics and tracers 
    2828   USE dom_oce         ! ocean space and time domain 
    29    USE sbc_oce         ! Surface boundary condition: ocean fields 
     29   USE sbc_oce         ! surface boundary condition: ocean fields 
     30   USE sbcdcy          ! surface boundary condition: diurnal cycle on qsr 
    3031   USE phycst          ! physical constants 
    3132   USE fldread         ! read input fields 
     
    114115         REWIND ( numnam )               ! ... read in namlist namflx 
    115116         READ   ( numnam, namsbc_flx )  
    116  
    117          ! store namelist information in an array 
     117         ! 
     118         !                                         ! check: do we plan to use ln_dm2dc with non-daily forcing? 
     119         IF( ln_dm2dc .AND. sn_qsr%nfreqh /= 24 )   & 
     120            &   CALL ctl_stop( 'sbc_blk_core: ln_dm2dc can be activated only with daily short-wave forcing' )  
     121         ! 
     122         !                                         ! store namelist information in an array 
    118123         slf_i(jp_utau) = sn_utau   ;   slf_i(jp_vtau) = sn_vtau 
    119124         slf_i(jp_qtot) = sn_qtot   ;   slf_i(jp_qsr ) = sn_qsr  
     
    141146      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN 
    142147         ! 
     148         IF( ln_dm2dc ) THEN   ;   qsr(:,:) = sbc_dcy( sf(jp_qsr)%fnow(:,:) )   ! modify now Qsr to include the diurnal cycle 
     149         ELSE                  ;   qsr(:,:) =          sf(jp_qsr)%fnow(:,:) 
     150         ENDIF 
    143151         ! set the ocean fluxes from read fields 
    144152!CDIR COLLAPSE 
     
    148156               vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj) 
    149157               qns (ji,jj) = sf(jp_qtot)%fnow(ji,jj) - sf(jp_qsr)%fnow(ji,jj) 
    150                qsr (ji,jj) = sf(jp_qsr )%fnow(ji,jj) 
    151158               emp (ji,jj) = sf(jp_emp )%fnow(ji,jj) 
    152159            END DO 
  • branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r2160 r2292  
    1818   USE sbc_oce         ! Surface boundary condition: ocean fields 
    1919   USE sbc_ice         ! Surface boundary condition: ice fields 
     20   USE sbcdcy          ! surface boundary condition: diurnal cycle 
    2021   USE sbcssm          ! surface boundary condition: sea-surface mean variables 
    2122   USE sbcana          ! surface boundary condition: analytical formulation 
     
    8283      READ  ( numnam, namsbc ) 
    8384 
    84       ! overwrite namelist parameter using CPP key information 
    85 !!gm here no overwrite, test all option via namelist change: require more incore memory 
    86 !!gm  IF( lk_sbc_cpl       ) THEN   ;   ln_cpl      = .TRUE.   ;   ELSE   ;   ln_cpl      = .FALSE.   ;   ENDIF 
    87  
    88       IF ( Agrif_Root() ) THEN 
    89         IF( lk_lim2 )            nn_ice      = 2 
    90         IF( lk_lim3 )            nn_ice      = 3 
    91       ENDIF 
    92       ! 
    93       IF( cp_cfg == 'gyre' ) THEN 
     85      !                          ! overwrite namelist parameter using CPP key information 
     86      IF( Agrif_Root() ) THEN                ! AGRIF zoom 
     87        IF( lk_lim2 )   nn_ice      = 2 
     88        IF( lk_lim3 )   nn_ice      = 3 
     89      ENDIF 
     90      IF( cp_cfg == 'gyre' ) THEN            ! GYRE configuration 
    9491          ln_ana      = .TRUE.    
    9592          nn_ice      =   0 
    9693      ENDIF 
    9794       
    98       ! Control print 
    99       IF(lwp) THEN 
     95      IF(lwp) THEN               ! Control print 
    10096         WRITE(numout,*) '        Namelist namsbc (partly overwritten with CPP key setting)' 
    10197         WRITE(numout,*) '           frequency update of sbc (and ice)             nn_fsbc     = ', nn_fsbc 
     
    116112      ENDIF 
    117113 
     114      !                          ! Checks: 
    118115      IF( .NOT. ln_rnf ) THEN                      ! no specific treatment in vicinity of river mouths  
    119116         ln_rnf_mouth  = .false.                       
     
    138135         &   CALL ctl_stop( 'sea-ice model requires a bulk formulation or coupled configuration' ) 
    139136       
    140       ! Choice of the Surface Boudary Condition (set nsbc) 
     137      IF( ln_dm2dc )   nday_qsr = -1   ! initialisation flag 
     138 
     139      IF( ln_dm2dc .AND. .NOT.( ln_flx .OR. ln_blk_core ) )   & 
     140         &   CALL ctl_stop( 'diurnal cycle into qsr field from daily values requires a flux or core-bulk formulation' ) 
     141       
     142      IF( ln_dm2dc .AND. ( ( NINT(rday) / ( nn_fsbc * NINT(rdt) ) )  < 8 ) )   & 
     143         &   CALL ctl_warn( 'diurnal cycle for qsr: the sampling of the diurnal cycle is too small...' ) 
     144       
     145      !                          ! Choice of the Surface Boudary Condition (set nsbc) 
    141146      icpt = 0 
    142147      IF( ln_ana          ) THEN   ;   nsbc =  1   ; icpt = icpt + 1   ;   ENDIF       ! analytical      formulation 
     
    147152      IF( cp_cfg == 'gyre') THEN   ;   nsbc =  0                       ;   ENDIF       ! GYRE analytical formulation 
    148153      IF( lk_esopa        )            nsbc = -1                                       ! esopa test, ALL formulations 
    149  
     154      ! 
    150155      IF( icpt /= 1 .AND. .NOT.lk_esopa ) THEN 
    151156         WRITE(numout,*) 
     
    216221      ! Misc. Options 
    217222      ! ------------- 
    218  
    219 !!gm  IF( ln_dm2dc       )   CALL sbc_dcy( kt )                 ! Daily mean qsr distributed over the Diurnal Cycle 
    220223       
    221224      SELECT CASE( nn_ice )                                     ! Update heat and freshwater fluxes over sea-ice areas 
     
    239242         CALL iom_put( "emp"    , emp       )                   ! upward water flux 
    240243         CALL iom_put( "emps"   , emps      )                   ! c/d water flux 
    241          CALL iom_put( "qns+qsr", qns + qsr )                   ! total heat flux   (caution if ln_dm2dc=true, to be  
    242          CALL iom_put( "qns"    , qns       )                   ! solar heat flux    moved after the call to iom_setkt) 
    243          CALL iom_put( "qsr"    ,       qsr )                   ! solar heat flux    moved after the call to iom_setkt) 
     244         CALL iom_put( "qns+qsr", qns + qsr )                   ! total heat flux 
     245         CALL iom_put( "qns"    , qns       )                   ! solar heat flux 
     246         CALL iom_put( "qsr"    ,       qsr )                   ! solar heat flux 
    244247         IF(  nn_ice > 0 )   CALL iom_put( "ice_cover", fr_i )  ! ice fraction  
    245248      ENDIF 
  • branches/DEV_r1879_FCM/NEMOGCM/TOOLS/COMPILE/Fgo_to_TOOLS.sh

    r2143 r2292  
    5353#- 
    5454 
    55 local MAIN_DIR=${PWD%/NEMOGCM/*}/NEMOGCM 
    5655cd ${MAIN_DIR}/TOOLS 
  • branches/DEV_r1879_FCM/NEMOGCM/TOOLS/COMPILE/bld.cfg

    r2178 r2292  
    7575bld::excl_dep        use::mod_prism_get_proto 
    7676bld::excl_dep        use::mod_prism_put_proto 
     77bld::excl_dep        use::mod_comprism_proto 
    7778bld::excl_dep        use::mkl_dfti 
    7879# Don't generate interface files 
  • branches/DEV_r1879_FCM/NEMOGCM/TOOLS/maketools

    r2158 r2292  
    7474#- Local variables --- 
    7575b_n=$(basename ${0}) 
    76 export MAIN_DIR=${PWD%/NEMOGCM*}/NEMOGCM 
     76export MAIN_DIR=${PWD%/TOOLS*} 
    7777export TOOLS_DIR=${MAIN_DIR}/TOOLS 
    7878export COMPIL_DIR=${MAIN_DIR}/TOOLS/COMPILE 
Note: See TracChangeset for help on using the changeset viewer.