1 | MODULE icb_oce |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE icb_oce *** |
---|
4 | !! Icebergs: declare variables for iceberg tracking |
---|
5 | !!====================================================================== |
---|
6 | !! History : 3.3 ! 2010-01 (T. Martin & A. Adcroft) Original code |
---|
7 | !! - ! 2011-03 (G. Madec) Part conversion to NEMO form |
---|
8 | !! - ! Removal of mapping from another grid |
---|
9 | !! - ! 2011-04 (S. Alderson) Extensive rewrite ; Split into separate modules |
---|
10 | !!---------------------------------------------------------------------- |
---|
11 | !! |
---|
12 | !! Track Icebergs as Lagrangian objects within the model domain |
---|
13 | !! Interaction with the other model variables through 'icebergs_gridded' |
---|
14 | !! |
---|
15 | !! A single iceberg is held as an instance of type 'iceberg' |
---|
16 | !! This type defines a linked list, so each instance contains a pointer |
---|
17 | !! to the previous and next icebergs in the list |
---|
18 | !! |
---|
19 | !! Type 'icebergs' is a convenience container for all relevant arrays |
---|
20 | !! It contains one pointer to an 'iceberg' instance representing all icebergs in the processor |
---|
21 | !! |
---|
22 | !! Each iceberg has a position represented as a real cartesian coordinate which is |
---|
23 | !! fractional grid cell, centred on T-points; so an iceberg position of (1.0,1.0) lies |
---|
24 | !! exactly on the first T-point and the T-cell spans 0.5 to 1.5 in each direction |
---|
25 | !! |
---|
26 | !! Each iceberg is assigned a unique id even in MPI |
---|
27 | !! This consists of an array of integers: the first element is used to label, the second |
---|
28 | !! and subsequent elements are used to count the number of times the first element wraps |
---|
29 | !! around all possible values within the valid size for this datatype. |
---|
30 | !! Labelling is done by starting the first label in each processor (even when only one) |
---|
31 | !! as narea, and then incrementing by jpnij (i.e. the total number of processors. |
---|
32 | !! This means that the source processor for each iceberg can be identified by arithmetic |
---|
33 | !! modulo jpnij. |
---|
34 | !! |
---|
35 | !!---------------------------------------------------------------------- |
---|
36 | USE par_oce ! ocean parameters |
---|
37 | USE lib_mpp ! MPP library |
---|
38 | |
---|
39 | IMPLICIT NONE |
---|
40 | PUBLIC |
---|
41 | |
---|
42 | PUBLIC icb_alloc ! routine called by icb_init in icbini.F90 module |
---|
43 | |
---|
44 | INTEGER, PUBLIC, PARAMETER :: nclasses = 10 !: Number of icebergs classes |
---|
45 | INTEGER, PUBLIC, PARAMETER :: nkounts = 3 !: Number of integers combined for unique naming |
---|
46 | |
---|
47 | TYPE, PUBLIC :: icebergs_gridded !: various icebergs properties on model grid |
---|
48 | REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: calving ! Calving mass rate (into stored ice) [kg/s] |
---|
49 | REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: calving_hflx ! Calving heat flux [heat content of calving] [W/m2] |
---|
50 | REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: floating_melt ! Net melting rate to icebergs + bits [kg/s/m^2] |
---|
51 | INTEGER , DIMENSION(:,:) , ALLOCATABLE :: maxclass ! maximum class number at calving source point |
---|
52 | REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: tmp ! Temporary work space |
---|
53 | REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: stored_ice ! Accumulated ice mass flux at calving locations [kg] |
---|
54 | REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: stored_heat ! Heat content of stored ice [J] |
---|
55 | END TYPE icebergs_gridded |
---|
56 | |
---|
57 | TYPE, PUBLIC :: point !: properties of an individual iceberg (position, mass, size, etc...) |
---|
58 | INTEGER :: year |
---|
59 | REAL(wp) :: xi , yj ! iceberg coordinates in the (i,j) referential (global) |
---|
60 | REAL(wp) :: e1 , e2 ! horizontal scale factors at the iceberg position |
---|
61 | REAL(wp) :: lon, lat, day ! geographic position |
---|
62 | REAL(wp) :: mass, thickness, width, length, uvel, vvel ! iceberg physical properties |
---|
63 | REAL(wp) :: uo, vo, ui, vi, ua, va, ssh_x, ssh_y, sst, cn, hi, sss ! properties of iceberg environment |
---|
64 | REAL(wp) :: mass_of_bits, heat_density |
---|
65 | END TYPE point |
---|
66 | |
---|
67 | TYPE, PUBLIC :: iceberg !: linked list defining all the icebergs present in the model domain |
---|
68 | TYPE(iceberg), POINTER :: prev=>NULL(), next=>NULL() ! pointers to previous and next unique icebergs in linked list |
---|
69 | INTEGER, DIMENSION(nkounts) :: number ! variables which do not change for this iceberg |
---|
70 | REAL(wp) :: mass_scaling ! - - - - |
---|
71 | TYPE(point), POINTER :: current_point => NULL() ! variables which change with time are held in a separate type |
---|
72 | END TYPE iceberg |
---|
73 | |
---|
74 | |
---|
75 | TYPE(icebergs_gridded), POINTER :: berg_grid !: master instance of gridded iceberg type |
---|
76 | TYPE(iceberg) , POINTER :: first_berg => NULL() !: master instance of linked list iceberg type |
---|
77 | |
---|
78 | ! !!! parameters controlling iceberg characteristics and modelling |
---|
79 | REAL(wp) :: berg_dt !: Time-step between iceberg CALLs (should make adaptive?) |
---|
80 | REAL(wp), DIMENSION(:), ALLOCATABLE :: first_width, first_length !: |
---|
81 | LOGICAL :: l_restarted_bergs=.FALSE. ! Indicate whether we read state from a restart or not |
---|
82 | ! ! arbitrary numbers for diawri entry |
---|
83 | REAL(wp), DIMENSION(nclasses), PUBLIC :: class_num=(/ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10 /) |
---|
84 | |
---|
85 | ! Extra arrays with bigger halo, needed when interpolating forcing onto iceberg position |
---|
86 | ! particularly for MPP when iceberg can lie inside T grid but outside U, V, or f grid |
---|
87 | REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE :: uo_e, vo_e |
---|
88 | REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE :: ff_e, tt_e, fr_e, ss_e |
---|
89 | REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE :: ua_e, va_e |
---|
90 | REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE :: ssh_e |
---|
91 | REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE :: tmask_e, umask_e, vmask_e |
---|
92 | #if defined key_si3 || defined key_cice |
---|
93 | REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE :: hi_e, ui_e, vi_e |
---|
94 | #endif |
---|
95 | |
---|
96 | !!gm almost all those PARAM ARE defined in NEMO |
---|
97 | REAL(wp), PUBLIC, PARAMETER :: pp_rho_ice = 916.7_wp !: Density of fresh ice @ 0oC [kg/m^3] |
---|
98 | REAL(wp), PUBLIC, PARAMETER :: pp_rho_water = 999.8_wp !: Density of fresh water @ 0oC [kg/m^3] |
---|
99 | REAL(wp), PUBLIC, PARAMETER :: pp_rho_air = 1.1_wp !: Density of air @ 0oC [kg/m^3] |
---|
100 | REAL(wp), PUBLIC, PARAMETER :: pp_rho_seawater = 1025._wp !: Approx. density of surface sea water @ 0oC [kg/m^3] |
---|
101 | !!gm end |
---|
102 | REAL(wp), PUBLIC, PARAMETER :: pp_Cd_av = 1.3_wp !: (Vertical) Drag coefficient between bergs and atmos |
---|
103 | REAL(wp), PUBLIC, PARAMETER :: pp_Cd_ah = 0.0055_wp !: (lateral ) Drag coefficient between bergs and atmos |
---|
104 | REAL(wp), PUBLIC, PARAMETER :: pp_Cd_wv = 0.9_wp !: (Vertical) Drag coefficient between bergs and ocean |
---|
105 | REAL(wp), PUBLIC, PARAMETER :: pp_Cd_wh = 0.0012_wp !: (lateral ) Drag coefficient between bergs and ocean |
---|
106 | REAL(wp), PUBLIC, PARAMETER :: pp_Cd_iv = 0.9_wp !: (Vertical) Drag coefficient between bergs and sea-ice |
---|
107 | !TOM> no horizontal drag for sea ice! real, PARAMETER :: pp_Cd_ih=0.0012 ! (lateral) Drag coeff. between bergs and sea-ice |
---|
108 | |
---|
109 | ! !!* namberg namelist parameters (and defaults) ** |
---|
110 | LOGICAL , PUBLIC :: ln_bergdia !: Calculate budgets |
---|
111 | INTEGER , PUBLIC :: nn_verbose_level !: Turn on debugging when level > 0 |
---|
112 | INTEGER , PUBLIC :: nn_test_icebergs !: Create icebergs in absence of a restart file from the supplied class nb |
---|
113 | REAL(wp), PUBLIC, DIMENSION(4) :: rn_test_box !: lon1,lon2,lat1,lat2 box to create them in |
---|
114 | LOGICAL , PUBLIC :: ln_use_calving !: Force use of calving data even with nn_test_icebergs > 0 |
---|
115 | ! (default is not to use calving data with test bergs) |
---|
116 | INTEGER , PUBLIC :: nn_sample_rate !: Timesteps between sampling of position for trajectory storage |
---|
117 | INTEGER , PUBLIC :: nn_verbose_write !: timesteps between verbose messages |
---|
118 | REAL(wp), PUBLIC :: rn_rho_bergs !: Density of icebergs |
---|
119 | REAL(wp), PUBLIC :: rn_LoW_ratio !: Initial ratio L/W for newly calved icebergs |
---|
120 | REAL(wp), PUBLIC :: rn_bits_erosion_fraction !: Fraction of erosion melt flux to divert to bergy bits |
---|
121 | REAL(wp), PUBLIC :: rn_sicn_shift !: Shift of sea-ice concentration in erosion flux modulation (0<sicn_shift<1) |
---|
122 | LOGICAL , PUBLIC :: ln_operator_splitting !: Use first order operator splitting for thermodynamics |
---|
123 | LOGICAL , PUBLIC :: ln_passive_mode !: iceberg - ocean decoupling |
---|
124 | LOGICAL , PUBLIC :: ln_time_average_weight !: Time average the weight on the ocean !!gm I don't understand that ! |
---|
125 | REAL(wp), PUBLIC :: rn_speed_limit !: CFL speed limit for a berg |
---|
126 | ! |
---|
127 | ! restart |
---|
128 | CHARACTER(len=256), PUBLIC :: cn_icbrst_indir , cn_icbrst_in !: in: restart directory, restart name |
---|
129 | CHARACTER(len=256), PUBLIC :: cn_icbrst_outdir, cn_icbrst_out !: out: restart directory, restart name |
---|
130 | ! |
---|
131 | ! ! Mass thresholds between iceberg classes [kg] |
---|
132 | REAL(wp), DIMENSION(nclasses), PUBLIC :: rn_initial_mass ! Fraction of calving to apply to this class [non-dim] |
---|
133 | REAL(wp), DIMENSION(nclasses), PUBLIC :: rn_distribution ! Ratio between effective and real iceberg mass (non-dim) |
---|
134 | REAL(wp), DIMENSION(nclasses), PUBLIC :: rn_mass_scaling ! Total thickness of newly calved bergs [m] |
---|
135 | REAL(wp), DIMENSION(nclasses), PUBLIC :: rn_initial_thickness ! Single instance of an icebergs type initialised in icebergs_init and updated in icebergs_run |
---|
136 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: src_calving, src_calving_hflx !: accumulate input ice |
---|
137 | INTEGER , PUBLIC , SAVE :: numicb !: iceberg IO |
---|
138 | INTEGER , PUBLIC , SAVE, DIMENSION(nkounts) :: num_bergs !: iceberg counter |
---|
139 | INTEGER , PUBLIC , SAVE :: nicbdi, nicbei, nicbdj, nicbej !: processor bounds |
---|
140 | REAL(wp), PUBLIC , SAVE :: ricb_left, ricb_right !: cyclical bounds |
---|
141 | INTEGER , PUBLIC , SAVE :: nicbpack !: packing integer |
---|
142 | INTEGER , PUBLIC , SAVE :: nktberg, nknberg !: helpers |
---|
143 | INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: nicbfldpts !: nfold packed points |
---|
144 | INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: nicbflddest !: nfold destination proc |
---|
145 | INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: nicbfldproc !: nfold destination proc |
---|
146 | INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: nicbfldnsend !: nfold number of bergs to send to nfold neighbour |
---|
147 | INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: nicbfldexpect !: nfold expected number of bergs |
---|
148 | INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: nicbfldreq !: nfold message handle (immediate send) |
---|
149 | !!---------------------------------------------------------------------- |
---|
150 | !! NEMO/OCE 4.0 , NEMO Consortium (2018) |
---|
151 | !! $Id$ |
---|
152 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
153 | !!---------------------------------------------------------------------- |
---|
154 | CONTAINS |
---|
155 | |
---|
156 | INTEGER FUNCTION icb_alloc() |
---|
157 | !!---------------------------------------------------------------------- |
---|
158 | !! *** ROUTINE icb_alloc *** |
---|
159 | !!---------------------------------------------------------------------- |
---|
160 | INTEGER :: ill |
---|
161 | !!---------------------------------------------------------------------- |
---|
162 | ! |
---|
163 | icb_alloc = 0 |
---|
164 | ALLOCATE( berg_grid, STAT=ill ) |
---|
165 | icb_alloc = icb_alloc + ill |
---|
166 | ALLOCATE( berg_grid%calving (jpi,jpj) , berg_grid%calving_hflx (jpi,jpj) , & |
---|
167 | & berg_grid%stored_heat(jpi,jpj) , berg_grid%floating_melt(jpi,jpj) , & |
---|
168 | & berg_grid%maxclass (jpi,jpj) , berg_grid%stored_ice (jpi,jpj,nclasses) , & |
---|
169 | & berg_grid%tmp (jpi,jpj) , STAT=ill) |
---|
170 | icb_alloc = icb_alloc + ill |
---|
171 | ! |
---|
172 | ! expanded arrays for bilinear interpolation |
---|
173 | ALLOCATE( uo_e(0:jpi+1,0:jpj+1) , ua_e(0:jpi+1,0:jpj+1) , & |
---|
174 | & vo_e(0:jpi+1,0:jpj+1) , va_e(0:jpi+1,0:jpj+1) , & |
---|
175 | #if defined key_si3 || defined key_cice |
---|
176 | & ui_e(0:jpi+1,0:jpj+1) , & |
---|
177 | & vi_e(0:jpi+1,0:jpj+1) , & |
---|
178 | & hi_e(0:jpi+1,0:jpj+1) , & |
---|
179 | #endif |
---|
180 | & ff_e(0:jpi+1,0:jpj+1) , fr_e(0:jpi+1,0:jpj+1) , & |
---|
181 | & tt_e(0:jpi+1,0:jpj+1) , ssh_e(0:jpi+1,0:jpj+1) , & |
---|
182 | & ss_e(0:jpi+1,0:jpj+1) , & |
---|
183 | & first_width(nclasses) , first_length(nclasses) , & |
---|
184 | & src_calving (jpi,jpj) , & |
---|
185 | & src_calving_hflx(jpi,jpj) , STAT=ill) |
---|
186 | icb_alloc = icb_alloc + ill |
---|
187 | |
---|
188 | ALLOCATE( tmask_e(0:jpi+1,0:jpj+1), umask_e(0:jpi+1,0:jpj+1), vmask_e(0:jpi+1,0:jpj+1), & |
---|
189 | & STAT=ill) |
---|
190 | icb_alloc = icb_alloc + ill |
---|
191 | |
---|
192 | ALLOCATE( nicbfldpts(jpi) , nicbflddest(jpi) , nicbfldproc(jpni) , & |
---|
193 | & nicbfldnsend(jpni), nicbfldexpect(jpni) , nicbfldreq(jpni), STAT=ill) |
---|
194 | icb_alloc = icb_alloc + ill |
---|
195 | |
---|
196 | CALL mpp_sum ( 'icb_oce', icb_alloc ) |
---|
197 | IF( icb_alloc > 0 ) CALL ctl_warn('icb_alloc: allocation of arrays failed') |
---|
198 | ! |
---|
199 | END FUNCTION icb_alloc |
---|
200 | |
---|
201 | !!====================================================================== |
---|
202 | END MODULE icb_oce |
---|