Ignore:
Timestamp:
07/16/14 18:05:01 (10 years ago)
Author:
milmd
Message:

Last LMDZ version (1315) with OpenMP directives and other stuff

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/inifis.F

    r222 r227  
    1010      use comsoil_h, only: ini_comsoil_h 
    1111      use control_mod, only: ecritphy 
     12      use planete_mod, only: nres 
    1213      use planetwide_mod, only: planetwide_sumval 
    1314 
     
    4950      use datafile_mod, only: datadir 
    5051! to use  'getin' 
    51       USE ioipsl_getincom  
     52!      USE ioipsl_getincom  
     53      USE ioipsl_getincom_p 
    5254      IMPLICIT NONE 
    53 #include "dimensions.h" 
    54 #include "dimphys.h" 
    55 #include "planete.h" 
     55!#include "dimensions.h" 
     56!#include "dimphys.h" 
     57!#include "planete.h" 
    5658#include "comcstfi.h" 
    5759#include "callkeys.h" 
     
    7880      real psurf,pN2 ! added by RW for Gliese 581d N2+CO2 
    7981 
     82!$OMP MASTER 
    8083      rad=prad 
    8184      daysec=pdaysec 
     
    8891      avocado = 6.02214179e23   ! added by RW 
    8992 
    90 ! -------------------------------------------------------- 
    91 !     The usual Tests 
    92 !     -------------- 
    93       IF (nlayer.NE.nlayermx) THEN 
    94          PRINT*,'STOP in inifis' 
    95          PRINT*,'Probleme de dimensions :' 
    96          PRINT*,'nlayer     = ',nlayer 
    97          PRINT*,'nlayermx   = ',nlayermx 
    98          STOP 
    99       ENDIF 
     93!$OMP END MASTER 
     94!$OMP BARRIER 
    10095 
    10196      ! read in 'ecritphy' (frequency of calls to physics, in dynamical steps) 
    10297      ! (also done in dyn3d/defrun_new but not in LMDZ.COMMON) 
    103       call getin("ecritphy",ecritphy) 
     98      call getin_p("ecritphy",ecritphy) 
    10499 
    105100! -------------------------------------------------------------- 
     
    107102! -------------------------------------------------------------- 
    108103      
     104!$OMP MASTER      
    109105      ! check that 'callphys.def' file is around 
    110106      OPEN(99,file='callphys.def',status='old',form='formatted' 
    111107     &     ,iostat=ierr) 
    112108      CLOSE(99) 
     109      IF(ierr.EQ.0) iscallphys=.true. !iscallphys initialised as false in callkeys.h 
     110!$OMP END MASTER 
     111!$OMP BARRIER 
    113112       
    114       IF(ierr.EQ.0) THEN 
     113!!!      IF(ierr.EQ.0) THEN 
     114      IF(iscallphys) THEN 
    115115         PRINT* 
    116116         PRINT* 
     
    121121         write(*,*) "Directory where external input files are:" 
    122122         ! default 'datadir' is set in "datadir_mod" 
    123          call getin("datadir",datadir) ! default path 
     123         call getin_p("datadir",datadir) ! default path 
    124124         write(*,*) " datadir = ",trim(datadir) 
    125125 
    126126         write(*,*) "Run with or without tracer transport ?" 
    127127         tracer=.false. ! default value 
    128          call getin("tracer",tracer) 
     128         call getin_p("tracer",tracer) 
    129129         write(*,*) " tracer = ",tracer 
    130130 
     
    132132     &      " due to tracer evaporation/condensation?" 
    133133         mass_redistrib=.false. ! default value 
    134          call getin("mass_redistrib",mass_redistrib) 
     134         call getin_p("mass_redistrib",mass_redistrib) 
    135135         write(*,*) " mass_redistrib = ",mass_redistrib 
    136136 
     
    138138         write(*,*) "(if diurnal=false, diurnal averaged solar heating)" 
    139139         diurnal=.true. ! default value 
    140          call getin("diurnal",diurnal) 
     140         call getin_p("diurnal",diurnal) 
    141141         write(*,*) " diurnal = ",diurnal 
    142142 
     
    145145     &   "set in 'start'" 
    146146         season=.true. ! default value 
    147          call getin("season",season) 
     147         call getin_p("season",season) 
    148148         write(*,*) " season = ",season 
    149149 
    150150         write(*,*) "Tidally resonant rotation ?" 
    151151         tlocked=.false. ! default value 
    152          call getin("tlocked",tlocked) 
     152         call getin_p("tlocked",tlocked) 
    153153         write(*,*) "tlocked = ",tlocked 
    154154 
    155155         write(*,*) "Saturn ring shadowing ?" 
    156156         rings_shadow = .false. 
    157          call getin("rings_shadow", rings_shadow) 
     157         call getin_p("rings_shadow", rings_shadow) 
    158158         write(*,*) "rings_shadow = ", rings_shadow 
    159159          
    160160         write(*,*) "Compute latitude-dependent gravity field?" 
    161161         oblate = .false. 
    162          call getin("oblate", oblate) 
     162         call getin_p("oblate", oblate) 
    163163         write(*,*) "oblate = ", oblate 
    164164 
    165165         write(*,*) "Flattening of the planet (a-b)/a " 
    166166         flatten = 0.0 
    167          call getin("flatten", flatten) 
     167         call getin_p("flatten", flatten) 
    168168         write(*,*) "flatten = ", flatten 
    169169          
     
    171171         write(*,*) "Needed if oblate=.true.: J2" 
    172172         J2 = 0.0 
    173          call getin("J2", J2) 
     173         call getin_p("J2", J2) 
    174174         write(*,*) "J2 = ", J2 
    175175          
    176176         write(*,*) "Needed if oblate=.true.: Planet mass (*1e24 kg)" 
    177177         MassPlanet = 0.0 
    178          call getin("MassPlanet", MassPlanet) 
     178         call getin_p("MassPlanet", MassPlanet) 
    179179         write(*,*) "MassPlanet = ", MassPlanet          
    180180 
    181181         write(*,*) "Needed if oblate=.true.: Planet mean radius (m)" 
    182182         Rmean = 0.0 
    183          call getin("Rmean", Rmean) 
     183         call getin_p("Rmean", Rmean) 
    184184         write(*,*) "Rmean = ", Rmean 
    185185          
     
    193193         write(*,*) "Tidal resonance ratio ?" 
    194194         nres=0          ! default value 
    195          call getin("nres",nres) 
     195         call getin_p("nres",nres) 
    196196         write(*,*) "nres = ",nres 
    197197 
    198198         write(*,*) "Write some extra output to the screen ?" 
    199199         lwrite=.false. ! default value 
    200          call getin("lwrite",lwrite) 
     200         call getin_p("lwrite",lwrite) 
    201201         write(*,*) " lwrite = ",lwrite 
    202202 
    203203         write(*,*) "Save statistics in file stats.nc ?" 
    204204         callstats=.true. ! default value 
    205          call getin("callstats",callstats) 
     205         call getin_p("callstats",callstats) 
    206206         write(*,*) " callstats = ",callstats 
    207207 
    208208         write(*,*) "Test energy conservation of model physics ?" 
    209209         enertest=.false. ! default value 
    210          call getin("enertest",enertest) 
     210         call getin_p("enertest",enertest) 
    211211         write(*,*) " enertest = ",enertest 
    212212 
    213213         write(*,*) "Check to see if cpp values used match gases.def ?" 
    214214         check_cpp_match=.true. ! default value 
    215          call getin("check_cpp_match",check_cpp_match) 
     215         call getin_p("check_cpp_match",check_cpp_match) 
    216216         write(*,*) " check_cpp_match = ",check_cpp_match 
    217217 
    218218         write(*,*) "call radiative transfer ?" 
    219219         callrad=.true. ! default value 
    220          call getin("callrad",callrad) 
     220         call getin_p("callrad",callrad) 
    221221         write(*,*) " callrad = ",callrad 
    222222 
    223223         write(*,*) "call correlated-k radiative transfer ?" 
    224224         corrk=.true. ! default value 
    225          call getin("corrk",corrk) 
     225         call getin_p("corrk",corrk) 
    226226         write(*,*) " corrk = ",corrk 
    227227 
    228228         write(*,*) "prohibit calculations outside corrk T grid?" 
    229229         strictboundcorrk=.true. ! default value 
    230          call getin("strictboundcorrk",strictboundcorrk) 
     230         call getin_p("strictboundcorrk",strictboundcorrk) 
    231231         write(*,*) "strictboundcorrk = ",strictboundcorrk 
    232232 
     
    234234     &              "(matters only if callrad=T)" 
    235235         callgasvis=.false. ! default value 
    236          call getin("callgasvis",callgasvis) 
     236         call getin_p("callgasvis",callgasvis) 
    237237         write(*,*) " callgasvis = ",callgasvis 
    238238         
     
    240240     &              "(matters only if callrad=T)" 
    241241         continuum=.true. ! default value 
    242          call getin("continuum",continuum) 
     242         call getin_p("continuum",continuum) 
    243243         write(*,*) " continuum = ",continuum 
    244244 
    245245         write(*,*) "use analytic function for H2O continuum ?" 
    246246         H2Ocont_simple=.false. ! default value 
    247          call getin("H2Ocont_simple",H2Ocont_simple) 
     247         call getin_p("H2Ocont_simple",H2Ocont_simple) 
    248248         write(*,*) " H2Ocont_simple = ",H2Ocont_simple 
    249249  
    250250         write(*,*) "call turbulent vertical diffusion ?" 
    251251         calldifv=.true. ! default value 
    252          call getin("calldifv",calldifv) 
     252         call getin_p("calldifv",calldifv) 
    253253         write(*,*) " calldifv = ",calldifv 
    254254 
    255255         write(*,*) "use turbdiff instead of vdifc ?" 
    256256         UseTurbDiff=.true. ! default value 
    257          call getin("UseTurbDiff",UseTurbDiff) 
     257         call getin_p("UseTurbDiff",UseTurbDiff) 
    258258         write(*,*) " UseTurbDiff = ",UseTurbDiff 
    259259 
    260260         write(*,*) "call convective adjustment ?" 
    261261         calladj=.true. ! default value 
    262          call getin("calladj",calladj) 
     262         call getin_p("calladj",calladj) 
    263263         write(*,*) " calladj = ",calladj 
    264264 
    265265         write(*,*) "call CO2 condensation ?" 
    266266         co2cond=.false. ! default value 
    267          call getin("co2cond",co2cond) 
     267         call getin_p("co2cond",co2cond) 
    268268         write(*,*) " co2cond = ",co2cond 
    269269! Test of incompatibility 
     
    275275         write(*,*) "CO2 supersaturation level ?" 
    276276         co2supsat=1.0 ! default value 
    277          call getin("co2supsat",co2supsat) 
     277         call getin_p("co2supsat",co2supsat) 
    278278         write(*,*) " co2supsat = ",co2supsat 
    279279 
    280280         write(*,*) "Radiative timescale for Newtonian cooling ?" 
    281281         tau_relax=30. ! default value 
    282          call getin("tau_relax",tau_relax) 
     282         call getin_p("tau_relax",tau_relax) 
    283283         write(*,*) " tau_relax = ",tau_relax 
    284284         tau_relax=tau_relax*24*3600 ! convert Earth days --> seconds 
     
    286286         write(*,*)"call thermal conduction in the soil ?" 
    287287         callsoil=.true. ! default value 
    288          call getin("callsoil",callsoil) 
     288         call getin_p("callsoil",callsoil) 
    289289         write(*,*) " callsoil = ",callsoil 
    290290          
     
    292292     &             " physical timestep" 
    293293         iradia=1 ! default value 
    294          call getin("iradia",iradia) 
     294         call getin_p("iradia",iradia) 
    295295         write(*,*)" iradia = ",iradia 
    296296        
    297297         write(*,*)"Rayleigh scattering ?" 
    298298         rayleigh=.false. 
    299          call getin("rayleigh",rayleigh) 
     299         call getin_p("rayleigh",rayleigh) 
    300300         write(*,*)" rayleigh = ",rayleigh 
    301301 
    302302         write(*,*) "Use blackbody for stellar spectrum ?" 
    303303         stelbbody=.false. ! default value 
    304          call getin("stelbbody",stelbbody) 
     304         call getin_p("stelbbody",stelbbody) 
    305305         write(*,*) " stelbbody = ",stelbbody 
    306306 
    307307         write(*,*) "Stellar blackbody temperature ?" 
    308308         stelTbb=5800.0 ! default value 
    309          call getin("stelTbb",stelTbb) 
     309         call getin_p("stelTbb",stelTbb) 
    310310         write(*,*) " stelTbb = ",stelTbb 
    311311 
    312312         write(*,*)"Output mean OLR in 1D?" 
    313313         meanOLR=.false. 
    314          call getin("meanOLR",meanOLR) 
     314         call getin_p("meanOLR",meanOLR) 
    315315         write(*,*)" meanOLR = ",meanOLR 
    316316 
    317317         write(*,*)"Output spectral OLR in 3D?" 
    318318         specOLR=.false. 
    319          call getin("specOLR",specOLR) 
     319         call getin_p("specOLR",specOLR) 
    320320         write(*,*)" specOLR = ",specOLR 
    321321 
    322322         write(*,*)"Operate in kastprof mode?" 
    323323         kastprof=.false. 
    324          call getin("kastprof",kastprof) 
     324         call getin_p("kastprof",kastprof) 
    325325         write(*,*)" kastprof = ",kastprof 
    326326 
    327327         write(*,*)"Uniform absorption in radiative transfer?" 
    328328         graybody=.false. 
    329          call getin("graybody",graybody) 
     329         call getin_p("graybody",graybody) 
    330330         write(*,*)" graybody = ",graybody 
    331331 
     
    333333         write(*,*) "Use slab-ocean ?" 
    334334         ok_slab_ocean=.false.         ! default value 
    335          call getin("ok_slab_ocean",ok_slab_ocean) 
     335         call getin_p("ok_slab_ocean",ok_slab_ocean) 
    336336         write(*,*) "ok_slab_ocean = ",ok_slab_ocean 
    337337 
    338338         write(*,*) "Use slab-sea-ice ?" 
    339339         ok_slab_sic=.true.         ! default value 
    340          call getin("ok_slab_sic",ok_slab_sic) 
     340         call getin_p("ok_slab_sic",ok_slab_sic) 
    341341         write(*,*) "ok_slab_sic = ",ok_slab_sic 
    342342 
    343343         write(*,*) "Use heat transport for the ocean ?" 
    344344         ok_slab_heat_transp=.true.   ! default value 
    345          call getin("ok_slab_heat_transp",ok_slab_heat_transp) 
     345         call getin_p("ok_slab_heat_transp",ok_slab_heat_transp) 
    346346         write(*,*) "ok_slab_heat_transp = ",ok_slab_heat_transp 
    347347 
     
    357357         write(*,*)"Stratospheric temperature for kastprof mode?" 
    358358         Tstrat=167.0 
    359          call getin("Tstrat",Tstrat) 
     359         call getin_p("Tstrat",Tstrat) 
    360360         write(*,*)" Tstrat = ",Tstrat 
    361361 
    362362         write(*,*)"Remove lower boundary?" 
    363363         nosurf=.false. 
    364          call getin("nosurf",nosurf) 
     364         call getin_p("nosurf",nosurf) 
    365365         write(*,*)" nosurf = ",nosurf 
    366366 
     
    375375     .             "... matters only if callsoil=F" 
    376376         intheat=0. 
    377          call getin("intheat",intheat) 
     377         call getin_p("intheat",intheat) 
    378378         write(*,*)" intheat = ",intheat 
    379379 
    380380         write(*,*)"Use Newtonian cooling for radiative transfer?" 
    381381         newtonian=.false. 
    382          call getin("newtonian",newtonian) 
     382         call getin_p("newtonian",newtonian) 
    383383         write(*,*)" newtonian = ",newtonian 
    384384 
     
    399399         write(*,*)"Test physics timescale in 1D?" 
    400400         testradtimes=.false. 
    401          call getin("testradtimes",testradtimes) 
     401         call getin_p("testradtimes",testradtimes) 
    402402         write(*,*)" testradtimes = ",testradtimes 
    403403 
     
    411411         write(*,*)"Default planetary temperature?" 
    412412         tplanet=215.0 
    413          call getin("tplanet",tplanet) 
     413         call getin_p("tplanet",tplanet) 
    414414         write(*,*)" tplanet = ",tplanet 
    415415 
    416416         write(*,*)"Which star?" 
    417417         startype=1 ! default value = Sol 
    418          call getin("startype",startype) 
     418         call getin_p("startype",startype) 
    419419         write(*,*)" startype = ",startype 
    420420 
    421421         write(*,*)"Value of stellar flux at 1 AU?" 
    422422         Fat1AU=1356.0 ! default value = Sol today 
    423          call getin("Fat1AU",Fat1AU) 
     423         call getin_p("Fat1AU",Fat1AU) 
    424424         write(*,*)" Fat1AU = ",Fat1AU 
    425425 
     
    429429         write(*,*)"Varying H2O cloud fraction?" 
    430430         CLFvarying=.false.     ! default value 
    431          call getin("CLFvarying",CLFvarying) 
     431         call getin_p("CLFvarying",CLFvarying) 
    432432         write(*,*)" CLFvarying = ",CLFvarying 
    433433 
    434434         write(*,*)"Value of fixed H2O cloud fraction?" 
    435435         CLFfixval=1.0                ! default value 
    436          call getin("CLFfixval",CLFfixval) 
     436         call getin_p("CLFfixval",CLFfixval) 
    437437         write(*,*)" CLFfixval = ",CLFfixval 
    438438 
    439439         write(*,*)"fixed radii for Cloud particles?" 
    440440         radfixed=.false. ! default value 
    441          call getin("radfixed",radfixed) 
     441         call getin_p("radfixed",radfixed) 
    442442         write(*,*)" radfixed = ",radfixed 
    443443 
     
    448448         write(*,*)"Number mixing ratio of CO2 ice particles:" 
    449449         Nmix_co2=1.e6 ! default value 
    450          call getin("Nmix_co2",Nmix_co2) 
     450         call getin_p("Nmix_co2",Nmix_co2) 
    451451         write(*,*)" Nmix_co2 = ",Nmix_co2 
    452452 
    453453!         write(*,*)"Number of radiatively active aerosols:" 
    454454!         naerkind=0. ! default value 
    455 !         call getin("naerkind",naerkind) 
     455!         call getin_p("naerkind",naerkind) 
    456456!         write(*,*)" naerkind = ",naerkind 
    457457 
    458458         write(*,*)"Opacity of dust (if used):" 
    459459         dusttau=0. ! default value 
    460          call getin("dusttau",dusttau) 
     460         call getin_p("dusttau",dusttau) 
    461461         write(*,*)" dusttau = ",dusttau 
    462462 
    463463         write(*,*)"Radiatively active CO2 aerosols?" 
    464464         aeroco2=.false.     ! default value 
    465          call getin("aeroco2",aeroco2) 
     465         call getin_p("aeroco2",aeroco2) 
    466466         write(*,*)" aeroco2 = ",aeroco2 
    467467 
    468468         write(*,*)"Fixed CO2 aerosol distribution?" 
    469469         aerofixco2=.false.     ! default value 
    470          call getin("aerofixco2",aerofixco2) 
     470         call getin_p("aerofixco2",aerofixco2) 
    471471         write(*,*)" aerofixco2 = ",aerofixco2 
    472472 
    473473         write(*,*)"Radiatively active water ice?" 
    474474         aeroh2o=.false.     ! default value 
    475          call getin("aeroh2o",aeroh2o) 
     475         call getin_p("aeroh2o",aeroh2o) 
    476476         write(*,*)" aeroh2o = ",aeroh2o 
    477477 
    478478         write(*,*)"Fixed H2O aerosol distribution?" 
    479479         aerofixh2o=.false.     ! default value 
    480          call getin("aerofixh2o",aerofixh2o) 
     480         call getin_p("aerofixh2o",aerofixh2o) 
    481481         write(*,*)" aerofixh2o = ",aerofixh2o 
    482482 
    483483         write(*,*)"Radiatively active sulfuric acid aersols?" 
    484484         aeroh2so4=.false.     ! default value 
    485          call getin("aeroh2so4",aeroh2so4) 
     485         call getin_p("aeroh2so4",aeroh2so4) 
    486486         write(*,*)" aeroh2so4 = ",aeroh2so4 
    487487          
     
    490490         write(*,*)"Radiatively active two-layer aersols?" 
    491491         aeroback2lay=.false.     ! default value 
    492          call getin("aeroback2lay",aeroback2lay) 
     492         call getin_p("aeroback2lay",aeroback2lay) 
    493493         write(*,*)" aeroback2lay = ",aeroback2lay 
    494494 
     
    496496     &              "in the tropospheric layer (visible)" 
    497497         obs_tau_col_tropo=8.D0 
    498          call getin("obs_tau_col_tropo",obs_tau_col_tropo) 
     498         call getin_p("obs_tau_col_tropo",obs_tau_col_tropo) 
    499499         write(*,*)" obs_tau_col_tropo = ",obs_tau_col_tropo 
    500500 
     
    502502     &              "in the stratospheric layer (visible)" 
    503503         obs_tau_col_strato=0.08D0 
    504          call getin("obs_tau_col_strato",obs_tau_col_strato) 
     504         call getin_p("obs_tau_col_strato",obs_tau_col_strato) 
    505505         write(*,*)" obs_tau_col_strato = ",obs_tau_col_strato 
    506506 
    507507         write(*,*)"TWOLAY AEROSOL: pres_bottom_tropo? in pa" 
    508508         pres_bottom_tropo=66000.0 
    509          call getin("pres_bottom_tropo",pres_bottom_tropo) 
     509         call getin_p("pres_bottom_tropo",pres_bottom_tropo) 
    510510         write(*,*)" pres_bottom_tropo = ",pres_bottom_tropo 
    511511 
    512512         write(*,*)"TWOLAY AEROSOL: pres_top_tropo? in pa" 
    513513         pres_top_tropo=18000.0 
    514          call getin("pres_top_tropo",pres_top_tropo) 
     514         call getin_p("pres_top_tropo",pres_top_tropo) 
    515515         write(*,*)" pres_top_tropo = ",pres_top_tropo 
    516516 
    517517         write(*,*)"TWOLAY AEROSOL: pres_bottom_strato? in pa" 
    518518         pres_bottom_strato=2000.0 
    519          call getin("pres_bottom_strato",pres_bottom_strato) 
     519         call getin_p("pres_bottom_strato",pres_bottom_strato) 
    520520         write(*,*)" pres_bottom_strato = ",pres_bottom_strato 
    521521 
    522522         write(*,*)"TWOLAY AEROSOL: pres_top_strato? in pa" 
    523523         pres_top_strato=100.0 
    524          call getin("pres_top_strato",pres_top_strato) 
     524         call getin_p("pres_top_strato",pres_top_strato) 
    525525         write(*,*)" pres_top_strato = ",pres_top_strato 
    526526 
     
    528528     &              "tropospheric layer, in meters" 
    529529         size_tropo=2.e-6 
    530          call getin("size_tropo",size_tropo) 
     530         call getin_p("size_tropo",size_tropo) 
    531531         write(*,*)" size_tropo = ",size_tropo 
    532532 
     
    534534     &              "stratospheric layer, in meters" 
    535535         size_strato=1.e-7 
    536          call getin("size_strato",size_strato) 
     536         call getin_p("size_strato",size_strato) 
    537537         write(*,*)" size_strato = ",size_strato 
    538538 
     
    541541         write(*,*)"Cloud pressure level (with kastprof only):" 
    542542         cloudlvl=0. ! default value 
    543          call getin("cloudlvl",cloudlvl) 
     543         call getin_p("cloudlvl",cloudlvl) 
    544544         write(*,*)" cloudlvl = ",cloudlvl 
    545545 
     
    547547         Tstrat=167.0 
    548548         varactive=.false. 
    549          call getin("varactive",varactive) 
     549         call getin_p("varactive",varactive) 
    550550         write(*,*)" varactive = ",varactive 
    551551 
    552552         write(*,*)"Is the variable gas species distribution set?" 
    553553         varfixed=.false. 
    554          call getin("varfixed",varfixed) 
     554         call getin_p("varfixed",varfixed) 
    555555         write(*,*)" varfixed = ",varfixed 
    556556 
    557557         write(*,*)"What is the saturation % of the variable species?" 
    558558         satval=0.8 
    559          call getin("satval",satval) 
     559         call getin_p("satval",satval) 
    560560         write(*,*)" satval = ",satval 
    561561 
     
    570570         write(*,*) "Gravitationnal sedimentation ?" 
    571571         sedimentation=.false. ! default value 
    572          call getin("sedimentation",sedimentation) 
     572         call getin_p("sedimentation",sedimentation) 
    573573         write(*,*) " sedimentation = ",sedimentation 
    574574 
    575575         write(*,*) "Compute water cycle ?" 
    576576         water=.false. ! default value 
    577          call getin("water",water) 
     577         call getin_p("water",water) 
    578578         write(*,*) " water = ",water 
    579579          
     
    587587         write(*,*) "Include water condensation ?" 
    588588         watercond=.false. ! default value 
    589          call getin("watercond",watercond) 
     589         call getin_p("watercond",watercond) 
    590590         write(*,*) " watercond = ",watercond 
    591591 
     
    599599         write(*,*) "Include water precipitation ?" 
    600600         waterrain=.false. ! default value 
    601          call getin("waterrain",waterrain) 
     601         call getin_p("waterrain",waterrain) 
    602602         write(*,*) " waterrain = ",waterrain 
    603603 
    604604         write(*,*) "Include surface hydrology ?" 
    605605         hydrology=.false. ! default value 
    606          call getin("hydrology",hydrology) 
     606         call getin_p("hydrology",hydrology) 
    607607         write(*,*) " hydrology = ",hydrology 
    608608 
    609609         write(*,*) "Evolve surface water sources ?" 
    610610         sourceevol=.false. ! default value 
    611          call getin("sourceevol",sourceevol) 
     611         call getin_p("sourceevol",sourceevol) 
    612612         write(*,*) " sourceevol = ",sourceevol 
    613613 
    614614         write(*,*) "Ice evolution timestep ?" 
    615615         icetstep=100.0 ! default value 
    616          call getin("icetstep",icetstep) 
     616         call getin_p("icetstep",icetstep) 
    617617         write(*,*) " icetstep = ",icetstep 
    618618 
    619619         write(*,*) "Snow albedo ?" 
    620620         albedosnow=0.5         ! default value 
    621          call getin("albedosnow",albedosnow) 
     621         call getin_p("albedosnow",albedosnow) 
    622622         write(*,*) " albedosnow = ",albedosnow 
    623623 
    624624         write(*,*) "Maximum ice thickness ?" 
    625625         maxicethick=2.0         ! default value 
    626          call getin("maxicethick",maxicethick) 
     626         call getin_p("maxicethick",maxicethick) 
    627627         write(*,*) " maxicethick = ",maxicethick 
    628628 
    629629         write(*,*) "Freezing point of seawater ?" 
    630630         Tsaldiff=-1.8          ! default value 
    631          call getin("Tsaldiff",Tsaldiff) 
     631         call getin_p("Tsaldiff",Tsaldiff) 
    632632         write(*,*) " Tsaldiff = ",Tsaldiff 
    633633 
    634634         write(*,*) "Does user want to force cpp and mugaz?" 
    635635         force_cpp=.false. ! default value 
    636          call getin("force_cpp",force_cpp) 
     636         call getin_p("force_cpp",force_cpp) 
    637637         write(*,*) " force_cpp = ",force_cpp 
    638638 
     
    640640           mugaz = -99999. 
    641641           PRINT *,'MEAN MOLECULAR MASS in g mol-1 ?' 
    642            call getin("mugaz",mugaz) 
     642           call getin_p("mugaz",mugaz) 
    643643           IF (mugaz.eq.-99999.) THEN 
    644644               PRINT *, "mugaz must be set if force_cpp = T" 
     
    649649           cpp = -99999. 
    650650           PRINT *,'SPECIFIC HEAT CAPACITY in J K-1 kg-1 ?' 
    651            call getin("cpp",cpp) 
     651           call getin_p("cpp",cpp) 
    652652           IF (cpp.eq.-99999.) THEN 
    653653               PRINT *, "cpp must be set if force_cpp = T" 
     
    711711      ENDDO 
    712712 
     713!$OMP MASTER 
    713714      pi=2.*asin(1.) ! NB: pi is a common in comcstfi.h 
     715!$OMP END MASTER 
     716!$OMP BARRIER 
    714717 
    715718      ! allocate "comsoil_h" arrays 
Note: See TracChangeset for help on using the changeset viewer.