New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
icb_oce.F90 in NEMO/branches/2020/dev_r13648_ASINTER-04_laurent_bulk_ice/src/OCE/ICB – NEMO

source: NEMO/branches/2020/dev_r13648_ASINTER-04_laurent_bulk_ice/src/OCE/ICB/icb_oce.F90 @ 14038

Last change on this file since 14038 was 14038, checked in by laurent, 3 years ago

Catch up with trunk at rev r14037

  • Property svn:keywords set to Id
File size: 15.0 KB
Line 
1MODULE 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 , zk                                              ! iceberg coordinates in the (i,j) referential (global) and deepest level affected
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) ::   ssu, ssv, ui, vi, ua, va, ssh_x, ssh_y, sst, sss, cn, hi  ! properties of iceberg environment
64      REAL(wp) ::   mass_of_bits, heat_density
65      INTEGER  ::   kb                                                   ! icb bottom level
66   END TYPE point
67
68   TYPE, PUBLIC ::   iceberg            !: linked list defining all the icebergs present in the model domain
69      TYPE(iceberg), POINTER      ::   prev=>NULL(), next=>NULL()   ! pointers to previous and next unique icebergs in linked list
70      INTEGER, DIMENSION(nkounts) ::   number                       ! variables which do not change for this iceberg
71      REAL(wp)                    ::   mass_scaling                 !    -        -            -                - 
72      TYPE(point), POINTER        ::   current_point => NULL()      ! variables which change with time are held in a separate type
73   END TYPE iceberg
74
75
76   TYPE(icebergs_gridded), POINTER ::   berg_grid                 !: master instance of gridded iceberg type
77   TYPE(iceberg)         , POINTER ::   first_berg => NULL()      !: master instance of linked list iceberg type
78
79   !                                                             !!! parameters controlling iceberg characteristics and modelling
80   REAL(wp)                            ::   berg_dt                   !: Time-step between iceberg CALLs (should make adaptive?)
81   REAL(wp), DIMENSION(:), ALLOCATABLE ::   first_width, first_length !:
82   LOGICAL                             ::   l_restarted_bergs=.FALSE.  ! Indicate whether we read state from a restart or not
83   !                                                               ! arbitrary numbers for diawri entry
84   REAL(wp), DIMENSION(nclasses), PUBLIC ::   class_num=(/ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10 /)
85
86   ! Extra arrays with bigger halo, needed when interpolating forcing onto iceberg position
87   ! particularly for MPP when iceberg can lie inside T grid but outside U, V, or f grid
88   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   ssu_e, ssv_e
89   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   sst_e, sss_e, fr_e
90   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   ua_e, va_e
91   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   ssh_e
92   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   tmask_e, umask_e, vmask_e
93   REAl(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   rlon_e, rlat_e, ff_e
94   REAl(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::   uoce_e, voce_e, toce_e, e3t_e
95   !
96#if defined key_si3 || defined key_cice
97   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   hi_e, ui_e, vi_e
98#endif
99
100   !!gm almost all those PARAM ARE defined in NEMO
101   REAL(wp), PUBLIC, PARAMETER :: pp_rho_ice      = 916.7_wp   !: Density of fresh ice   @ 0oC [kg/m^3]
102   REAL(wp), PUBLIC, PARAMETER :: pp_rho_water    = 999.8_wp   !: Density of fresh water @ 0oC [kg/m^3]
103   REAL(wp), PUBLIC, PARAMETER :: pp_rho_air      = 1.1_wp     !: Density of air         @ 0oC [kg/m^3]
104   REAL(wp), PUBLIC, PARAMETER :: pp_rho_seawater = 1025._wp   !: Approx. density of surface sea water @ 0oC [kg/m^3]
105   !!gm end
106   REAL(wp), PUBLIC, PARAMETER :: pp_Cd_av = 1.3_wp      !: (Vertical) Drag coefficient between bergs and atmos
107   REAL(wp), PUBLIC, PARAMETER :: pp_Cd_ah = 0.0055_wp   !: (lateral ) Drag coefficient between bergs and atmos
108   REAL(wp), PUBLIC, PARAMETER :: pp_Cd_wv = 0.9_wp      !: (Vertical) Drag coefficient between bergs and ocean
109   REAL(wp), PUBLIC, PARAMETER :: pp_Cd_wh = 0.0012_wp   !: (lateral ) Drag coefficient between bergs and ocean
110   REAL(wp), PUBLIC, PARAMETER :: pp_Cd_iv = 0.9_wp      !: (Vertical) Drag coefficient between bergs and sea-ice
111!TOM> no horizontal drag for sea ice! real, PARAMETER :: pp_Cd_ih=0.0012 ! (lateral) Drag coeff. between bergs and sea-ice
112
113   !                                                         !!* namberg namelist parameters (and defaults) **
114   LOGICAL , PUBLIC ::   ln_bergdia                      !: Calculate budgets
115   INTEGER , PUBLIC ::   nn_verbose_level                !: Turn on debugging when level > 0
116   INTEGER , PUBLIC ::   nn_test_icebergs                !: Create icebergs in absence of a restart file from the supplied class nb
117   REAL(wp), PUBLIC, DIMENSION(4) ::   rn_test_box       !: lon1,lon2,lat1,lat2 box to create them in
118   LOGICAL , PUBLIC ::   ln_use_calving                  !: Force use of calving data even with nn_test_icebergs > 0
119                                                         !  (default is not to use calving data with test bergs)
120   INTEGER , PUBLIC ::   nn_sample_rate                  !: Timesteps between sampling of position for trajectory storage
121   INTEGER , PUBLIC ::   nn_verbose_write                !: timesteps between verbose messages
122   REAL(wp), PUBLIC ::   rn_rho_bergs                    !: Density of icebergs
123   REAL(wp), PUBLIC ::   rho_berg_1_oce                  !: convertion factor (thickness to draft) (rn_rho_bergs/pp_rho_seawater)
124   REAL(wp), PUBLIC ::   rn_LoW_ratio                    !: Initial ratio L/W for newly calved icebergs
125   REAL(wp), PUBLIC ::   rn_bits_erosion_fraction        !: Fraction of erosion melt flux to divert to bergy bits
126   REAL(wp), PUBLIC ::   rn_sicn_shift                   !: Shift of sea-ice concentration in erosion flux modulation (0<sicn_shift<1)
127   LOGICAL , PUBLIC ::   ln_operator_splitting           !: Use first order operator splitting for thermodynamics
128   LOGICAL , PUBLIC ::   ln_passive_mode                 !: iceberg - ocean decoupling
129   LOGICAL , PUBLIC ::   ln_time_average_weight          !: Time average the weight on the ocean    !!gm I don't understand that !
130   REAL(wp), PUBLIC ::   rn_speed_limit                  !: CFL speed limit for a berg
131   LOGICAL , PUBLIC ::   ln_M2016, ln_icb_grd            !: use Nacho's Merino 2016 work
132   !
133   ! restart
134   CHARACTER(len=256), PUBLIC :: cn_icbrst_indir , cn_icbrst_in  !:  in: restart directory, restart name
135   CHARACTER(len=256), PUBLIC :: cn_icbrst_outdir, cn_icbrst_out !: out: restart directory, restart name
136   !
137   !                                     ! Mass thresholds between iceberg classes [kg]
138   REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_initial_mass      ! Fraction of calving to apply to this class [non-dim]
139   REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_distribution      ! Ratio between effective and real iceberg mass (non-dim)
140   REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_mass_scaling      ! Total thickness of newly calved bergs [m]
141   REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_initial_thickness !  Single instance of an icebergs type initialised in icebergs_init and updated in icebergs_run
142   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   src_calving, src_calving_hflx    !: accumulate input ice
143   INTEGER , PUBLIC             , SAVE                     ::   micbkb                           !: deepest level affected by icebergs
144   INTEGER , PUBLIC             , SAVE                     ::   numicb                           !: iceberg IO
145   INTEGER , PUBLIC             , SAVE, DIMENSION(nkounts) ::   num_bergs                        !: iceberg counter
146   INTEGER , PUBLIC             , SAVE                     ::   nicbdi, nicbei, nicbdj, nicbej   !: processor bounds
147   REAL(wp), PUBLIC             , SAVE                     ::   ricb_left, ricb_right            !: cyclical bounds
148   INTEGER , PUBLIC             , SAVE                     ::   nicbpack                         !: packing integer
149   INTEGER , PUBLIC             , SAVE                     ::   nktberg, nknberg                 !: helpers
150   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   nicbfldpts                       !: nfold packed points
151   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   nicbflddest                      !: nfold destination proc
152   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   nicbfldproc                      !: nfold destination proc
153   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   nicbfldnsend                     !: nfold number of bergs to send to nfold neighbour
154   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   nicbfldexpect                    !: nfold expected number of bergs
155   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   nicbfldreq                       !: nfold message handle (immediate send)
156   !!----------------------------------------------------------------------
157   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
158   !! $Id$
159   !! Software governed by the CeCILL license (see ./LICENSE)
160   !!----------------------------------------------------------------------
161CONTAINS
162   
163   INTEGER FUNCTION icb_alloc()
164      !!----------------------------------------------------------------------
165      !!                ***  ROUTINE icb_alloc  ***
166      !!----------------------------------------------------------------------
167      INTEGER ::   ill
168      !!----------------------------------------------------------------------
169      !
170      icb_alloc = 0
171      ALLOCATE( berg_grid, STAT=ill )
172      icb_alloc = icb_alloc + ill
173      ALLOCATE( berg_grid%calving    (jpi,jpj) , berg_grid%calving_hflx (jpi,jpj)          ,   &
174         &      berg_grid%stored_heat(jpi,jpj) , berg_grid%floating_melt(jpi,jpj)          ,   &
175         &      berg_grid%maxclass   (jpi,jpj) , berg_grid%stored_ice   (jpi,jpj,nclasses) ,   &
176         &      berg_grid%tmp        (jpi,jpj) , STAT=ill)
177      icb_alloc = icb_alloc + ill
178      !
179      ! expanded arrays for bilinear interpolation
180      ALLOCATE( ssu_e(0:jpi+1,0:jpj+1) , ua_e(0:jpi+1,0:jpj+1) ,   &
181         &      ssv_e(0:jpi+1,0:jpj+1) , va_e(0:jpi+1,0:jpj+1) ,   &
182#if defined key_si3 || defined key_cice
183         &      ui_e(0:jpi+1,0:jpj+1) ,                            &
184         &      vi_e(0:jpi+1,0:jpj+1) ,                            &
185         &      hi_e(0:jpi+1,0:jpj+1) ,                            &
186#endif
187         &      fr_e(0:jpi+1,0:jpj+1) ,                            &
188         &      sst_e(0:jpi+1,0:jpj+1) , ssh_e(0:jpi+1,0:jpj+1) ,  &
189         &      sss_e(0:jpi+1,0:jpj+1) ,                           & 
190         &      first_width(nclasses) , first_length(nclasses) ,   &
191         &      src_calving (jpi,jpj) ,                            &
192         &      src_calving_hflx(jpi,jpj) , STAT=ill)
193      icb_alloc = icb_alloc + ill
194
195      IF ( ln_M2016 ) THEN
196         ALLOCATE( uoce_e(0:jpi+1,0:jpj+1,jpk), voce_e(0:jpi+1,0:jpj+1,jpk), &
197            &      toce_e(0:jpi+1,0:jpj+1,jpk), e3t_e(0:jpi+1,0:jpj+1,jpk) , STAT=ill )
198         icb_alloc = icb_alloc + ill
199      END IF
200      !
201      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), &
202         &      rlon_e(0:jpi+1,0:jpj+1) , rlat_e(0:jpi+1,0:jpj+1) , ff_e(0:jpi+1,0:jpj+1)   , STAT=ill)
203      icb_alloc = icb_alloc + ill
204
205      ALLOCATE( nicbfldpts(jpi) , nicbflddest(jpi) , nicbfldproc(jpni) , &
206         &      nicbfldnsend(jpni), nicbfldexpect(jpni) , nicbfldreq(jpni), STAT=ill)
207      icb_alloc = icb_alloc + ill
208
209      CALL mpp_sum ( 'icb_oce', icb_alloc )
210      IF( icb_alloc > 0 )   CALL ctl_warn('icb_alloc: allocation of arrays failed')
211      !
212   END FUNCTION icb_alloc
213
214   !!======================================================================
215END MODULE icb_oce
Note: See TracBrowser for help on using the repository browser.