source: branches/publications/ORCHIDEE_Biochar/src_parameters/control.f90 @ 8375

Last change on this file since 8375 was 7366, checked in by simon.bowring, 3 years ago

Biochar version

File size: 20.0 KB
Line 
1! =================================================================================================================================
2! MODULE       : control
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        "control" module contains subroutines to initialize run time control parameters.
10!!
11!!\n DESCRIPTION:
12!!
13!! SVN          :
14!! $HeadURL:
15!! $Date: 
16!! $Revision:
17!! \n
18!_ ================================================================================================================================
19
20MODULE control
21 
22  USE constantes_soil
23  USE constantes_var
24!  USE time
25  USE pft_parameters
26  USE vertical_soil
27  USE constantes
28
29  IMPLICIT NONE
30
31CONTAINS
32!! ================================================================================================================================
33!! SUBROUTINE   : control_initialize
34!!
35!>\BRIEF        This subroutine reads the configuration flags which control the behaviour of the model
36!!              This subroutine was previsouly named intsurf_config and located in intersurf module.
37!!
38!! DESCRIPTION  : None
39!!
40!! RECENT CHANGE(S): None
41!!
42!! MAIN OUTPUT VARIABLE(S): None
43!!
44!! REFERENCE(S) : None
45!!
46!! FLOWCHART    : None
47!! \n
48!_ ================================================================================================================================
49
50  SUBROUTINE control_initialize
51
52    IMPLICIT NONE
53   
54    INTEGER(i_std)                             :: jv            !! Local index variable
55    INTEGER(i_std)                             :: ier           !! Error handeling
56
57    ! Start reading options from parameter file
58    !
59    !Config key   = ENABLE_NC_RESTART_COMPRESSION
60    !Config Desc  = Restart netcdf outputs file are written in compression mode
61    !Config If    =
62    !Config Def   = n
63    !Config Help  = This flag allows the user to decide if the restart netcdf
64    !Config         output files are compressed by default 
65    !Config Units = [FLAG]
66    !
67    NC_COMPRESSION_ENABLE = .TRUE.
68    CALL getin_p('ENABLE_NC_RESTART_COMPRESSION', NC_COMPRESSION_ENABLE)
69    WRITE(numout,*) "Netcdf restart compression is : ", NC_COMPRESSION_ENABLE
70
71    !Config Key   = SOILTYPE_CLASSIF
72    !Config Desc  = Type of classification used for the map of soil types
73    !Config Def   = zobler
74    !Config If    = !IMPOSE_VEG
75    !Config Help  = The classification used in the file that we use here
76    !Config         There are three classification supported: 
77    !Config         FAO (3 soil types), Zobler (7 converted to 3) and USDA (12)
78    !Config Units = [-]
79    !
80    !-tdo- Suivant le type de classification utilisee pour le sol, on adapte nscm
81    soil_classif = 'zobler'
82    CALL getin_p('SOILTYPE_CLASSIF',soil_classif)
83    SELECTCASE (soil_classif)
84    CASE ('zobler', 'fao','none')
85       nscm = nscm_fao
86    CASE ('usda')
87       nscm = nscm_usda
88    CASE DEFAULT
89       WRITE(numout,*) "Unsupported soil type classification. Choose between zobler, fao and usda according to the map"
90       STOP 'intsurf_config'
91    ENDSELECT
92
93
94    !Config Key   = RIVER_ROUTING
95    !Config Desc  = Decides if we route the water or not
96    !Config If    = OK_SECHIBA
97    !Config Def   = n
98    !Config Help  = This flag allows the user to decide if the runoff
99    !Config         and drainage should be routed to the ocean
100    !Config         and to downstream grid boxes.
101    !Config Units = [FLAG]
102    !
103    river_routing = .FALSE.
104    CALL getin_p('RIVER_ROUTING', river_routing)
105    IF (printlev>=1) WRITE(numout,*) "RIVER routing is activated : ",river_routing
106    !
107    !Config key   = HYDROL_CWRR
108    !Config Desc  = Allows to switch on the multilayer hydrology of CWRR
109    !Config If    = OK_SECHIBA
110    !Config Def   = n
111    !Config Help  = This flag allows the user to decide if the vertical
112    !Config         hydrology should be treated using the multi-layer
113    !Config         diffusion scheme adapted from CWRR by Patricia de Rosnay.
114    !Config         by default the Choisnel hydrology is used.
115    !Config Units = [FLAG]
116    !
117    hydrol_cwrr = .FALSE.
118    CALL getin_p('HYDROL_CWRR', hydrol_cwrr)
119    IF (printlev>=1) WRITE(numout,*) "CWRR hydrology is activated : ",hydrol_cwrr
120
121    !Config Key   = DO_IRRIGATION
122    !Config Desc  = Should we compute an irrigation flux
123    !Config If    = RIVER_ROUTING
124    !Config Def   = n
125    !Config Help  = This parameters allows the user to ask the model
126    !Config         to compute an irigation flux. This performed for the
127    !Config         on very simple hypothesis. The idea is to have a good
128    !Config         map of irrigated areas and a simple function which estimates
129    !Config         the need to irrigate.
130    !Config Units = [FLAG]
131    !
132    do_irrigation = .FALSE.
133    IF ( river_routing ) CALL getin_p('DO_IRRIGATION', do_irrigation)
134
135!!!!! crop irrigation
136    ! whether we disrupt water balance to fulfill crop needs
137    do_fullirr = .FALSE.
138    CALL getin_p('DO_FULLIRR', do_fullirr)
139    IF (do_fullirr) THEN
140        WRITE(numout,*) "do full irrigation regardless of water balance"
141    ENDIF 
142!!!!! end crops, xuhui
143
144!!!! crop rotation parameters
145    ok_rotate = .FALSE.
146    CALL getin_p('OK_ROTATE',ok_rotate)
147    dyn_plntdt = .FALSE.
148    CALL getin_p('DYN_PLNTDT',dyn_plntdt)
149!    dyn_cropfert = .FALSE.
150!    CALL getin_p('DYN_CROPFERT',dyn_cropfert)
151    nvm_plnt = .FALSE.
152    CALL getin_p('NVM_PLNT',nvm_plnt)
153    nvm_rot = .FALSE.
154    CALL getin_p('NVM_ROT',nvm_rot)
155    nvm_nfert = .FALSE.
156    CALL getin_p('NVM_NFERT',nvm_nfert)
157    cyc_rot_max = 1
158    CALL getin_p('CYC_ROT_MAX',cyc_rot_max)
159    CALL getin_p('ROT_CMD_MAX',rot_cmd_max) !by default it is 5
160    ! if reading maps, it will be automatically updated by map dimension
161    !!! resolving conflict
162    IF (.NOT. ok_rotate) THEN
163        cyc_rot_max = 1
164        WRITE(numout,*) 'xuhui: cyc_rot_max is forced to be 1, when ok_rotate is false'
165    ELSE !ok_rotate
166        dyn_plntdt = .FALSE.
167        WRITE(numout,*) 'xuhui: deactivate plantdate dynamics so that it follows rotation command'
168    ENDIF
169!!!! end rotation, xuhui
170
171    !
172    !Config Key   = DO_FLOODPLAINS
173    !Config Desc  = Should we include floodplains
174    !Config If    = RIVER_ROUTING
175    !Config Def   = n
176    !Config Help  = This parameters allows the user to ask the model
177    !Config         to take into account the flood plains and return
178    !Config         the water into the soil moisture. It then can go
179    !Config         back to the atmopshere. This tried to simulate
180    !Config         internal deltas of rivers.
181    !Config Units = [FLAG] 
182    !
183    do_floodplains = .FALSE.
184    IF ( river_routing ) CALL getin_p('DO_FLOODPLAINS', do_floodplains)
185    !
186    !Config Key   = CHECK_WATERBAL
187    !Config Desc  = Should we check the global water balance
188    !Config If    = OK_SECHIBA
189    !Config Def   = n
190    !Config Help  = This parameters allows the user to check
191    !Config         the integrated water balance at the end
192    !Config         of each time step
193    !Config Units = [FLAG] 
194    !
195    check_waterbal = .FALSE.
196    CALL getin_p('CHECK_WATERBAL', check_waterbal)
197
198    IF (check_waterbal .AND. do_fullirr) THEN
199        WRITE(numout,*) "setting conflicts: "
200        WRITE(numout,*) "DO_FULLIRR and CHECK_WATERBAL cannot coexist"
201        WRITE(numout,*) "change CHECK_WATERBAL to false"
202        check_waterbal = .FALSE.
203    ENDIF
204
205    !Config Key   = OK_EXPLICITSNOW
206    !Config Desc  = Activate explict snow scheme
207    !Config If    = OK_SECHIBA
208    !Config Def   = FALSE
209    !Config Help  = Activate explicit snow scheme instead of default snow scheme
210    !Config Units = [FLAG]
211    ok_explicitsnow = .FALSE.
212    CALL getin_p('OK_EXPLICITSNOW', ok_explicitsnow)
213
214    !Config Key   = OK_PC
215    !Config Desc  = Activate explict snow scheme
216    !Config If    = OK_SECHIBA
217    !Config Def   = FALSE
218    !Config Help  = Activate explicit snow scheme instead of default snow scheme
219    !Config Units = [FLAG]
220    ok_pc = .FALSE.
221    CALL getin_p('OK_PC', ok_pc)
222
223    !
224    !Config Key   = STOMATE_OK_STOMATE
225    !Config Desc  = Activate STOMATE?
226    !Config If    = OK_SECHIBA
227    !Config Def   = n
228    !Config Help  = set to TRUE if STOMATE is to be activated
229    !Config Units = [FLAG]
230    !
231    ok_stomate = .FALSE.
232    CALL getin_p('STOMATE_OK_STOMATE',ok_stomate)
233    IF (printlev>=1) WRITE(numout,*) 'STOMATE is activated: ',ok_stomate
234
235
236    IF ( ok_stomate ) THEN
237       ok_co2 = .TRUE.
238    ELSE
239       !Config Key   = STOMATE_OK_CO2
240       !Config Desc  = Activate CO2?
241       !Config If    = OK_SECHIBA
242       !Config Def   = y if OK_STOMATE else n
243       !Config Help  = set to TRUE if photosynthesis is to be activated
244       !Config Units = [FLAG]
245       ok_co2 = .FALSE.
246       CALL getin_p('STOMATE_OK_CO2', ok_co2)
247    END IF
248    IF (printlev>=1) WRITE(numout,*) 'Photosynthesis: ', ok_co2
249
250    !
251    !Config Key   = STOMATE_OK_DGVM
252    !Config Desc  = Activate DGVM?
253    !Config If    = OK_STOMATE
254    !Config Def   = n
255    !Config Help  = set to TRUE if DGVM is to be activated
256    !Config Units = [FLAG]
257    !
258    ok_dgvm = .FALSE.
259    CALL getin_p('STOMATE_OK_DGVM',ok_dgvm)
260    !
261    !Config Key   = CHEMISTRY_BVOC
262    !Config Desc  = Activate calculations for BVOC
263    !Config If    = OK_SECHIBA
264    !Config Def   = n
265    !Config Help  = set to TRUE if biogenic emissions calculation is to be activated
266    !Config Units = [FLAG]
267    !
268    ok_bvoc = .FALSE.
269    CALL getin_p('CHEMISTRY_BVOC', ok_bvoc)
270    IF (printlev>=1) WRITE(numout,*) 'Biogenic emissions: ', ok_bvoc
271
272    IF ( ok_bvoc ) THEN
273       ok_leafage         = .TRUE. 
274       ok_radcanopy       = .TRUE. 
275       ok_multilayer      = .TRUE.
276       ok_pulse_NOx       = .TRUE.
277       ok_bbgfertil_NOx   = .TRUE.
278       ok_cropsfertil_NOx = .TRUE.
279    ELSE
280       ok_leafage         = .FALSE. 
281       ok_radcanopy       = .FALSE. 
282       ok_multilayer      = .FALSE.
283       ok_pulse_NOx       = .FALSE.
284       ok_bbgfertil_NOx   = .FALSE.
285       ok_cropsfertil_NOx = .FALSE.
286    ENDIF
287    !
288    !Config Key   = CHEMISTRY_LEAFAGE
289    !Config Desc  = Activate LEAFAGE?
290    !Config If    = CHEMISTRY_BVOC
291    !Config Def   = n
292    !Config Help  = set to TRUE if biogenic emissions calculation takes leaf age into account
293    !Config Units = [FLAG]
294    !
295    CALL getin_p('CHEMISTRY_LEAFAGE', ok_leafage)
296    IF (printlev>=1) WRITE(numout,*) 'Leaf Age: ', ok_leafage
297    !
298    !Config Key   = CANOPY_EXTINCTION
299    !Config Desc  = Use canopy radiative transfer model?
300    !Config If    = CHEMISTRY_BVOC
301    !Config Def   = n
302    !Config Help  = set to TRUE if canopy radiative transfer model is used for biogenic emissions
303    !Config Units = [FLAG]
304    !
305    CALL getin_p('CANOPY_EXTINCTION', ok_radcanopy)
306    IF (printlev>=1) WRITE(numout,*) 'Canopy radiative transfer model: ', ok_radcanopy
307    !
308    !Config Key   = CANOPY_MULTILAYER
309    !Config Desc  = Use canopy radiative transfer model with multi-layers
310    !Config If    = CANOPY_EXTINCTION
311    !Config Def   = n
312    !Config Help  = set to TRUE if canopy radiative transfer model is with multiple layers
313    !Config Units = [FLAG]
314    !
315    CALL getin_p('CANOPY_MULTILAYER', ok_multilayer)
316    IF (printlev>=1) WRITE(numout,*) 'Multi-layer Canopy model: ', ok_multilayer
317    !
318    !Config Key   = NOx_RAIN_PULSE
319    !Config Desc  = Calculate NOx emissions with pulse?
320    !Config If    = CHEMISTRY_BVOC
321    !Config Def   = n
322    !Config Help  = set to TRUE if NOx rain pulse is taken into account
323    !Config Units = [FLAG]
324    !
325    CALL getin_p('NOx_RAIN_PULSE', ok_pulse_NOx)
326    IF (printlev>=1) WRITE(numout,*) 'Rain NOx pulsing: ', ok_pulse_NOx
327    !
328    !Config Key   = NOx_BBG_FERTIL
329    !Config Desc  = Calculate NOx emissions with bbg fertilizing effect?
330    !Config If    = CHEMISTRY_BVOC
331    !Config Def   = n
332    !Config Help  = set to TRUE if NOx emissions are calculated with bbg effect
333    !Config         Fertil effect of bbg on NOx soil emissions
334    !Config Units = [FLAG]
335    !
336    CALL getin_p('NOx_BBG_FERTIL', ok_bbgfertil_NOx)
337    IF (printlev>=1) WRITE(numout,*) 'NOx bbg fertil effect: ', ok_bbgfertil_NOx
338    !
339    !Config Key   = NOx_FERTILIZERS_USE
340    !Config Desc  = Calculate NOx emissions with fertilizers use?
341    !Config If    = CHEMISTRY_BVOC
342    !Config Def   = n
343    !Config Help  = set to TRUE if NOx emissions are calculated with fertilizers use
344    !Config         Fertilizers use effect on NOx soil emissions 
345    !Config Units = [FLAG]
346    !
347    CALL getin_p('NOx_FERTILIZERS_USE', ok_cropsfertil_NOx)
348    IF (printlev>=1) WRITE(numout,*) 'NOx Fertilizers use: ', ok_cropsfertil_NOx
349    !Config Key  = Is CO2 impact on BVOC accounted for using Possell 2005 ?
350    !Config Desc = In this case we use Possell 2005 parameterisation
351    !Config Desc = to take into account the impact of CO2 on biogenic emissions for
352    !Config Desc = isoprene
353    !Config Def  = n
354    !Config Help = set to TRUE if Possell parameterisation has to be considered for the CO2 impact
355    !
356    ok_co2bvoc_poss = .FALSE.
357    CALL getin_p('CO2_FOR_BVOC_POSSELL', ok_co2bvoc_poss)
358    IF (printlev>=1) WRITE(numout,*) 'CO2 impact on BVOC - Possell parameterisation: ', ok_co2bvoc_poss
359    !
360    !Config Key  = Is CO2 impact on BVOC accounted for using Wilkinson 2009 ?
361    !Config Desc = In this case we use Wilkinson 2009 parameterisation
362    !Config Desc = to take into account the impact of CO2 on biogenic emissions for
363    !Config Desc = isoprene
364    !Config Def  = n
365    !Config Help = set to TRUE if Wilkinson parameterisation has to be considered for the CO2 impact
366    !
367    ok_co2bvoc_wilk = .FALSE.
368    CALL getin_p('CO2_FOR_BVOC_WILKINSON', ok_co2bvoc_wilk)
369    IF (printlev>=1) WRITE(numout,*) 'CO2 impact on BVOC - Wilkinson parameterisation: ', ok_co2bvoc_wilk
370   
371    !
372    ! control initialisation with sechiba
373    !
374    ok_sechiba = .TRUE.
375    !
376    !
377    ! Ensure consistency
378    !
379    IF ( ok_dgvm ) ok_stomate = .TRUE.
380    IF ( ok_multilayer .AND. .NOT.(ok_radcanopy) ) THEN
381       ok_radcanopy  = .TRUE.
382       IF (printlev>=1) WRITE(numout,*) 'You want to use the multilayer model without activating the flag CANOPY_EXTINCTION'
383       IF (printlev>=1) WRITE(numout,*) 'We set CANOPY_EXTINCTION to TRUE to ensure consistency'
384    ENDIF
385    IF ( ok_dgvm .AND. ok_rotate) THEN
386        STOP 'ok_dgvm & ok_rotate cannot be true at the same time'
387    ENDIF
388
389
390
391    !
392    ! Here we need the same initialisation as above
393    !
394    ok_pheno = .TRUE.
395
396    !
397    ! Configuration : number of PFTs and parameters
398    !
399
400    ! 1. Number of PFTs defined by the user
401
402    !Config Key   = NVM
403    !Config Desc  = number of PFTs 
404    !Config If    = OK_SECHIBA or OK_STOMATE
405    !Config Def   = 13
406    !Config Help  = The number of vegetation types define by the user
407    !Config Units = [-]
408    !
409    CALL getin_p('NVM',nvm)
410    IF (printlev>=1) WRITE(numout,*) 'The number of pfts used by the model is : ', nvm
411
412    ! 2. Should we read the parameters in the run.def file ?
413
414    !Config Key   = IMPOSE_PARAM
415    !Config Desc  = Do you impose the values of the parameters?
416    !Config if    = OK_SECHIBA or OK_STOMATE
417    !Config Def   = y
418    !Config Help  = This flag can deactivate the reading of some parameters.
419    !               Useful if you want to use the standard values without commenting the run.def
420    !Config Units = [FLAG]
421    !
422    CALL getin_p('IMPOSE_PARAM',impose_param)
423
424
425    !! Initialize vertical discretization
426    IF (hydrol_cwrr) THEN
427       !! Case CWRR : All initialization is done in the vertical module
428       !! Calculate ngrnd and nslm
429       CALL vertical_soil_init
430    ELSE
431       !! Case Choisnel : get depth of soil and number of soil levels
432       ! Remove Config Key description because this was already done in vertical_soil_init.
433       !Config Def   = 2.0 or 4.0 depending on hydrol_cwrr flag
434       !Config Help  = Maximum depth of soil for soil moisture
435       !Config Units = m
436       zmaxh=4.0
437       CALL getin_p("DEPTH_MAX_H",zmaxh)
438
439       !Config Key   = THERMOSOIL_NBLEV
440       !Config Desc  = Number of soil level
441       !Config If    = HDYROL_CWRR=FALSE
442       !Config Def   = 7
443       !Config Help  = Use at least 11 for long term simulation where soil thermal inertia matters
444       !Config Units = (-)
445       ngrnd=7
446       CALL getin_p("THERMOSOIL_NBLEV",ngrnd)
447
448       ! Define nslm, number of levels in CWRR. This variable will not be used for Choisnel but needs to be initialized.
449       nslm=11
450    END IF
451
452    ! 3. Allocate and intialize the pft parameters
453
454    CALL pft_parameters_main()
455
456    ! 4. Activation sub-models of ORCHIDEE
457
458    CALL activate_sub_models()
459
460    ! 5. Vegetation configuration
461
462    CALL veget_config
463
464    ! 6. Read the parameters in the run.def file  according the flags
465
466    IF (impose_param ) THEN
467       CALL config_pft_parameters
468    ENDIF
469
470    IF ( ok_sechiba ) THEN
471       IF (impose_param ) THEN
472          IF (printlev>=2) WRITE(numout,*)'In control_initialize: call config_sechiba_parameters and config_sechiba_pft_parameters'
473          CALL config_sechiba_parameters
474          CALL config_sechiba_pft_parameters()
475       ENDIF
476    ENDIF
477
478
479    !! Initialize variables in constantes_soil
480    CALL config_soil_parameters()
481
482
483    !! Coherence check for depth of thermosoil for long term simulation where soil thermal inertia matters
484    !! ok_freeze_thermix is defined in config_soil_parameters
485    IF (hydrol_cwrr) THEN
486       ! Case CWRR
487       IF (ok_freeze_thermix .AND. zmaxt < 11) THEN
488          WRITE(numout,*) 'ERROR : Incoherence between ok_freeze_thermix activated and soil depth too small. '
489          WRITE(numout,*) 'Here a soil depth of ', zmaxt, 'm is used for the soil thermodynamics'
490          WRITE(numout,*) 'Set DEPTH_MAX_T=11 or higher in run.def parameter file or deactivate soil freezing'
491          CALL ipslerr_p(3,'control_initialize','Too shallow soil chosen for the thermodynamic for soil freezing', &
492               'Adapt run.def with at least DEPTH_MAX=11','')
493       END IF
494    ELSE
495       ! Case Choisnel
496       IF (ok_freeze_thermix .AND. ngrnd < 11) THEN
497          WRITE(numout,*) 'ERROR : Incoherence between ok_freeze_thermix activated and ngrnd to small. Here used ngrnd=',ngrnd
498          WRITE(numout,*) 'Set THERMOSOIL_NBLEV=11 or higher in run.def parameter file or deactivate soil freezing'
499          CALL ipslerr_p(3,'control_initialize','Not enough thermodynamic soil levels for soil freezing', &
500               'Adapt run.def with at least THERMOSOIL_NBLEV=11','')
501       END IF
502    END IF
503       
504    ! Define diaglev as the depth of the bottom of each layer
505    ! diaglev defines the vertical axes for the variables transmitted from sechiba
506    ! to stomate (stempdiag, shumdiag).
507    ALLOCATE(diaglev(nslm), stat=ier)
508    IF (ier /= 0) CALL ipslerr_p(3,'control_initialize','Pb in allocation of diaglev','','')
509
510    IF ( hydrol_cwrr ) THEN
511       ! Get diaglev from module vertical for CWRR
512       ! We take the top nslm (number of layer in CWRR) layer of the thermodynamics
513       ! for the diagnostics. The layers in the hydrology and the thermodynamics are
514       ! placed a the same depth (the top nslm layers) but the upper boundary condition
515       ! is simpler in the thermodynamics.
516       diaglev=zlt(1:nslm)
517    ELSE
518       ! Calculate diaglev for Choisnel
519       DO jv = 1, nslm-1
520           diaglev(jv) = zmaxh/(2**(nslm-1) -1) * ( ( 2**(jv-1) -1) + ( 2**(jv)-1) ) / deux
521      ENDDO
522      diaglev(nslm) = zmaxh
523    END IF
524    IF (printlev>=2) WRITE(numout,*) 'In control_initialize, diaglev = ',diaglev
525
526    IF ( ok_co2 ) THEN
527       IF ( impose_param ) THEN
528          IF (printlev>=2) WRITE(numout,*)'In control_initialize: call config_co2_parameters'
529          CALL config_co2_parameters
530       ENDIF
531    ENDIF
532   
533    IF ( ok_stomate ) THEN
534       IF ( impose_param ) THEN
535          IF (printlev>=2) WRITE(numout,*)'In control_initialize: call config_stomate_parameters and config_stomate_pft_parameters'
536          CALL config_stomate_parameters
537          CALL config_stomate_pft_parameters
538       ENDIF
539    ENDIF
540   
541    IF ( ok_dgvm ) THEN
542       IF ( impose_param ) THEN
543          IF (printlev>=2) WRITE(numout,*)'In control_initialize: call config_dgvm_parameters'
544          CALL config_dgvm_parameters
545       ENDIF
546    ENDIF   
547  END SUBROUTINE control_initialize
548 
549END MODULE control
Note: See TracBrowser for help on using the repository browser.