Changeset 2292
- Timestamp:
- 2010-10-19T12:15:40+02:00 (14 years ago)
- 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 15 15 16 16 17 %NCDF_INC -I/ usr/local/SX8/soft/netcdf/include18 %NCDF_LIB -L/ usr/local/SX8/soft/netcdf/lib -lnetcdf17 %NCDF_INC -I/ccc/applications/sx8/netcdf-3.6.1/include 18 %NCDF_LIB -L/ccc/applications/sx8/netcdf-3.6.1/lib -lnetcdf 19 19 %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 21 21 %FFLAGS %FCFLAGS 22 22 %LD sxmpif90 23 %LDFLAGS 23 %LDFLAGS -size_t64 24 24 %FPPFLAGS -P -C -traditional 25 25 %AR sxar 26 26 %ARFLAGS rs 27 %MK gmake27 %MK sxgmake 28 28 %USER_INC %NCDF_INC 29 29 %USER_LIB %NCDF_LIB -
branches/DEV_r1879_FCM/NEMOGCM/CONFIG/makenemo
r2158 r2292 57 57 # :: 58 58 # 59 # $ ./makenemo - tifort_osx - j3 -n ORCA2_LIM59 # $ ./makenemo -m ifort_osx - j3 -n ORCA2_LIM 60 60 # 61 61 # … … 79 79 #- Local variables --- 80 80 b_n=$(basename ${0}) 81 export MAIN_DIR=${PWD%/ NEMOGCM*}/NEMOGCM81 export MAIN_DIR=${PWD%/CONFIG*} 82 82 export CONFIG_DIR=${MAIN_DIR}/CONFIG 83 83 export TOOLS_DIR=${MAIN_DIR}/TOOLS … … 85 85 export NEMO_DIR=${MAIN_DIR}/NEMO 86 86 export AGRIFUSE=10 87 87 88 declare -a TAB 88 89 #- -
branches/DEV_r1879_FCM/NEMOGCM/EXTERNAL/XMLIO_SERVER/src/IOSERVER/mod_mpi_buffer_server.f90
r1897 r2292 157 157 158 158 SUBROUTINE Fill_request(n,pos,message_size) 159 USE mpi 159 USE mpi_mod 160 160 IMPLICIT NONE 161 161 INTEGER :: n -
branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/DOM/phycst.F90
r2160 r2292 48 48 #endif 49 49 50 REAL(wp), PUBLIC :: rau0 = 10 20._wp !: reference volumic mass (density) (kg/m3)50 REAL(wp), PUBLIC :: rau0 = 1035._wp !: reference volumic mass (density) (kg/m3) 51 51 REAL(wp), PUBLIC :: rau0r !: reference specific volume (m3/kg) 52 52 REAL(wp), PUBLIC :: rcp = 4.e+3_wp !: ocean specific heat -
branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/OBC/obcfla.F90
r2097 r2292 87 87 & - sshfoe(jj) ) ) * uemsk(jj,1) 88 88 END DO 89 END DO90 DO ji = nie0p1, nie1p191 89 DO jj = 1, jpj 92 90 sshfoe_b(ji,jj) = sshfoe_b(ji,jj) + sqrt( grav*hur(ji,jj) ) & … … 156 154 & - sshfon(ji) ) ) * vnmsk(ji,1) 157 155 END DO 158 END DO159 DO jj = njn0p1, njn1p1160 156 DO ji = 1, jpi 161 157 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 70 70 71 71 ! convert DOCTOR namelist name into the OLD names 72 nbobc = 073 72 nobc_dta = nn_obcdta 74 73 cffile = cn_obcdta … … 430 429 END DO 431 430 END IF 431 432 432 IF( lp_obc_west ) THEN ! ... West open boundary lateral surface 433 433 DO ji = niw0, niw1 … … 437 437 END DO 438 438 END IF 439 439 440 IF( lp_obc_north ) THEN ! ... North open boundary lateral surface 440 441 DO jj = njn0, njn1 -
branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/SBC/cpl_oasis3.F90
r2160 r2292 29 29 USE mod_prism_put_proto ! OASIS3 prism module for snding 30 30 USE mod_prism_get_proto ! OASIS3 prism module for receiving 31 USE mod_comprism_proto ! OASIS3 prism module to get coupling frequency 31 32 USE par_oce ! ocean parameters 32 33 USE dom_oce ! ocean space and time domain … … 61 62 PUBLIC cpl_prism_snd 62 63 PUBLIC cpl_prism_rcv 64 PUBLIC cpl_prism_freq 63 65 PUBLIC cpl_prism_finalize 64 66 … … 210 212 !! * Arguments 211 213 !! 212 INTEGER, INTENT( IN ) :: kid ! variable in tex in the array214 INTEGER, INTENT( IN ) :: kid ! variable index in the array 213 215 INTEGER, INTENT( OUT ) :: kinfo ! OASIS3 info argument 214 216 INTEGER, INTENT( IN ) :: kstep ! ocean time-step in seconds … … 247 249 !! like stresses and fluxes from the coupler or remote application. 248 250 !!---------------------------------------------------------------------- 249 INTEGER, INTENT( IN ) :: kid ! variable in tex in the array251 INTEGER, INTENT( IN ) :: kid ! variable index in the array 250 252 INTEGER, INTENT( IN ) :: kstep ! ocean time-step in seconds 251 253 REAL(wp), DIMENSION(jpi,jpj), INTENT( INOUT ) :: pdata ! IN to keep the value if nothing is done … … 293 295 294 296 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 295 311 SUBROUTINE cpl_prism_finalize 296 312 -
branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_core.F90
r2160 r2292 26 26 USE fldread ! read input fields 27 27 USE sbc_oce ! Surface boundary condition: ocean fields 28 USE sbcdcy ! surface boundary condition: diurnal cycle 28 29 USE iom ! I/O manager library 29 30 USE in_out_manager ! I/O manager … … 61 62 REAL(wp), PARAMETER :: Stef = 5.67e-8 ! Stefan Boltzmann constant 62 63 REAL(wp), PARAMETER :: Cice = 1.63e-3 ! transfer coefficient over ice 64 REAL(wp), PARAMETER :: albo = 0.066 ! ocean albedo assumed to be contant 63 65 64 66 ! !!* Namelist namsbc_core : CORE bulk parameters … … 146 148 REWIND( numnam ) ! ... read in namlist namsbc_core 147 149 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 150 159 slf_i(jp_wndi) = sn_wndi ; slf_i(jp_wndj) = sn_wndj 151 160 slf_i(jp_qsr ) = sn_qsr ; slf_i(jp_qlw ) = sn_qlw … … 260 269 ! ----------------------------------------------------------------------------- ! 261 270 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 265 276 !CDIR COLLAPSE 266 277 zqlw(:,:) = ( sf(jp_qlw)%fnow(:,:) - Stef * zst(:,:)*zst(:,:)*zst(:,:)*zst(:,:) ) * tmask(:,:,1) ! Long Wave … … 414 425 REAL(wp) :: zst2, zst3 415 426 REAL(wp) :: zcoef_wnorm, zcoef_wnorm2, zcoef_dqlw, zcoef_dqla, zcoef_dqsb 427 REAL(wp) :: zztmp ! temporary variable 416 428 REAL(wp) :: zcoef_frca ! fractional cloud amount 417 429 REAL(wp) :: zwnorm_f, zwndi_f , zwndj_f ! relative wind module and components at F-point … … 501 513 END SELECT 502 514 515 zztmp = 1. / ( 1. - albo ) 503 516 ! ! ========================== ! 504 517 DO jl = 1, ijpl ! Loop over ice categories ! … … 515 528 zst3 = pst(ji,jj,jl) * zst2 516 529 ! 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) 518 531 ! Long Wave (lw) 519 532 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 23 23 USE sbc_oce ! Surface boundary condition: ocean fields 24 24 USE sbc_ice ! Surface boundary condition: ice fields 25 USE sbcdcy ! surface boundary condition: diurnal cycle 25 26 USE phycst ! physical constants 26 27 #if defined key_lim3 … … 527 528 CALL cpl_prism_define(jprcv, jpsnd) 528 529 ! 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 529 533 END SUBROUTINE sbc_cpl_init 530 534 … … 728 732 IF( srcv(jpr_qsroce)%laction ) qsr(:,:) = frcv(:,:,jpr_qsroce) 729 733 IF( srcv(jpr_qsrmix)%laction ) qsr(:,:) = frcv(:,:,jpr_qsrmix) 734 IF( ln_dm2dc ) qsr(:,:) = sbc_dcy( qsr ) ! modify qsr to include the diurnal cycle 730 735 ! 731 736 ! ! total freshwater fluxes over the ocean (emp, emps) … … 1159 1164 & + palbi (:,:,1) * zicefr(:,:,1) ) ) 1160 1165 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 1161 1170 1162 1171 SELECT CASE( TRIM( cn_rcv_dqnsdt ) ) -
branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/SBC/sbcflx.F90
r2160 r2292 27 27 USE oce ! ocean dynamics and tracers 28 28 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 30 31 USE phycst ! physical constants 31 32 USE fldread ! read input fields … … 114 115 REWIND ( numnam ) ! ... read in namlist namflx 115 116 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 118 123 slf_i(jp_utau) = sn_utau ; slf_i(jp_vtau) = sn_vtau 119 124 slf_i(jp_qtot) = sn_qtot ; slf_i(jp_qsr ) = sn_qsr … … 141 146 IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN 142 147 ! 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 143 151 ! set the ocean fluxes from read fields 144 152 !CDIR COLLAPSE … … 148 156 vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj) 149 157 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)151 158 emp (ji,jj) = sf(jp_emp )%fnow(ji,jj) 152 159 END DO -
branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90
r2160 r2292 18 18 USE sbc_oce ! Surface boundary condition: ocean fields 19 19 USE sbc_ice ! Surface boundary condition: ice fields 20 USE sbcdcy ! surface boundary condition: diurnal cycle 20 21 USE sbcssm ! surface boundary condition: sea-surface mean variables 21 22 USE sbcana ! surface boundary condition: analytical formulation … … 82 83 READ ( numnam, namsbc ) 83 84 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 94 91 ln_ana = .TRUE. 95 92 nn_ice = 0 96 93 ENDIF 97 94 98 ! Control print 99 IF(lwp) THEN 95 IF(lwp) THEN ! Control print 100 96 WRITE(numout,*) ' Namelist namsbc (partly overwritten with CPP key setting)' 101 97 WRITE(numout,*) ' frequency update of sbc (and ice) nn_fsbc = ', nn_fsbc … … 116 112 ENDIF 117 113 114 ! ! Checks: 118 115 IF( .NOT. ln_rnf ) THEN ! no specific treatment in vicinity of river mouths 119 116 ln_rnf_mouth = .false. … … 138 135 & CALL ctl_stop( 'sea-ice model requires a bulk formulation or coupled configuration' ) 139 136 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) 141 146 icpt = 0 142 147 IF( ln_ana ) THEN ; nsbc = 1 ; icpt = icpt + 1 ; ENDIF ! analytical formulation … … 147 152 IF( cp_cfg == 'gyre') THEN ; nsbc = 0 ; ENDIF ! GYRE analytical formulation 148 153 IF( lk_esopa ) nsbc = -1 ! esopa test, ALL formulations 149 154 ! 150 155 IF( icpt /= 1 .AND. .NOT.lk_esopa ) THEN 151 156 WRITE(numout,*) … … 216 221 ! Misc. Options 217 222 ! ------------- 218 219 !!gm IF( ln_dm2dc ) CALL sbc_dcy( kt ) ! Daily mean qsr distributed over the Diurnal Cycle220 223 221 224 SELECT CASE( nn_ice ) ! Update heat and freshwater fluxes over sea-ice areas … … 239 242 CALL iom_put( "emp" , emp ) ! upward water flux 240 243 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 be242 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 244 247 IF( nn_ice > 0 ) CALL iom_put( "ice_cover", fr_i ) ! ice fraction 245 248 ENDIF -
branches/DEV_r1879_FCM/NEMOGCM/TOOLS/COMPILE/Fgo_to_TOOLS.sh
r2143 r2292 53 53 #- 54 54 55 local MAIN_DIR=${PWD%/NEMOGCM/*}/NEMOGCM56 55 cd ${MAIN_DIR}/TOOLS -
branches/DEV_r1879_FCM/NEMOGCM/TOOLS/COMPILE/bld.cfg
r2178 r2292 75 75 bld::excl_dep use::mod_prism_get_proto 76 76 bld::excl_dep use::mod_prism_put_proto 77 bld::excl_dep use::mod_comprism_proto 77 78 bld::excl_dep use::mkl_dfti 78 79 # Don't generate interface files -
branches/DEV_r1879_FCM/NEMOGCM/TOOLS/maketools
r2158 r2292 74 74 #- Local variables --- 75 75 b_n=$(basename ${0}) 76 export MAIN_DIR=${PWD%/ NEMOGCM*}/NEMOGCM76 export MAIN_DIR=${PWD%/TOOLS*} 77 77 export TOOLS_DIR=${MAIN_DIR}/TOOLS 78 78 export COMPIL_DIR=${MAIN_DIR}/TOOLS/COMPILE
Note: See TracChangeset
for help on using the changeset viewer.