! -Mode: f90 -*- !! MODULE mod_inipar !> prefixture du fichier de definitions CONTAINS SUBROUTINE inipar !! USE defprec USE dimensions USE fliocom USE getincom USE errioipsl !! IMPLICIT NONE INTEGER (kind=il) :: ierr CHARACTER (lEN=80) :: cn_arg CHARACTER (LEN=LEN(c_suffix)) :: cl_suffix ! WRITE (nout, *) 'Types par defaut : ' WRITE (nout, *) 'INTEGER : ', i_std WRITE (nout, *) 'REAL : ', r_std ! !! !Config Key = c_suffix !Config Desc = Rajoute un suffixe a tous les noms de fichiers !Config Help = !Config Def = 'none' c_suffix = 'none' CALL getin ('c_suffix', cl_suffix) IF ( LEN_TRIM (cl_suffix) == 0 .OR. TRIM(cl_suffix) == 'none' ) THEN c_suffix = '' ELSE c_suffix = '_' // TRIM(cl_suffix) END IF WRITE (unit=nout, fmt=*) 'cl_suffix : ', TRIM(cl_suffix) WRITE (unit=nout, fmt=*) 'c_suffix : ', TRIM(c_suffix) !Config Key = c_comment !Config Desc = Rajoute un commentaire dans tous les fichiers NetCDF !Config Help = !Config Def = 'none' c_comment = 'none' CALL getin ('c_comment', c_comment) WRITE (unit=nout, fmt=*) 'c_comment : ', TRIM(c_comment) !! !Config Key = l_ipsldbg !Config Desc = Pour mettre IOIPSL en mode debug. !Config Help = !Config Def = n l_ipsldbg= .FALSE. CALL getin ('l_ipsldbg', l_ipsldbg) WRITE (unit=nout, fmt=*) 'l_ipsldbg = ', l_ipsldbg CALL ipsldbg (l_ipsldbg) !! !Config Key = l_d_alloc !Config Desc = pour suivre les allocs memoire !Config Help = !Config Def = n l_d_alloc = .FALSE. CALL getin ('l_d_alloc', l_d_alloc) WRITE (unit=nout, fmt=*) 'l_d_alloc = ', l_d_alloc ! !Config Key = l_fast !Config Desc = Pour tester les I/O : calcul rapide de poids !Config Help = !Config Def = n l_fast = .FALSE. CALL getin ('l_fast', l_fast) WRITE (unit=nout, fmt=*) 'l_fast = ', l_fast !Config Key = l_dryrun !Config Desc = Pour tester les I/O : pas de calcul de poids. !Config Help = !Config Def = n l_dryrun= .FALSE. CALL getin ('l_dryrun', l_dryrun) WRITE (unit=nout, fmt=*) 'l_dryrun = ', l_dryrun !Config Key = lev_dry !Config Desc = Type de test !Config Help = !Config Def = 1 lev_dry= 1 CALL getin ('lev_dry', lev_dry) WRITE (unit=nout, fmt=*) 'lev_dry = ', lev_dry !! !! Define ocean model !! !Config Key = c_period !Config Help = !Config Def = 'none' c_period = 'none' CALL getin ('c_period', c_period) WRITE (unit=nout, fmt=*) 'c_period = ', c_period !! !Config Key = jpoi !Config Desc = ocean x dimension !Config Help = !Config Def = 0 CALL getin ('jpoi', jpoi) !Config Key = jpoj !Config Desc = ocean y dimension !Config Help = !Config Def = 0 CALL getin ('jpoj', jpoj) WRITE (unit=nout, fmt=*) 'jpoi = ', jpoi, ' jpoj = ', jpoj !Config Key = comod !Config Desc = ocean model name !Config Help = !Config Def = opa CALL getin ('comod', comod) !Config Key = cotyp !Config Desc = ocean model type !Config Help = !Config Def = orca2 cotyp = 'orca2' CALL getin ('cotyp', cotyp) WRITE (unit=nout, fmt=*) 'cotyp = ', cotyp !Config Key = jpoe !Config Desc = number of edges for ocean !Config Def = 9 !Config Help = Number (maxi) of edges to describe ocean box jpoe = 9_il CALL getin ('jpoe', jpoe) WRITE (unit=nout, fmt=*) 'jpoe = ', jpoe !Config Key = noperio !Config Desc = ocean periodicity type !Config Def = 4 !Config Help = Number (maxi) of edges to describe ocean box noperio = 4_il CALL getin ('noperio', noperio) WRITE (unit=nout, fmt=*) 'noperio = ', noperio !Config Key = l_recalc_o !Config Desc = Recompute ocean surfaces !Config Def = y !Config Help = Recompute ocean surfaces l_recalc_o = .TRUE. CALL getin ('l_recalc_o', l_recalc_o) WRITE (unit=nout, fmt=*) 'l_recalc_o = ', l_recalc_o !! !! Define atmosphere model !Config Key = jpai !Config Desc = atm x dimension !Config Help = !Config Def = 0 CALL getin ('jpai', jpai) !Config Key = jpaj !Config Desc = atm y dimension !Config Help = !Config Def = 0 CALL getin ('jpaj', jpaj) jpait = jpai ; jpajt = jpaj+1 jpaiu = jpai+1 ; jpaju = jpaj+1 jpaiv = jpai+1 ; jpajv = jpaj jpaj = jpaj+1 WRITE (unit=nout, fmt=*) 'jpai = ', jpai , ' jpaj = ', jpaj WRITE (unit=nout, fmt=*) 'jpait = ', jpait, ' jpajt = ', jpajt WRITE (unit=nout, fmt=*) 'jpaiu = ', jpaiu, ' jpaju = ', jpaju WRITE (unit=nout, fmt=*) 'jpaiv = ', jpaiv, ' jpajv = ', jpajv !Config Key = camod !Config Desc = atm model name !Config Help = !Config Def = lmd CALL getin ('camod', camod) WRITE (unit=nout, fmt=*) 'comod = ', comod !Config Key = catyp !Config Desc = atm model type !Config Help = !Config Def = lmdz catyp = 'lmdz' CALL getin ('catyp', catyp) WRITE (unit=nout, fmt=*) 'catyp = ', catyp !Config Key = jpae !Config Desc = number of edges for atm !Config Def = 9 !Config Help = Number (maxi) of edges to describe atm box jpae = 9_il CALL getin ('jpae', jpae) WRITE (unit=nout, fmt=*) 'jpae = ', jpae !Config Key = naperio !Config Desc = atm periodicity type !Config Def = -1 !Config Help = Number (maxi) of edges to describe ocean box naperio = -1_il CALL getin ('naperio', naperio) WRITE (UNIT=nout, FMT=*) 'naperio = ', naperio !Config Key = la_nortop !Config Desc = atm latitudes orientation in masks.nc, areas.nc, grids.nc !Config Def = .TRUE. !Config Help = .TRUE. increasing latitudes la_nortop = .TRUE. CALL getin ('la_nortop', la_nortop) WRITE (unit=nout, fmt=*) 'la_nortop = ', la_nortop !Config Key = l_recalc_a !Config Desc = Recompute atm surfaces !Config Def = y !Config Help = Recompute atm surfaces l_recalc_a = .TRUE. CALL getin ('l_recalc_a', l_recalc_a) WRITE (unit=nout, fmt=*) 'l_recalc_a = ', l_recalc_a !Config Key = la_pole !Config Desc special handing of atm pole point !Config Def = y la_pole = .FALSE. CALL getin ( 'la_pole', la_pole) WRITE (unit=nout, fmt=*) 'la_pole = ', la_pole !Config Key = o2a_orien !Config Desc = orientation for o2a diag file !Config Def = nord_en_haut o2a_orien = "nord_en_haut" CALL getin ( 'o2a_orien', o2a_orien) WRITE (unit=nout, fmt=*) 'o2a_orien = ', TRIM(o2a_orien) !Config Key = lmaska !Config Desc = If TRUE, masked points of atmospheric grid (land) are considered for computing. !Config Def = y lmaska = .TRUE. CALL getin ( 'lmaska', lmaska) WRITE (unit=nout, fmt=*) 'lmaska = ', lmaska !Config Key = lmasko !Config Desc = If TRUE, masked points of ocean grid (land) are considered for computing. !Config Def = n lmasko = .FALSE. CALL getin ( 'lmasko', lmasko) WRITE (unit=nout, fmt=*) 'lmasko = ', lmasko !Config Key = lwro2a !Config Desc = TRUE if oce -> atm weights/adresses are computed !Config Def = y lwro2a = .TRUE. CALL getin ( 'lwro2a', lwro2a) WRITE (unit=nout, fmt=*) 'lwro2a = ', lwro2a !Config Key = lwra2o !Config Desc = TRUE if atm -> oce weights/adresses are computed !Config Def = y lwra2o = .TRUE. CALL getin ( 'lwra2o', lwra2o) WRITE (unit=nout, fmt=*) 'lwra2o = ', lwra2o !Config Key = normo2a !Config Desc = Type of normalization oce -> atm: 0: none, 1: intensive, 2: extensive !Config Def = 1 normo2a = 1 CALL getin ( 'normo2a', normo2a) WRITE (unit=nout, fmt=*) 'normo2a = ', normo2a !Config Key = norma2o !Config Desc = Type of normalization atm->oce : 0: none, 1: intensive, 2: extensive !Config Def = 1 norma2o = 1 CALL getin ( 'norma2o', norma2o) WRITE (unit=nout, fmt=*) 'norma2o = ', norma2o !!! !Config Key = jpa2o !Config Desc = max number of neighbors of a->o weights !Config Help = !Config Def = 0 CALL getin ('jpa2o', jpa2o) WRITE (UNIT=nout, FMT=*) 'jpa2o = ', jpa2O !Config Key = jpo2a !Config Desc = max number of neighbors of o-> weights !Config Help = !Config Def = 0 CALL getin ('jpo2a', jpo2a) WRITE (UNIT=nout, FMT=*) 'jpo2a = ', jpo2a !! !Config Key = jma2o !Config Desc = number of neighbors of a->o weights (fluxes) !Config Help = !Config Def = 0 jma2o = jpa2o CALL getin ('jma2o', jma2o) WRITE (UNIT=nout, FMT=*) 'jma2o = ', jma2o !Config Key = jma2or !Config Desc = number of neighbors of a->o weights (runoff) !Config Help = !Config Def = 0 jma2or = jpa2o CALL getin ('jma2or', jma2or) WRITE (UNIT=nout, FMT=*) 'jma2or = ', jma2or !Config Key = jma2oi !Config Desc = number of neighbors of a->o weights (icestreams) !Config Help = !Config Def = 0 jma2oi = jpa2o CALL getin ('jma2oi', jma2oi) !Config Key = jmo2a !Config Desc = number of neighbors of o->a weights (temp) !Config Help = !Config Def = 0 jmo2a = jpo2a CALL getin ('jmo2a', jmo2a) WRITE (UNIT=nout, FMT=*) 'jmo2a = ', jmo2a !Config Key = norma2o !Config Desc = type of normalization a->o !Config Help = !Config Def = 0 norma2o = 1 CALL getin ('norma2o', norma2o) WRITE (UNIT=nout, FMT=*) 'norma2o = ', norma2o !Config Key = normo2a !Config Desc = type of normalization o->a !Config Help = !Config Def = 0 normo2a = 1 CALL getin ('normo2a', normo2a) WRITE (UNIT=nout, FMT=*) 'normo2a = ', normo2a !! !Config Key = limit_stack !Config Desc = use to limit memory usage in NetCDF !Config Help = !Config Def = n limit_stack = .FALSE. CALL getin ('limit_stack', limit_stack) WRITE (UNIT=nout, FMT=*) 'limit_stack = ', limit_stack !! !Config Key = l_limit_iosize !COnfig Desc = do not output some diagnostique to limit size of NetCDF files !Config Help = !Config Def = n l_limit_iosize = .FALSE. CALL getin ('l_limit_iosize', l_limit_iosize) WRITE (unit=nout, fmt=*) 'l_limit_iosize = ', l_limit_iosize !Config Key = slice_size !Config Desc = Size of slice in case of limit_stack !Config Help = !Config Def = 10 slice_size = 10 CALL getin ('slice_size', slice_size) WRITE (UNIT=nout, FMT=*) 'slice_size = ', slice_size !Config Key = c_oasis !Config Desc = define file format for Oasis !Config Help = !Config Def = 2.2 c_oasis = '2.2' CALL getin ('c_oasis', c_oasis) WRITE (UNIT=nout, FMT=*) 'c_oasis = ', c_oasis !Config Key = l_grid_cdf !Config Desc = Use if cdf grid should be produced !Config Help = !Config Def = y l_grid_cdf = .TRUE. CALL getin ('l_grid_cdf', l_grid_cdf) WRITE (UNIT=nout, FMT=*) 'l_grid_cdf = ', l_grid_cdf !-$$ !Config Key = l_wei_cdf !-$$ !Config Desc = Use if cdf weights file produced !-$$ !Config Help = !-$$ !Config Def = y !-$$ l_wei_cdf = .TRUE. !-$$ CALL getin ('l_wei_cdf', l_wei_cdf) !-$$ WRITE (UNIT=nout, FMT=*) 'l_wei_cdf = ', l_wei_cdf !Config Key = l_wei_i4 !Config Desc = Use if i4 weights file produced !Config Help = !Config Def = y l_wei_i4 = .TRUE. CALL getin ('l_wei_i4', l_wei_i4) WRITE (UNIT=nout, FMT=*) 'l_wei_i4 = ', l_wei_i4 !Config Key = l_wei_i8 !Config Desc = Use if I8 weights file produced !Config Help = !Config Def = y l_wei_i8 = .FALSE. CALL getin ('l_wei_i8', l_wei_i8) WRITE (UNIT=nout, FMT=*) 'l_wei_i8 = ', l_wei_i8 !Config Key = l_wei_oasis_3 !Config Desc = Use if OASIS3 weights file produced !Config Help = !Config Def = y l_wei_oasis_3 = .TRUE. CALL getin ('l_wei_oasis_3', l_wei_oasis_3) WRITE (UNIT=nout, FMT=*) 'l_wei_oasis_3 = ', l_wei_oasis_3 !Config Key = l_wei_oasis_mct !Config Desc = Use if OASIS MCT weights file produced !Config Help = !Config Def = y l_wei_oasis_mct = .TRUE. CALL getin ('l_wei_oasis_mct', l_wei_oasis_mct) WRITE (UNIT=nout, FMT=*) 'l_wei_oasis_mct = ', l_wei_oasis_mct !Config Key = c_read_wei !Config Desc = determined in whihc format weights are read !Config Help = !Config Def = oasis_3 CALL getin ('c_read_wei', c_read_wei) WRITE (UNIT=nout, FMT=*) 'c_read_wei = ', TRIM(c_read_wei) !Config Key = c_FlioMode !Config Desc = c_FlioMode = '32', '64', 'REPLACE', 'REP', 'REP64', 'HDF', 'REPHDF' !Config Help = !Config Def = n c_FlioMode = 'REPLACE' CALL getin ('c_FlioMode', c_FlioMode) WRITE (UNIT=nout, FMT=*) 'c_FlioMode = ', c_FlioMode !! !! ======================================= !! !! Computed quantities !! jpon = jpoi * jpoj ! Global (1D) dimensions for ocean jpan = jpai * jpaj ! Global (1D) dimensions for ocean jpanu = jpai * jpaj jpanv = jpai * jpaj !! WRITE (UNIT=nout, FMT=*) 'jpon = ', jpon WRITE (UNIT=nout, FMT=*) 'jpan = ', jpan WRITE (UNIT=nout, FMT=*) 'jpanu = ', jpanu WRITE (UNIT=nout, FMT=*) 'jpanv = ', jpanv !! !Config Key = locerev !Config Desc = Strategie de nommage. Si TRUE: opat.lon, sinon topa.lon !Config Def = n SELECT CASE (TRIM(cotyp)) CASE ('orca4') WRITE (unit=nout,fmt=*) 'Case ORCA4 for locerev' locerev = .TRUE. ! Si .TRUE. nom de champs type opat.lon, sinon topa.lon CASE ('orca2') WRITE (unit=nout,fmt=*) 'Case ORCA2 for locerev' locerev = .TRUE. CASE ('orca2.1') WRITE (unit=nout,fmt=*) 'Case ORCA2 for locerev' locerev = .TRUE. CASE Default WRITE (unit=nout,fmt=*) 'Default case for locerev ' locerev = .FALSE. END SELECT CALL getin ('locerev', locerev) WRITE (UNIT=nout, FMT=*) 'locerev = ', locerev !! !Config Key = lriv !Config Desc = Traitement du runoff des rivières avec les embouchures exactes !Config Def = n lriv = .FALSE. CALL getin ('lriv', lriv) WRITE (UNIT=nout, FMT=*) 'lriv = ', lriv !Config Key = lcoast !Config Desc = Traitement specifique des points cotiers !Config Def = y lcoast = .TRUE. CALL getin ('lcoast', lcoast) WRITE (UNIT=nout, FMT=*) 'lcoast = ', lcoast !Config Key = lint_atm !Config Desc = Calcul pour run-off intégré sur la maille atm !Config Def = y lint_atm = .TRUE. CALL getin ('lint_atm', lint_atm) WRITE (UNIT=nout, FMT=*) 'lint_atm = ', lint_atm !Config Key = lint_oce !Config Desc = Calcul pour run-off intégré sur la maille oce !Config Def = n CALL getin ('lint_oce', lint_oce) lint_oce = .FALSE. WRITE (UNIT=nout, FMT=*) 'lint_oce = ', lint_oce !Config Key = l_etal_oce !Config Desc = ! On etale sur les point océans proches !Config Def = n l_etal_oce = .TRUE. CALL getin ('l_etal_oce', l_etal_oce) WRITE (UNIT=nout, FMT=*) 'l_etal_oce = ',l_etal_oce !Config Key = dist_etal_oce !Config Desc = ! On etale sur les point océans proches !Config Def = 400.0E0 l_etal_oce = .TRUE. CALL getin ('dist_etal_oce', dist_etal_oce) WRITE (UNIT=nout, FMT=*) 'dist_etal_oce = ', dist_etal_oce !Config Key = lnear !Config Desc = Extension de 1 point a l''interieur, vers le point ocean le plus proche' !Config Def = n lnear = .FALSE. CALL getin ('lnear', lnear) WRITE (UNIT=nout, FMT=*) 'lnear = ', lnear !Config Key = lnei !Config Desc = Extension de 1 point a l''interieur, vers le point atm voisin' !Config Def = n lnei = .FALSE. CALL getin ('lnei', lnei) WRITE (UNIT=nout, FMT=*) 'lnei = ', lnei !Config Key = ltotal !Config Desc = les point atmosphères mouilles les plus proches. !Config Def = n ltotal = .FALSE. ! Route tout les point atm vers l'oce le plus proche. CALL getin ('ltotal', ltotal) WRITE (UNIT=nout, FMT=*) 'ltotal = ', ltotal !Config Key = ltotal_dist !Config Desc = ! Route tout les point atm vers l'oce le plus proche, avec distance maxi !Config Def = n ltotal_dist = .FALSE. CALL getin ('ltotal_dist', ltotal_dist) WRITE (UNIT=nout, FMT=*) 'ltotal_dist = ', ltotal_dist !Config Key = ltotal_dist_2 !Config Desc = ! Route tout les point atm vers les oce le plus proche, avec distance maxi ! ! On etale sur les point océans cotes proches !Config Def = n ltotal_dist_2 = .TRUE. CALL getin ('ltotal_dist_2', ltotal_dist_2) WRITE (UNIT=nout, FMT=*) 'ltotal_dist_2 = ', ltotal_dist_2 !Config Key = ltotal_dist_3 !Config Desc = ! Route tout les point atm vers les oce le plus proche, avec distance maxi ! ! On etale sur les point océans proches, cotiers ou pas !Config Def = n ltotal_dist_3 = .TRUE. CALL getin ('ltotal_dist_3', ltotal_dist_3) WRITE (UNIT=nout, FMT=*) 'ltotal_dist_3 = ', ltotal_dist_3 !Config Key = dist_max !Config Desc = Distance maximale de recherche des voisins océans cotiers !Config Def = 400.0E3 dist_max = 400.0E3_rl CALL getin ('dist_max_voisin', dist_max) WRITE (UNIT=nout, FMT=*) 'dist_max = ', dist_max !Config Key = dist_max_oce !Config Desc = Distance maximale de recherche des voisins océans !Config Def = 400.0E3 dist_max_oce = 400.0E3_rl CALL getin ('dist_max_oce', dist_max_oce) WRITE (UNIT=nout, FMT=*) 'dist_max_oce = ', dist_max_oce !Config Key = dist_max_atm !Config Desc = Distance maximale de recherche des voisins atmosphere !Config Def = 400.0E3 dist_max_atm = 400.0E3_rl CALL getin ('dist_max_atm', dist_max_atm) WRITE (UNIT=nout, FMT=*) 'dist_max_atm = ', dist_max_atm !Config Key = dist_max_large !Config Desc = Distance maximale de recherche des larges océans, vers le large !Config Def = 400.0E3 dist_max_large = 400.0E3_rl CALL getin ('dist_max_large', dist_max_large) WRITE (UNIT=nout, FMT=*) 'dist_max_large = ', dist_max_large l_large = .TRUE. CALL getin ( 'l_large', l_large) !! !Config Key = lessai !Config Desc = Essai de completion du run-off !Config Def = n lessai = .FALSE. CALL getin ('lessai', lessai) WRITE (UNIT=nout, FMT=*) 'lessai = ', lessai !Config Key = jp_calv !Config Desc = nombre de bandes pour le calving !Config Def = 3 jp_calv = 3 CALL getin ('jp_calv', jp_calv) WRITE (nout,*) 'Nombre de bandes : ', jp_calv ALLOCATE (ylimits (1:jp_calv+1), STAT=ierr) ; CALL chk_allo (ierr, 'ylimits') !Config Key = ylimits !Config Desc = nombre de bandes pour le calving CALL getin ('ylimits', ylimits) WRITE (nout,*) 'Limites des bandes : ', ylimits !Config Key = l_calving_nomed !Config Desc = Calving does not go to mediterranean seas (includes Red Sea, Persian Gulf) !Config Def = n l_calving_nomed = .FALSE. CALL getin ('l_calving_nomed', l_calving_nomed) WRITE (UNIT=nout, FMT=*) 'l_calving_nomed = ', l_calving_nomed !Config Key = l_calving_noatl !Config Desc = Calving does not go to Atlantic !Config Def = n l_calving_noatl = .FALSE. CALL getin ('l_calving_noatl', l_calving_noatl) WRITE (UNIT=nout, FMT=*) 'l_calving_noatl = ', l_calving_noatl !Config Key = l_calving_nopac !Config Desc = Calving does not go to Pacific !Config Def = n l_calving_nopac = .FALSE. CALL getin ('l_calving_nopac', l_calving_nopac) WRITE (UNIT=nout, FMT=*) 'l_calving_nopac = ', l_calving_nopac !Config Key = cotes_omsk !Config Desc = what ocean mask is written in Mosaic MCT file for runoff !Config Def = noperio cotes_omsk='noperio' CALL getin ('cotes_omsk', cotes_omsk) WRITE (UNIT=nout, FMT=*) 'cotes_omsk = ', TRIM(cotes_omsk) !Config Key = cotes_amsk !Config Desc = what atm mask is written in Mosaic MCT file for runoff !Config Def = full cotes_amsk='full' CALL getin ('cotes_amsk', cotes_amsk) WRITE (UNIT=nout, FMT=*) 'cotes_amsk = ', TRIM(cotes_amsk) c_basins = 'eORCA1.2.nc' CALL getin ( 'c_basins', c_basins) WRITE (UNIT=nout, FMT=*) 'c_basins = ', c_basins cl_atl = 'mask_atl' CALL getin ('cl_atl', cl_atl ) WRITE (UNIT=nout, FMT=*) 'cl_atl = ', cl_atl cl_pac = 'mask_pac' CALL getin ('cl_pac', cl_pac ) WRITE (UNIT=nout, FMT=*) 'cl_pac = ', cl_pac cl_nomed = 'mask_nomed' CALL getin ('cl_nomed', cl_nomed ) WRITE (UNIT=nout, FMT=*) 'cl_nomed = ',cl_nomed cl_noclo = 'mask_noclose' CALL getin ('cl_noclo', cl_noclo ) WRITE (UNIT=nout, FMT=*) 'cl_noclo = ', cl_noclo CALL getin_dump !! ( 'used' // TRIM(c_suffix)) !! END SUBROUTINE inipar END MODULE mod_inipar