Changeset 311


Ignore:
Timestamp:
2011-07-08T14:24:28+02:00 (13 years ago)
Author:
didier.solyga
Message:

Move and clean the rest of the externalized parameters from sechiba and stomate to src_parameters. Add two subroutines in constantes. Correct Olson type number 79 in vegcorr

Location:
branches/ORCHIDEE_EXT/ORCHIDEE
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_parameters/constantes.f90

    r257 r311  
    4545 
    4646  ! undef integer for integer arrays 
    47   INTEGER(i_std), PARAMETER :: undef_integer = 999999999 
    48  
     47  INTEGER(i_std), PARAMETER    :: undef_int = 999999999 
    4948  ! Specific value if no restart value 
    5049  REAL(r_std),SAVE :: val_exp = 999999. 
     
    8281!  DIMENSIONING AND INDICES PARAMETERS 
    8382!--------------------------------------- 
     83 
     84  !------------- 
     85  ! condveg 
     86  !------------- 
     87  ! index for visible albedo 
     88  INTEGER(i_std), PARAMETER         :: ivis = 1  
     89  ! index for near infrared albedo 
     90  INTEGER(i_std), PARAMETER         :: inir = 2  
    8491 
    8592  !---------------- 
     
    389396  REAL(r_std),SAVE      :: qsintcst = 0.1 
    390397  ! Total depth of soil reservoir (for hydrolc) 
    391   REAL(r_std),SAVE :: dpu_cste =  deux 
     398  REAL(r_std),SAVE :: dpu_cste =  2.0_r_std 
    392399  ! Total depth of soil reservoir (m) 
    393400  REAL(r_std),SAVE,DIMENSION(nstm) :: dpu =  (/ 2.0_r_std, 2.0_r_std, 2.0_r_std /) 
    394401 
    395   ! FLAGS 
    396  
    397   ! allow agricultural PFTs 
    398   LOGICAL,SAVE :: agriculture = .TRUE. !(read in slowproc) 
     402  ! 
     403  ! FLAGS ACTIVATING SUB-MODELS 
     404  ! 
     405  LOGICAL, SAVE  :: doirrigation = .FALSE. 
     406  LOGICAL, SAVE  :: dofloodplains = .FALSE. 
    399407  ! Do we treat PFT expansion across a grid point after introduction? 
    400408  ! default = .FALSE. 
    401   LOGICAL,SAVE :: treat_expansion = .FALSE. 
     409  LOGICAL,SAVE    :: treat_expansion = .FALSE. 
    402410  ! herbivores? 
    403   LOGICAL,SAVE :: ok_herbivores = .FALSE. 
     411  LOGICAL,SAVE    :: ok_herbivores = .FALSE. 
    404412  ! harvesting ? 
    405   LOGICAL,SAVE :: harvest_agri = .TRUE. 
     413  LOGICAL,SAVE    :: harvest_agri = .TRUE. 
    406414  ! constant moratlity 
    407   LOGICAL,SAVE :: lpj_gap_const_mort=.TRUE. 
    408  
     415  LOGICAL,SAVE    :: lpj_gap_const_mort=.TRUE. 
     416  ! flag that disable fire 
     417  LOGICAL, SAVE   :: disable_fire 
     418 
     419  ! 
     420  ! Configuration vegetation 
     421  ! 
     422  ! allow agricultural PFTs 
     423  LOGICAL,SAVE :: agriculture = .TRUE.  
     424  LOGICAL, SAVE  :: impveg = .FALSE. 
     425  LOGICAL, SAVE  :: impsoilt = .FALSE. 
     426  ! Land cover change flag 
     427  LOGICAL,SAVE   :: lcchange=.FALSE. 
     428  ! Lai Map 
     429  LOGICAL, SAVE   :: read_lai = .FALSE.   
     430  ! Old Lai Map interpolation  
     431  LOGICAL, SAVE   :: old_lai = .FALSE.  
     432  ! Old veget Map interpolation   
     433  LOGICAL, SAVE   :: old_veget = .FALSE.   
     434  ! Land Use  
     435  LOGICAL, SAVE   :: land_use = .FALSE.      
     436  ! To change LAND USE file in a run. 
     437  LOGICAL, SAVE   :: veget_reinit=.FALSE.   
     438 
     439  ! 
    409440  ! Parameters used by both hydrology models 
    410  
     441  ! 
    411442  ! Maximum period of snow aging 
    412443  REAL(r_std),SAVE :: max_snow_age = 50._r_std 
     
    451482  ! Critical value for computation of snow albedo [Kg/m^2] 
    452483  REAL(r_std),SAVE :: snowcri_alb=10. 
     484  ! In case we wish a fxed snow albedo 
     485  REAL(r_std), SAVE  :: fixed_snow_albedo = undef_sechiba 
     486  ! Switch to old (albedo bare depend on soil wetness) or new one (mean of soilalb)  
     487  LOGICAL, SAVE  :: alb_bare_model = .FALSE. 
     488  ! Choice on the surface parameters 
     489  LOGICAL, SAVE  :: impaze = .FALSE. 
     490  ! Chooses the method for the z0 average 
     491  LOGICAL, SAVE  :: z0cdrag_ave=.FALSE.   
     492  ! Roughness used to initialize the scheme 
     493  REAL(r_std), SAVE  :: z0_scal = 0.15_r_std 
     494  ! Height to displace the surface from the zero wind height. 
     495  REAL(r_std), SAVE  :: roughheight_scal = zero 
     496  ! Surface emissivity  used to initialize the scheme 
     497  REAL(r_std), SAVE   :: emis_scal = un     
    453498 
    454499  ! 2. Arrays 
     
    458503  ! albedo of ice, VIS+NIR 
    459504  REAL(r_std),DIMENSION(2),SAVE :: alb_ice = (/ .60, .20/) 
     505  ! albedo values need for initialisation 
     506  REAL(r_std),DIMENSION(2),SAVE  :: albedo_scal = (/ 0.25_r_std, 0.25_r_std /) 
    460507  !   The correspondance table for the soil color numbers and their albedo 
    461508  ! 
     
    540587  !SZ changed this according to SP from 0.03 to 0.08, 080806 
    541588  REAL(r_std),SAVE :: hcrit_litter=0.08_r_std 
    542  
    543  
     589  ! do horizontal diffusion? 
     590  LOGICAL, SAVE    :: ok_hdiff  = .FALSE. 
    544591 
    545592 
     
    613660  ! Minimal fraction of mesh a vegetation type can occupy 
    614661  REAL(r_std),SAVE :: min_vegfrac=0.001 
    615  ! Value for frac_nobio for tests in 0-dim simulations 
     662  ! Value for frac_nobio for tests in 0-dim simulations 
    616663  ! laisser ca tant qu'il n'y a que de la glace (pas de lacs) 
    617664  !DS : used in slowproc 
    618665  REAL(r_std),SAVE :: frac_nobio_fixed_test_1 = 0.0 
     666  ! first year for landuse 
     667  INTEGER(i_std) , SAVE  :: veget_year_orig = 0 
     668  ! DS which is the default value? I found also  :: veget_year_orig=282 
     669  ! only needed for an initial LAI if there is no restart file 
     670  REAL(r_std), SAVE :: stempdiag_bid = 280.  
    619671 
    620672  ! 2. Arrays 
     
    10951147 CONTAINS 
    10961148 
     1149   SUBROUTINE activate_sub_models(active_sechiba,active_routing, active_stomate) 
     1150 
     1151     IMPLICIT NONE 
     1152     ! first call 
     1153     LOGICAL, SAVE ::  first_call = .TRUE.    
     1154     ! input 
     1155     LOGICAL, INTENT(in) :: active_sechiba 
     1156     LOGICAL, INTENT(in) :: active_routing 
     1157     LOGICAL, INTENT(in) :: active_stomate     
     1158 
     1159     IF (first_call) THEN  
     1160 
     1161        IF(active_sechiba .AND. active_routing) THEN 
     1162            
     1163           !Config Key  = DO_IRRIGATION 
     1164           !Config Desc = Should we compute an irrigation flux  
     1165           !Config Def  = FALSE 
     1166           !Config Help = This parameters allows the user to ask the model 
     1167           !Config        to compute an irigation flux. This performed for the 
     1168           !Config        on very simple hypothesis. The idea is to have a good 
     1169           !Config        map of irrigated areas and a simple function which estimates 
     1170           !Config        the need to irrigate. 
     1171           CALL getin_p('DO_IRRIGATION', doirrigation) 
     1172           ! 
     1173           !Config Key  = DO_FLOODPLAINS 
     1174           !Config Desc = Should we include floodplains  
     1175           !Config Def  = FALSE 
     1176           !Config Help = This parameters allows the user to ask the model 
     1177           !Config        to take into account the flood plains and return  
     1178           !Config        the water into the soil moisture. It then can go  
     1179           !Config        back to the atmopshere. This tried to simulate  
     1180           !Config        internal deltas of rivers. 
     1181           CALL getin_p('DO_FLOODPLAINS', dofloodplains) 
     1182         
     1183        ENDIF 
     1184 
     1185            
     1186        IF(active_stomate) THEN 
     1187 
     1188           !Config  Key  = HERBIVORES 
     1189           !Config  Desc = herbivores allowed? 
     1190           !Config  Def  = n 
     1191           !Config  Help = With this variable, you can determine 
     1192           !Config         if herbivores are activated 
     1193           CALL getin_p('HERBIVORES', ok_herbivores) 
     1194           ! 
     1195           !Config  Key  = TREAT_EXPANSION 
     1196           !Config  Desc = treat expansion of PFTs across a grid cell? 
     1197           !Config  Def  = n 
     1198           !Config  Help = With this variable, you can determine 
     1199           !Config         whether we treat expansion of PFTs across a 
     1200           !Config         grid cell. 
     1201           CALL getin_p('TREAT_EXPANSION', treat_expansion) 
     1202           ! 
     1203           !Config Key  = LPJ_GAP_CONST_MORT 
     1204           !Config Desc = prescribe mortality if not using DGVM? 
     1205           !Config Def  = y 
     1206           !Config Help = set to TRUE if constant mortality is to be activated 
     1207           !              ignored if DGVM=true! 
     1208           CALL getin('LPJ_GAP_CONST_MORT', lpj_gap_const_mort) 
     1209           ! 
     1210           !Config  Key  = HARVEST_AGRI 
     1211           !Config  Desc = Harvert model for agricol PFTs. 
     1212           !Config  Def  = y 
     1213           !Config  Help = Compute harvest above ground biomass for agriculture. 
     1214           !Config         Change daily turnover. 
     1215           CALL getin_p('HARVEST_AGRI', harvest_agri) 
     1216           ! 
     1217           !Config  Key  = FIRE_DISABLE 
     1218           !Config  Desc = no fire allowed 
     1219           !Config  Def  = n 
     1220           !Config  Help = With this variable, you can allow or not 
     1221           !Config         the estimation of CO2 lost by fire 
     1222           CALL getin_p('FIRE_DISABLE', disable_fire) 
     1223 
     1224        ENDIF 
     1225 
     1226        ! 
     1227        ! Check consistency (see later) 
     1228        ! 
     1229!!$        IF(.NOT.(active_routing) .AND. (doirrigation .OR. dofloodplains)) THEN 
     1230!!$           CALL ipslerr (2,'activate_sub_models', & 
     1231!!$               &     'Problem :you tried to activate the irrigation and floodplains without activating the routing',& 
     1232!!$               &     'Are you sure ?', & 
     1233!!$               &     '(check your parameters).') 
     1234!!$        ENDIF 
     1235        
     1236!!$        IF(.NOT.(active_stomate) .AND. (ok_herbivores .OR. treat_expansion .OR. lpj_gap_const_mort & 
     1237!!$            & .OR. harvest_agri .OR. disable_fire)) THEN 
     1238!!$          CALL ipslerr (2,'activate_sub_models', & 
     1239!!$               &     'Problem : try to activate the following options : herbivory, treat_expansion, fire,',& 
     1240!!$               &     'harvest_agri and constant mortality without stomate activated.',& 
     1241!!$               &     '(check your parameters).') 
     1242!!$        ENDIF 
     1243             
     1244        first_call =.FALSE. 
     1245 
     1246     ENDIF 
     1247 
     1248   END SUBROUTINE activate_sub_models 
     1249! 
     1250!= 
     1251! 
     1252   SUBROUTINE veget_config 
     1253 
     1254     ! DS : this subroutine reads the flags previously in slowproc.f90 . As these parameters 
     1255     !      let the user to configure the vegetation, it is called veget_config. 
     1256       
     1257     IMPLICIT NONE 
     1258      
     1259        !Config  Key  = AGRICULTURE 
     1260        !Config  Desc = agriculture allowed? 
     1261        !Config  Def  = y 
     1262        !Config  Help = With this variable, you can determine 
     1263        !Config         whether agriculture is allowed 
     1264        ! 
     1265        CALL getin_p('AGRICULTURE', agriculture) 
     1266        ! 
     1267        !Config Key  = IMPOSE_VEG 
     1268        !Config Desc = Should the vegetation be prescribed 
     1269        !Config Def  = n 
     1270        !Config Help = This flag allows the user to impose a vegetation distribution 
     1271        !Config        and its characterisitcs. It is espacially interesting for 0D 
     1272        !Config        simulations. On the globe it does not make too much sense as 
     1273        !Config        it imposes the same vegetation everywhere 
     1274        ! 
     1275        CALL getin_p('IMPOSE_VEG', impveg) 
     1276        ! 
     1277        !Config Key  = IMPOSE_SOILT 
     1278        !Config Desc = Should the soil typ be prescribed 
     1279        !Config Def  = n 
     1280        !Config If   = IMPOSE_VEG 
     1281        !Config Help = This flag allows the user to impose a soil type distribution. 
     1282        !Config        It is espacially interesting for 0D 
     1283        !Config        simulations. On the globe it does not make too much sense as 
     1284        !Config        it imposes the same soil everywhere 
     1285        CALL getin_p('IMPOSE_SOILT', impsoilt)      
     1286        ! 
     1287        !Config  Key  = LAND_COVER_CHANGE 
     1288        !Config  Desc = treat land use modifications 
     1289        !Config  If   = LAND_USE 
     1290        !Config  Def  = y 
     1291        !Config  Help = With this variable, you can use a Land Use map 
     1292        !Config         to simulate anthropic modifications such as  
     1293        !Config         deforestation. 
     1294        CALL getin_p('LAND_COVER_CHANGE', lcchange) 
     1295        ! 
     1296        !Config Key  = LAI_MAP 
     1297        !Config Desc = Read the LAI map 
     1298        !Config Def  = n 
     1299        !Config Help = It is possible to read a 12 month LAI map which will 
     1300        !Config        then be interpolated to daily values as needed. 
     1301        CALL getin_p('LAI_MAP',read_lai) 
     1302        ! 
     1303        !Config Key  = SLOWPROC_LAI_OLD_INTERPOL 
     1304        !Config Desc = Flag to use old "interpolation" of LAI 
     1305        !Config If   = LAI_MAP 
     1306        !Config Def  = FALSE 
     1307        !Config Help = If you want to recover the old (ie orchidee_1_2 branch)  
     1308        !Config        "interpolation" of LAI map. 
     1309        CALL getin_p('SLOWPROC_LAI_OLD_INTERPOL',old_lai)       
     1310  
     1311        !Config Key  = SLOWPROC_VEGET_OLD_INTERPOL 
     1312        !Config Desc = Flag to use old "interpolation" of vegetation map. 
     1313        !Config If   = NOT IMPOSE_VEG and NOT LAND_USE 
     1314        !Config Def  = FALSE 
     1315        !Config Help = If you want to recover the old (ie orchidee_1_2 branch)  
     1316        !Config        "interpolation" of vegetation map. 
     1317        CALL getin_p('SLOWPROC_VEGET_OLD_INTERPOL',old_veget) 
     1318        ! 
     1319        !Config Key  = LAND_USE 
     1320        !Config Desc = Read a land_use vegetation map 
     1321        !Config Def  = n 
     1322        !Config Help = pft values are needed, max time axis is 293 
     1323        CALL getin_p('LAND_USE',land_use) 
     1324        ! 
     1325        !Config Key  = VEGET_REINIT 
     1326        !Config Desc = booleen to indicate that a new LAND USE file will be used. 
     1327        !Config If   = LAND_USE 
     1328        !Config Def  = n 
     1329        !Config Help = The parameter is used to bypass veget_year count  
     1330        !Config Help   and reinitialize it with VEGET_YEAR parameter. 
     1331        !Config Help   Then it is possible to change LAND USE file. 
     1332        CALL getin_p('VEGET_REINIT', veget_reinit) 
     1333 
     1334 
     1335        ! Check consistency 
     1336 
     1337        ! 1. You have to activate agriculture and land_use 
     1338        IF ( .NOT. agriculture .AND. land_use ) THEN  
     1339           CALL ipslerr (2,'veget_config', & 
     1340               &     'Problem with agriculture desactivated and Land Use activated.',& 
     1341               &     'Are you sure ?', & 
     1342               &     '(check your parameters).') 
     1343        ENDIF 
     1344 
     1345!!$        ! DS : Add warning in case of a wrong configuration (need to be discussed) 
     1346!!$        ! 2.  
     1347!!$        IF (.NOT.(read_lai) .AND. old_lai) THEN 
     1348!!$           CALL ipslerr (2,'veget_config', & 
     1349!!$               &     'Problem with lai_map desactivated and old_lai activated.',& 
     1350!!$               &     'Are you sure ?', & 
     1351!!$               &     '(check your parameters).') 
     1352!!$        ENDIF 
     1353!!$     
     1354!!$        ! 3. 
     1355!!$        IF ((impveg .OR. land_use) .AND. old_veget) THEN 
     1356!!$           CALL ipslerr (2,'veget_config', & 
     1357!!$                &     'Problem : try to use the old interpolation with a land use map or in impose_veg.',& 
     1358!!$                &     'Are you sure ?', & 
     1359!!$                &     '(check your parameters).') 
     1360!!$        ENDIF 
     1361!!$ 
     1362!!$        ! 4. 
     1363!!$        IF ( .NOT.(impveg) .AND. impsoilt) THEN 
     1364!!$           CALL ipslerr (2,'veget_config', & 
     1365!!$               &     'Problem : try to activate impose_soilt without activating impose_veg.',& 
     1366!!$               &     'Are you sure ?', & 
     1367!!$               &     '(check your parameters).') 
     1368!!$        ENDIF 
     1369!!$ 
     1370!!$        ! 5. 
     1371!!$        IF (.NOT.(land_use) .AND. (veget_reinit)) THEN 
     1372!!$           CALL ipslerr (2,'veget_config', & 
     1373!!$                &     'Problem : try to use a land_use map without activating land_use.',& 
     1374!!$                &     'Are you sure ?', & 
     1375!!$                &     '(check your parameters).')         
     1376!!$        ENDIF 
     1377!!$ 
     1378!!$        ! 6. 
     1379!!$        IF (.NOT.(land_use) .AND. lcchange) THEN 
     1380!!$           CALL ipslerr (2,'veget_config', & 
     1381!!$                &     'Problem : lcchange is activated without activating land_use.',& 
     1382!!$                &     'Are you sure ?', & 
     1383!!$                &     '(check your parameters).')         
     1384!!$        ENDIF 
     1385            
     1386   END SUBROUTINE veget_config 
     1387! 
     1388!= 
     1389! 
    10971390   SUBROUTINE getin_sechiba_parameters 
    10981391 
     
    11081401        CALL getin_p('MAXMASS_GLACIER',maxmass_glacier) 
    11091402        CALL getin_p('SNOWCRI',snowcri) 
     1403        ! 
     1404        !Interception reservoir coefficient 
     1405        !Config  Key  = 'SECHIBA_QSINT'  
     1406        !Config  Desc = Interception reservoir coefficient 
     1407        !Config  Def  = 0.1 
     1408        !Config  Help = Transforms leaf area index into size of interception reservoir 
     1409        !Config         for slowproc_derivvar or stomate 
    11101410        CALL getin_p('SECHIBA_QSINT', qsintcst) 
    1111         WRITE(numout, *)' SECHIBA_QSINT, qsintcst = ', qsintcst 
     1411        ! 
     1412        !Config Key  = HYDROL_SOIL_DEPTH 
     1413        !Config Desc = Total depth of soil reservoir 
     1414        !Config Def  = 2. 
    11121415        CALL getin_p("HYDROL_SOIL_DEPTH", dpu_cste) 
    11131416        ! 
     
    11341437        CALL getin_p('ALB_DEADLEAF',alb_deadleaf) 
    11351438        CALL getin_p('ALB_ICE',alb_ice) 
     1439        ! 
     1440        ! Get the fixed snow albedo if needed 
     1441        ! 
     1442        !Config Key  = CONDVEG_SNOWA 
     1443        !Config Desc = The snow albedo used by SECHIBA 
     1444        !Config Def  = DEF  
     1445        !Config Help = This option allows the user to impose a snow albedo. 
     1446        !Config        Default behaviour is to use the model of snow albedo 
     1447        !Config        developed by Chalita (1993). 
     1448        CALL getin_p('CONDVEG_SNOWA', fixed_snow_albedo) 
     1449        ! 
     1450        !Config Key  = ALB_BARE_MODEL 
     1451        !Config Desc = Switch bare soil albedo dependent (if TRUE) on soil wetness 
     1452        !Config Def  = FALSE 
     1453        !Config Help = If TRUE, the model for bare soil albedo is the old formulation. 
     1454        !Config        Then it depend on the soil dry or wetness. If FALSE, it is the  
     1455        !Config        new computation that is taken, it is the mean of soil albedo. 
     1456        CALL getin_p('ALB_BARE_MODEL', alb_bare_model) 
     1457        ! 
     1458        !Config Key  = IMPOSE_AZE 
     1459        !Config Desc = Should the surface parameters be prescribed 
     1460        !Config Def  = n 
     1461        !Config Help = This flag allows the user to impose the surface parameters 
     1462        !Config        (Albedo Roughness and Emissivity). It is espacially interesting for 0D 
     1463        !Config        simulations. On the globe it does not make too much sense as 
     1464        !Config        it imposes the same vegetation everywhere 
     1465        CALL getin_p('IMPOSE_AZE', impaze) 
     1466        ! 
     1467        !Config Key  = Z0CDRAG_AVE 
     1468        !Config Desc = Average method for z0 
     1469        !Config Def  = y 
     1470        !Config Help = If this flag is set to true (y) then the neutral Cdrag 
     1471        !Config        is averaged instead of the log(z0). This should be 
     1472        !Config        the prefered option. We still wish to keep the other 
     1473        !Config        option so we can come back if needed. If this is 
     1474        !Config        desired then one should set Z0CDRAG_AVE=n 
     1475        CALL getin_p('Z0CDRAG_AVE', z0cdrag_ave) 
     1476        ! 
     1477        !Config Key  = CONDVEG_Z0 
     1478        !Config Desc = Surface roughness (m) 
     1479        !Config Def  = 0.15 
     1480        !Config If   = IMPOSE_AZE 
     1481        !Config Help = Surface rougness to be used on the point if a 0-dim version 
     1482        !Config        of SECHIBA is used. Look at the description of the forcing   
     1483        !Config        data for the correct value. 
     1484        CALL getin_p('CONDVEG_Z0', z0_scal)   
     1485        ! 
     1486        !Config Key  = ROUGHHEIGHT 
     1487        !Config Desc = Height to be added to the height of the first level (m) 
     1488        !Config Def  = 0.0 
     1489        !Config If   = IMPOSE_AZE 
     1490        !Config Help = ORCHIDEE assumes that the atmospheric level height is counted 
     1491        !Config        from the zero wind level. Thus to take into account the roughness 
     1492        !Config        of tall vegetation we need to correct this by a certain fraction 
     1493        !Config        of the vegetation height. This is called the roughness height in 
     1494        !Config        ORCHIDEE talk. 
     1495        CALL getin_p('ROUGHHEIGHT', roughheight_scal) 
     1496        !  
     1497        !Config Key  = CONDVEG_ALBVIS 
     1498        !Config Desc = SW visible albedo for the surface 
     1499        !Config Def  = 0.25 
     1500        !Config If   = IMPOSE_AZE 
     1501        !Config Help = Surface albedo in visible wavelengths to be used  
     1502        !Config        on the point if a 0-dim version of SECHIBA is used.  
     1503        !Config        Look at the description of the forcing data for  
     1504        !Config        the correct value. 
     1505        CALL getin_p('CONDVEG_ALBVIS', albedo_scal(ivis)) 
     1506        ! 
     1507        !Config Key  = CONDVEG_ALBNIR 
     1508        !Config Desc = SW near infrared albedo for the surface 
     1509        !Config Def  = 0.25 
     1510        !Config If   = IMPOSE_AZE 
     1511        !Config Help = Surface albedo in near infrared wavelengths to be used  
     1512        !Config        on the point if a 0-dim version of SECHIBA is used.  
     1513        !Config        Look at the description of the forcing data for  
     1514        !Config        the correct value. 
     1515        CALL getin_p('CONDVEG_ALBNIR', albedo_scal(inir)) 
     1516        ! 
     1517        !Config Key  = CONDVEG_EMIS 
     1518        !Config Desc = Emissivity of the surface for LW radiation 
     1519        !Config Def  = 1.0 
     1520        !Config If   = IMPOSE_AZE 
     1521        !Config Help = The surface emissivity used for compution the LE emission 
     1522        !Config        of the surface in a 0-dim version. Values range between  
     1523        !Config        0.97 and 1.. The GCM uses 0.98. 
     1524        CALL getin_p('CONDVEG_EMIS', emis_scal) 
    11361525        !- 
    11371526        ! diffuco  
     
    11471536        CALL getin_p('MIN_VEGFRAC',min_vegfrac) 
    11481537        CALL getin_p('SOILTYPE_DEFAULT',soiltype_default) 
    1149          
    1150          
     1538        ! 
     1539        !Config Key  = VEGET_YEAR 
     1540        !Config Desc = Year of the land_use vegetation map to be read (0 == NO TIME AXIS) 
     1541        !Config If   = LAND_USE 
     1542        !Config Def  = 282 
     1543        !Config Help = First year for landuse vegetation (2D map by pft). 
     1544        !Config Help   If VEGET_YEAR == 0, this means there is no time axis. 
     1545        CALL getin_p('VEGET_YEAR', veget_year_orig) 
     1546        ! 
    11511547        first_call =.FALSE. 
    11521548         
     
    12041600        CALL getin_p('RSOL_CSTE',rsol_cste) 
    12051601        CALL getin_p('HCRIT_LITTER',hcrit_litter) 
    1206          
     1602        ! 
     1603        !Config  Key  = HYDROL_OK_HDIFF 
     1604        !Config  Desc = do horizontal diffusion? 
     1605        !Config  Def  = n 
     1606        !Config  Help = If TRUE, then water can diffuse horizontally between 
     1607        !Config         the PFTs' water reservoirs. 
     1608        CALL getin_p('HYDROL_OK_HDIFF',ok_hdiff)          
     1609 
    12071610        first_call =.FALSE. 
    12081611         
     
    12221625     LOGICAL, SAVE ::  first_call = .TRUE. 
    12231626      
    1224      IF(first_call) THEN 
     1627     IF (first_call) THEN 
    12251628         
    12261629        CALL getin_p('W_TIME',w_time) 
     
    12351638        CALL getin_p('MCW',mcw) 
    12361639        CALL getin_p('MC_AWET',mc_awet) 
    1237          
     1640          
    12381641        first_call =.FALSE. 
    12391642         
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_sechiba/condveg.f90

    r257 r311  
    3636  ! 
    3737  LOGICAL, SAVE                     :: l_first_condveg=.TRUE.           !! To keep first call's trace 
    38   LOGICAL, SAVE                     :: z0cdrag_ave=.FALSE.              !! Chooses the method for the z0 average 
    39   ! 
    40   REAL(r_std), SAVE                  :: fixed_snow_albedo                !! In case we wish a fxed snow albedo 
    41   INTEGER(i_std), PARAMETER         :: ivis = 1                         !! index for visible albedo 
    42   INTEGER(i_std), PARAMETER         :: inir = 2                         !! index for near infrared albedo 
    43   LOGICAL, SAVE                     :: impaze                           !! Choice on the surface parameters 
    44   ! 
    45   REAL(r_std), SAVE                  :: z0_scal                          !! Roughness used to initialize the scheme 
    46   REAL(r_std), SAVE                  :: roughheight_scal                 !! Height to displace the surface  
    47                                                                         !! from the zero wind height. 
    48   REAL(r_std), SAVE                  :: albedo_scal(2)                   !! Two albedos used to initialize the scheme 
    49   REAL(r_std), SAVE                  :: emis_scal                        !! Surface emissivity  used to initialize the scheme 
    5038  ! 
    5139  REAL(r_std), ALLOCATABLE, SAVE     :: soilalb_dry(:,:)                 !! albedo for the dry bare soil 
     
    6048  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: albedo_glob      !! Mean albedo 
    6149  ! 
    62   LOGICAL, SAVE                                  :: alb_bare_model   !! Switch to old (albedo bare depend on soil wetness)  
    63                                                                      !! or new one (mean of soilalb) 
    6450 
    6551CONTAINS 
     
    227213    ! initialisation 
    228214    IF (l_first_condveg) THEN  
    229        ! 
    230        ! Get the fixed snow albedo if needed 
    231        ! 
    232        ! 
    233        !Config Key  = CONDVEG_SNOWA 
    234        !Config Desc = The snow albedo used by SECHIBA 
    235        !Config Def  = DEF  
    236        !Config Help = This option allows the user to impose a snow albedo. 
    237        !Config        Default behaviour is to use the model of snow albedo 
    238        !Config        developed by Chalita (1993). 
    239        ! 
    240        fixed_snow_albedo = undef_sechiba 
    241        CALL getin_p('CONDVEG_SNOWA', fixed_snow_albedo) 
    242        ! 
    243        ! 
    244        !Config Key  = ALB_BARE_MODEL 
    245        !Config Desc = Switch bare soil albedo dependent (if TRUE) on soil wetness 
    246        !Config Def  = FALSE 
    247        !Config Help = If TRUE, the model for bare soil albedo is the old formulation. 
    248        !Config        Then it depend on the soil dry or wetness. If FALSE, it is the  
    249        !Config        new computation that is taken, it is the mean of soil albedo. 
    250        ! 
    251        alb_bare_model=.FALSE. 
    252        CALL getin_p('ALB_BARE_MODEL', alb_bare_model) 
    253215       !        
    254216       l_first_condveg=.FALSE. 
     
    392354    INTEGER(i_std)                                 :: jv 
    393355    ! initialisation of variables 
    394     ! 
    395  
    396     ! 
    397     !Config Key  = IMPOSE_AZE 
    398     !Config Desc = Should the surface parameters be prescribed 
    399     !Config Def  = n 
    400     !Config Help = This flag allows the user to impose the surface parameters 
    401     !Config        (Albedo Roughness and Emissivity). It is espacially interesting for 0D 
    402     !Config        simulations. On the globe it does not make too much sense as 
    403     !Config        it imposes the same vegetation everywhere 
    404     ! 
    405     impaze = .FALSE. 
    406     CALL getin_p('IMPOSE_AZE', impaze) 
    407356 
    408357    !! 
     
    412361    IF ( impaze ) THEN 
    413362       ! 
    414        !Config Key  = CONDVEG_EMIS 
    415        !Config Desc = Emissivity of the surface for LW radiation 
    416        !Config Def  = 1.0 
    417        !Config If   = IMPOSE_AZE 
    418        !Config Help = The surface emissivity used for compution the LE emission 
    419        !Config        of the surface in a 0-dim version. Values range between  
    420        !Config        0.97 and 1.. The GCM uses 0.98. 
    421        ! 
    422        emis_scal = un 
    423        CALL getin_p('CONDVEG_EMIS', emis_scal) 
    424363       emis(:) = emis_scal 
    425  
     364       ! 
    426365    ELSE 
    427366       !  Some day it will be moisture dependent 
     
    436375    ! 
    437376    IF ( impaze ) THEN 
    438       ! 
    439       !Config Key  = CONDVEG_ALBVIS 
    440       !Config Desc = SW visible albedo for the surface 
    441       !Config Def  = 0.25 
    442       !Config If   = IMPOSE_AZE 
    443       !Config Help = Surface albedo in visible wavelengths to be used  
    444       !Config        on the point if a 0-dim version of SECHIBA is used.  
    445       !Config        Look at the description of the forcing data for  
    446       !Config        the correct value. 
    447       ! 
    448         albedo_scal(ivis) = 0.25_r_std 
    449         CALL getin_p('CONDVEG_ALBVIS', albedo_scal(ivis)) 
     377       ! 
    450378       albedo(:,ivis) = albedo_scal(ivis) 
    451       ! 
    452       !Config Key  = CONDVEG_ALBNIR 
    453       !Config Desc = SW near infrared albedo for the surface 
    454       !Config Def  = 0.25 
    455       !Config If   = IMPOSE_AZE 
    456       !Config Help = Surface albedo in near infrared wavelengths to be used  
    457       !Config        on the point if a 0-dim version of SECHIBA is used.  
    458       !Config        Look at the description of the forcing data for  
    459       !Config        the correct value. 
    460       ! 
    461        albedo_scal(inir) = 0.25_r_std 
    462        CALL getin_p('CONDVEG_ALBNIR', albedo_scal(inir)) 
    463379       albedo(:,inir) = albedo_scal(inir) 
     380       ! 
    464381    ELSE 
    465382       ! 
     
    470387    !! calculs de z0 
    471388    !! 
    472     ! 
    473     !Config Key  = Z0CDRAG_AVE 
    474     !Config Desc = Average method for z0 
    475     !Config Def  = y 
    476     !Config Help = If this flag is set to true (y) then the neutral Cdrag 
    477     !Config        is averaged instead of the log(z0). This should be 
    478     !Config        the prefered option. We still wish to keep the other 
    479     !Config        option so we can come back if needed. If this is 
    480     !Config        desired then one should set Z0CDRAG_AVE=n 
    481     z0cdrag_ave = .TRUE. 
    482     CALL getin_p('Z0CDRAG_AVE', z0cdrag_ave) 
    483389    !! 
    484390    IF ( impaze ) THEN 
    485391      ! 
    486       !Config Key  = CONDVEG_Z0 
    487       !Config Desc = Surface roughness (m) 
    488       !Config Def  = 0.15 
    489       !Config If   = IMPOSE_AZE 
    490       !Config Help = Surface rougness to be used on the point if a 0-dim version 
    491       !Config        of SECHIBA is used. Look at the description of the forcing   
    492       !Config        data for the correct value. 
    493       ! 
    494       z0_scal = 0.15_r_std 
    495       CALL getin_p('CONDVEG_Z0', z0_scal) 
    496392      z0(:) = z0_scal 
    497       ! 
    498       !Config Key  = ROUGHHEIGHT 
    499       !Config Desc = Height to be added to the height of the first level (m) 
    500       !Config Def  = 0.0 
    501       !Config If   = IMPOSE_AZE 
    502       !Config Help = ORCHIDEE assumes that the atmospheric level height is counted 
    503       !Config        from the zero wind level. Thus to take into account the roughness 
    504       !Config        of tall vegetation we need to correct this by a certain fraction 
    505       !Config        of the vegetation height. This is called the roughness height in 
    506       !Config        ORCHIDEE talk. 
    507       ! 
    508       roughheight_scal = zero 
    509       CALL getin_p('ROUGHHEIGHT', roughheight_scal) 
    510393      roughheight(:) = roughheight_scal 
    511394      ! 
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_sechiba/hydrol.f90

    r282 r311  
    249249    IF (l_first_hydrol) THEN 
    250250 
    251        sneige = snowcri/mille 
    252  
    253251       IF (long_print) WRITE (numout,*) ' l_first_hydrol : call hydrol_init ' 
    254252 
    255253       CALL hydrol_init (kjit, ldrestart_read, kjpindex, index, rest_id, veget, soiltype, humrel,& 
    256254            & vegstress, snow, snow_age, snow_nobio, snow_nobio_age, qsintveg)  
     255 
    257256       CALL hydrol_var_init (kjpindex, veget, soiltype, mx_eau_var, shumdiag, litterhumdiag, & 
    258257            & drysoil_frac, evap_bare_lim)  
     
    498497       STOP 'hydrol_init' 
    499498    ENDIF 
     499 
     500    ! >> july 2011 DS : add initialisation of sneige and throughfall_by_pft 
     501    sneige = snowcri/mille 
     502    throughfall_by_pft = throughfall_by_pft / 100.    
    500503 
    501504    ! make dynamic allocation with good dimension 
     
    18921895    INTEGER(i_std)                                :: ji, jv 
    18931896    REAL(r_std), DIMENSION (kjpindex,nvm)          :: zqsintvegnew 
    1894     LOGICAL, SAVE                                  :: firstcall=.TRUE. 
    1895  
    1896     IF ( firstcall ) THEN 
    1897  
    1898        throughfall_by_pft = throughfall_by_pft / 100. 
    1899  
    1900        firstcall=.FALSE. 
    1901     ENDIF 
     1897!!$    LOGICAL, SAVE                                  :: firstcall=.TRUE. 
     1898!!$ 
     1899!!$    IF ( firstcall ) THEN 
     1900!!$ 
     1901!!$       throughfall_by_pft = throughfall_by_pft / 100. 
     1902!!$ 
     1903!!$       firstcall=.FALSE. 
     1904!!$    ENDIF 
    19021905 
    19031906 
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_sechiba/hydrolc.f90

    r282 r311  
    4040  ! 
    4141  LOGICAL, SAVE                                     :: check_waterbal=.FALSE. !! The check the water balance 
    42   LOGICAL, SAVE                                     :: ok_hdiff         !! do horizontal diffusion? 
    4342 
    4443  CHARACTER(LEN=80) , SAVE                          :: var_name         !! To store variables names for I/O 
     
    175174    IF (l_first_hydrol) THEN 
    176175 
    177        sneige = snowcri/mille 
    178  
    179176        IF (long_print) WRITE (numout,*) ' l_first_hydrol : call hydrolc_init ' 
    180177 
     
    450447    ENDIF 
    451448 
    452     !Config  Key  = HYDROL_OK_HDIFF 
    453     !Config  Desc = do horizontal diffusion? 
    454     !Config  Def  = n 
    455     !Config  Help = If TRUE, then water can diffuse horizontally between 
    456     !Config         the PFTs' water reservoirs. 
    457   
    458     ok_hdiff = .FALSE. 
    459     CALL getin_p('HYDROL_OK_HDIFF',ok_hdiff)  
     449    ! >> july 2011 add initialisation of sneige and throughfall_by_pft 
     450    sneige = snowcri/mille 
     451    throughfall_by_pft = throughfall_by_pft / 100.    
    460452 
    461453    ! make dynamic allocation with good dimension 
     
    854846        zdsp(:,:) = dpu_cste - bqsb(:,:) / mx_eau_eau 
    855847        dsp(1,1) = val_exp 
    856         call getin_p('HYDROL_DSP', dsp(1,1)) 
     848        CALL getin_p('HYDROL_DSP', dsp(1,1)) 
    857849        IF (dsp(1,1) == val_exp) THEN 
    858850           dsp(:,:) = zdsp(:,:) 
     
    14581450    INTEGER(i_std)                                :: ji, jv 
    14591451    REAL(r_std), DIMENSION (kjpindex,nvm)          :: zqsintvegnew 
    1460     LOGICAL, SAVE                                  :: firstcall=.TRUE. 
    1461  
    1462     IF ( firstcall ) THEN 
    1463  
    1464        throughfall_by_pft = throughfall_by_pft / 100. 
    1465  
    1466        firstcall=.FALSE. 
    1467     ENDIF 
     1452!!$    LOGICAL, SAVE                                  :: firstcall=.TRUE. 
     1453!!$ 
     1454!!$    IF ( firstcall ) THEN 
     1455!!$ 
     1456!!$       throughfall_by_pft = throughfall_by_pft / 100. 
     1457!!$ 
     1458!!$       firstcall=.FALSE. 
     1459!!$    ENDIF 
    14681460 
    14691461    ! calcul de qsintmax a prevoir a chaque pas de temps 
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_sechiba/intersurf.f90

    r281 r311  
    29612961    control_flags%ok_pheno = .TRUE. 
    29622962    ! 
     2963!>> july 2011 
     2964    ! DS: activation of sub-models of ORCHIDEE 
     2965    CALL activate_sub_models(control_flags%ok_sechiba, control_flags%river_routing,control_flags%ok_stomate) 
     2966    ! Vegetation configuration(impose_veg, land_use, lcchnage...previously in slowproc) 
     2967    CALL veget_config 
    29632968    ! 
    29642969    RETURN 
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_sechiba/routing.f90

    r277 r311  
    6767  REAL(r_std), PARAMETER                             :: maxevap_lake = 7.5/86400. 
    6868  ! 
    69   INTEGER(i_std), PARAMETER                         :: undef_int = 999999999 
    70   ! 
    7169  REAL(r_std),SAVE                                   :: dt_routing 
    72   ! 
    73   ! Logicals to control model configuration 
    74   ! 
    75   LOGICAL, SAVE                                     :: doirrigation = .FALSE. 
    76   LOGICAL, SAVE                                     :: dofloodplains = .FALSE. 
    77   ! 
    7870  ! 
    7971  ! The variables describing the basins and their routing, need to be in the restart file. 
     
    519511    num_largest = 50 
    520512    CALL getin_p('ROUTING_RIVERS', num_largest) 
    521     ! 
    522     !Config Key  = DO_IRRIGATION 
    523     !Config Desc = Should we compute an irrigation flux  
    524     !Config Def  = FALSE 
    525     !Config Help = This parameters allows the user to ask the model 
    526     !Config        to compute an irigation flux. This performed for the 
    527     !Config        on very simple hypothesis. The idea is to have a good 
    528     !Config        map of irrigated areas and a simple function which estimates 
    529     !Config        the need to irrigate. 
    530     ! 
    531     doirrigation = .FALSE. 
    532     CALL getin_p('DO_IRRIGATION', doirrigation) 
    533     ! 
    534     !Config Key  = DO_FLOODPLAINS 
    535     !Config Desc = Should we include floodplains  
    536     !Config Def  = FALSE 
    537     !Config Help = This parameters allows the user to ask the model 
    538     !Config        to take into account the flood plains and return  
    539     !Config        the water into the soil moisture. It then can go  
    540     !Config        back to the atmopshere. This tried to simulate  
    541     !Config        internal deltas of rivers. 
    542     ! 
    543     dofloodplains = .FALSE. 
    544     CALL getin_p('DO_FLOODPLAINS', dofloodplains) 
    545     ! 
    546513    ! 
    547514    ! In order to simplify the time cascade check that dt_routing 
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_sechiba/slowproc.f90

    r277 r311  
    5050  ! 
    5151  INTEGER(i_std) , SAVE                              :: veget_update=0   !! update frequency in years for landuse 
    52   INTEGER(i_std) , SAVE                              :: veget_year_orig=0     !! first year for landuse 
    53   LOGICAL, SAVE                                      :: land_use = .FALSE.        ! Land Use 
    54   LOGICAL, SAVE                                      :: veget_reinit=.FALSE.  !! To change LAND USE file in a run. 
    55   ! 
    56   LOGICAL, SAVE                                   :: read_lai = .FALSE.        ! Lai Map 
    57   LOGICAL, SAVE                                   :: old_lai = .FALSE.         ! Old Lai Map interpolation 
    58   LOGICAL, SAVE                                   :: impveg = .FALSE. 
    59   LOGICAL, SAVE                                   :: impsoilt = .FALSE. 
    60   LOGICAL, SAVE                                   :: old_veget = .FALSE.         ! Old veget Map interpolation 
    6152  ! 
    6253  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)    :: clayfraction  
     
    502493    CHARACTER(LEN=80)                                    :: var_name       !! To store variables names for I/O 
    503494    INTEGER(i_std)                                       :: ji, jv, ier 
    504     LOGICAL, INTENT(out)                                 ::  read_lai 
     495    ! DS 08072011 change in intent(in) 
     496    LOGICAL, INTENT(in)                                 ::  read_lai 
    505497    REAL(r_std)                                           :: frac_nobio1    !! temporary 
    506     REAL(r_std)                                           :: stempdiag_bid  !! only needed for an initial LAI  
    507                                                                             !! if there is no restart file 
    508498    REAL(r_std), DIMENSION(kjpindex,nbdl)                 :: stempdiag2_bid !! matrix to store stempdiag_bid 
    509499    CHARACTER(LEN=4)                                     :: vegsoil_dist   !! Flag to choose the soil/vegetation distribution 
     
    587577    CALL setvar_p (day_counter, val_exp, 'SECHIBA_DAY', zero) 
    588578    ! 
    589     !Config Key  = LAI_MAP 
    590     !Config Desc = Read the LAI map 
    591     !Config Def  = n 
    592     !Config Help = It is possible to read a 12 month LAI map which will 
    593     !Config        then be interpolated to daily values as needed. 
    594     ! 
    595     read_lai = .FALSE. 
    596     CALL getin_p('LAI_MAP',read_lai) 
    597     ! 
    598579    var_name= 'veget' 
    599580    CALL ioconf_setatt('UNITS', '-') 
     
    613594    CALL restget_p (rest_id, var_name, nbp_glo, nnobio, 1, kjit, .TRUE., frac_nobio, "gather", nbp_glo, index_g) 
    614595    ! 
    615     !Config Key  = LAND_USE 
    616     !Config Desc = Read a land_use vegetation map 
    617     !Config Def  = n 
    618     !Config Help = pft values are needed, max time axis is 293 
    619     ! 
    620     land_use = .FALSE. 
    621596    veget_update=0 
    622     CALL getin_p('LAND_USE',land_use) 
     597 
    623598    IF (land_use) THEN 
    624        ! 
    625        !Config Key  = VEGET_YEAR 
    626        !Config Desc = Year of the land_use vegetation map to be read (0 == NO TIME AXIS) 
    627        !Config If   = LAND_USE 
    628        !Config Def  = 282 
    629        !Config Help = First year for landuse vegetation (2D map by pft). 
    630        !Config Help   If VEGET_YEAR == 0, this means there is no time axis. 
    631        ! 
    632        veget_year_orig=282 
    633        CALL getin_p('VEGET_YEAR', veget_year_orig) 
    634        ! 
    635        !Config Key  = VEGET_REINIT 
    636        !Config Desc = booleen to indicate that a new LAND USE file will be used. 
    637        !Config If   = LAND_USE 
    638        !Config Def  = n 
    639        !Config Help = The parameter is used to bypass veget_year count  
    640        !Config Help   and reinitialize it with VEGET_YEAR parameter. 
    641        !Config Help   Then it is possible to change LAND USE file. 
    642        ! 
    643        veget_reinit = .FALSE. 
    644        CALL getin_p('VEGET_REINIT', veget_reinit) 
    645        ! 
    646599       ! 
    647600       var_name= 'veget_year' 
     
    678631       WRITE(numout,*) "Update frequency for land use in years :",veget_update 
    679632       ! 
    680        !Config  Key  = LAND_COVER_CHANGE 
    681        !Config  Desc = treat land use modifications 
    682        !Config  If   = LAND_USE 
    683        !Config  Def  = y 
    684        !Config  Help = With this variable, you can use a Land Use map 
    685        !Config         to simulate anthropic modifications such as  
    686        !Config         deforestation. 
    687        ! 
    688        lcchange = .TRUE.   
    689        CALL getin_p('LAND_COVER_CHANGE', lcchange) 
    690633       IF ( veget_update == 0 .AND. lcchange ) THEN 
    691634          CALL ipslerr (2,'slowproc_init', & 
     
    750693    CALL setvar_p (zcanop, val_exp, 'SECHIBA_ZCANOP', 0.5_r_std) 
    751694    ! 
    752     !Config Key  = HYDROL_SOIL_DEPTH 
    753     !Config Desc = Total depth of soil reservoir 
    754     !Config Def  = 2. 
    755     ! 
    756     dpu_cste=2. 
    757     CALL getin_p ("HYDROL_SOIL_DEPTH", dpu_cste) 
     695    ! Initialisation of dpu 
    758696    dpu(:)=dpu_cste 
    759697!MM, T. d'O. : before in constantes_soil : 
     
    783721 
    784722    ! 
    785     !  Interception reservoir coefficient 
    786     ! 
    787     !Config  Key  = 'SECHIBA_QSINT'  
    788     !Config  Desc = Interception reservoir coefficient 
    789     !Config  Def  = 0.1 
    790     !Config  Help = Transforms leaf area index into size of interception reservoir 
    791     !Config         for slowproc_derivvar or stomate 
    792  
    793 !!$    qsintcst = 0.1 
    794     CALL getin_p('SECHIBA_QSINT', qsintcst) 
    795     WRITE(numout, *)' SECHIBA_QSINT, qsintcst = ', qsintcst 
    796  
     723!!$    WRITE(numout, *)' SECHIBA_QSINT, qsintcst = ', qsintcst 
    797724    ! 
    798725    ! Time step of STOMATE and LAI update 
     
    807734    dt_slow = one_day 
    808735    CALL getin_p('DT_SLOW', dt_slow) 
    809     ! 
    810  
    811     !Config Key  = SLOWPROC_LAI_TEMPDIAG 
    812     !Config Desc = Temperature used for the initial guess of LAI 
    813     !Config Def  = 280. 
    814     !Config Help = If there is no LAI in the restart file, we may need 
    815     !Config        a temperature that is used to guess the initial LAI. 
    816     ! 
    817     stempdiag_bid = 280. 
    818     CALL getin_p('SLOWPROC_LAI_TEMPDIAG',stempdiag_bid) 
    819     !  
     736 
    820737    ! 
    821738    ! get restart value if none were found in the restart file 
    822739    ! 
    823     !Config  Key  = AGRICULTURE 
    824     !Config  Desc = agriculture allowed? 
    825     !Config  Def  = y 
    826     !Config  Help = With this variable, you can determine 
    827     !Config         whether agriculture is allowed 
    828     ! 
    829     agriculture = .TRUE. 
    830     CALL getin_p('AGRICULTURE', agriculture) 
    831     IF ( .NOT. agriculture .AND. land_use ) THEN  
    832        CALL ipslerr (2,'slowproc_init', & 
    833                &     'Problem with agriculture desactivated and Land Use activated.',& 
    834                &     'Are you sure ?', & 
    835                &     '(check your parameters).') 
    836     ENDIF 
    837  
    838     ! 
    839     !Config Key  = IMPOSE_VEG 
    840     !Config Desc = Should the vegetation be prescribed 
    841     !Config Def  = n 
    842     !Config Help = This flag allows the user to impose a vegetation distribution 
    843     !Config        and its characterisitcs. It is espacially interesting for 0D 
    844     !Config        simulations. On the globe it does not make too much sense as 
    845     !Config        it imposes the same vegetation everywhere 
    846     ! 
    847     impveg = .FALSE. 
    848     CALL getin_p('IMPOSE_VEG', impveg) 
     740!!$    IF ( .NOT. agriculture .AND. land_use ) THEN  
     741!!$       CALL ipslerr (2,'slowproc_init', & 
     742!!$               &     'Problem with agriculture desactivated and Land Use activated.',& 
     743!!$               &     'Are you sure ?', & 
     744!!$               &     '(check your parameters).') 
     745!!$    ENDIF 
    849746    ! 
    850747    IF ( impveg ) THEN 
     
    899796       CALL setvar_p (lai, val_exp, 'SECHIBA_LAI', llaimax) 
    900797 
    901        ! 
    902        !Config Key  = IMPOSE_SOILT 
    903        !Config Desc = Should the soil typ be prescribed 
    904        !Config Def  = n 
    905        !Config If   = IMPOSE_VEG 
    906        !Config Help = This flag allows the user to impose a soil type distribution. 
    907        !Config        It is espacially interesting for 0D 
    908        !Config        simulations. On the globe it does not make too much sense as 
    909        !Config        it imposes the same soil everywhere 
    910        ! 
    911        impsoilt = .FALSE. 
    912        CALL getin_p('IMPOSE_SOILT', impsoilt) 
    913798       IF (impsoilt) THEN 
    914799          !Config Key  = SOIL_FRACTIONS 
     
    958843 
    959844          IF ( .NOT. land_use ) THEN 
    960  
    961              !Config Key  = SLOWPROC_VEGET_OLD_INTERPOL 
    962              !Config Desc = Flag to use old "interpolation" of vegetation map. 
    963              !Config If   = NOT IMPOSE_VEG and NOT LAND_USE 
    964              !Config Def  = FALSE 
    965              !Config Help = If you want to recover the old (ie orchidee_1_2 branch)  
    966              !Config        "interpolation" of vegetation map. 
    967              ! 
    968              old_veget = .FALSE. 
    969              CALL getin_p('SLOWPROC_VEGET_OLD_INTERPOL',old_veget) 
    970845 
    971846             ! The interpolation of vegetation has changed. 
     
    1092967       ! 
    1093968       IF (read_lai) THEN 
    1094  
    1095           !Config Key  = SLOWPROC_LAI_OLD_INTERPOL 
    1096           !Config Desc = Flag to use old "interpolation" of LAI 
    1097           !Config If   = LAI_MAP 
    1098           !Config Def  = FALSE 
    1099           !Config Help = If you want to recover the old (ie orchidee_1_2 branch)  
    1100           !Config        "interpolation" of LAI map. 
    1101           ! 
    1102           old_lai = .FALSE. 
    1103           CALL getin_p('SLOWPROC_LAI_OLD_INTERPOL',old_lai) 
    1104969 
    1105970          ! 
     
    46704535    ! 79 warm C4 woody savanna 
    46714536    vegcorr(79,:) = & 
    4672          & (/0.0, 0.0, 0.4, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.6, 0.0, 0.0, 0.0/) 
     4537         & (/0.0, 0.0, 0.4, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.6, 0.0, 0.0/) 
    46734538    ! 80 cool woody savanna 
    46744539    vegcorr(80,:) = & 
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/lpj_fire.f90

    r257 r311  
    2929  ! first call 
    3030  LOGICAL, SAVE                                                   :: firstcall = .TRUE. 
    31   ! flag that disable fire 
    32   LOGICAL, SAVE                                                   :: disable_fire 
    3331 
    3432CONTAINS 
     
    157155 
    158156       firstcall = .FALSE. 
    159        ! 
    160        ! 1.3 read the flag that disable fire 
    161        ! 
    162        !Config  Key  = FIRE_DISABLE 
    163        !Config  Desc = no fire allowed 
    164        !Config  Def  = n 
    165        !Config  Help = With this variable, you can allow or not 
    166        !Config         the estimation of CO2 lost by fire 
    167        ! 
    168        disable_fire=.FALSE. 
    169        CALL getin_p('FIRE_DISABLE', disable_fire) 
    170157    ENDIF 
    171158 
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/stomate.f90

    r304 r311  
    245245  ! This variable must be .TRUE. once a year 
    246246  LOGICAL, SAVE                                :: EndOfYear=.FALSE. 
    247   ! Land cover change flag 
    248   LOGICAL,SAVE                                 :: lcchange=.FALSE. 
     247!!$  ! Land cover change flag 
     248!!$  LOGICAL,SAVE                                 :: lcchange=.FALSE. 
    249249  ! Do update of monthly variables ? 
    250250  ! This variable must be .TRUE. once a month 
    251251  LOGICAL, SAVE                                :: EndOfMonth=.FALSE. 
    252   PUBLIC  dt_days, day_counter, date, do_slow, EndOfYear, lcchange 
     252  PUBLIC  dt_days, day_counter, date, do_slow, EndOfYear !, lcchange 
    253253 
    254254 
     
    20472047       ENDDO 
    20482048    ENDDO 
    2049     ! 
    2050     ! 6 some flags 
    2051     ! 
    2052     ! 
    2053     !Config  Key  = HERBIVORES 
    2054     !Config  Desc = herbivores allowed? 
    2055     !Config  Def  = n 
    2056     !Config  Help = With this variable, you can determine 
    2057     !Config         if herbivores are activated 
    2058     ! 
    2059     ok_herbivores = .FALSE. 
    2060     CALL getin_p('HERBIVORES', ok_herbivores) 
    2061     ! 
    2062     WRITE(numout,*) 'herbivores activated: ',ok_herbivores 
    2063     ! 
    2064     !Config  Key  = TREAT_EXPANSION 
    2065     !Config  Desc = treat expansion of PFTs across a grid cell? 
    2066     !Config  Def  = n 
    2067     !Config  Help = With this variable, you can determine 
    2068     !Config         whether we treat expansion of PFTs across a 
    2069     !Config         grid cell. 
    2070     ! 
    2071     treat_expansion = .FALSE. 
    2072     CALL getin_p('TREAT_EXPANSION', treat_expansion) 
    2073     ! 
    2074     WRITE(numout,*) & 
    2075          &  'expansion across a grid cell is treated: ',treat_expansion 
    2076  
    2077     !Config Key  = LPJ_GAP_CONST_MORT 
    2078     !Config Desc = prescribe mortality if not using DGVM? 
    2079     !Config Def  = y 
    2080     !Config Help = set to TRUE if constant mortality is to be activated 
    2081     !              ignored if DGVM=true! 
    2082     ! 
    2083     lpj_gap_const_mort=.TRUE. 
    2084     CALL getin('LPJ_GAP_CONST_MORT', lpj_gap_const_mort) 
    2085     WRITE(numout,*) 'LPJ GAP: constant mortality:', lpj_gap_const_mort 
    2086  
    2087     !Config  Key  = HARVEST_AGRI 
    2088     !Config  Desc = Harvert model for agricol PFTs. 
    2089     !Config  Def  = y 
    2090     !Config  Help = Compute harvest above ground biomass for agriculture. 
    2091     !Config         Change daily turnover. 
    2092     harvest_agri = .TRUE. 
    2093     CALL getin_p('HARVEST_AGRI', harvest_agri) 
    2094  
    2095     ! 
    2096     ! 7 some global initializations 
     2049 
     2050    ! 
     2051    ! 6 some global initializations 
    20972052    ! 
    20982053    ! edit shilong 
Note: See TracChangeset for help on using the changeset viewer.