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 trunk/NEMOGCM/NEMO/OPA_SRC/ICB – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/ICB/icb_oce.F90 @ 3841

Last change on this file since 3841 was 3614, checked in by acc, 11 years ago

Branch dev_NOC_2012_r3555. #1006. Step 6: Minor code changes and updated namelists to enable successful SETTE testing

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