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 branches/2014/dev_r4650_UKMO11_restart_functionality/NEMOGCM/NEMO/OPA_SRC/ICB – NEMO

source: branches/2014/dev_r4650_UKMO11_restart_functionality/NEMOGCM/NEMO/OPA_SRC/ICB/icb_oce.F90 @ 5208

Last change on this file since 5208 was 5208, checked in by davestorkey, 9 years ago

Merge in changes from trunk up to 5021.

File size: 13.6 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
40   IMPLICIT NONE
41   PUBLIC
42
43   PUBLIC   icb_alloc   ! routine called by icb_init in icbini.F90 module
44
45INTEGER, PUBLIC, PARAMETER ::   nclasses = 10   !: Number of icebergs classes   
46   INTEGER, PUBLIC, PARAMETER ::   nkounts  =  3   !: Number of integers combined for unique naming
47
48   TYPE, PUBLIC ::   icebergs_gridded   !: various icebergs properties on model grid
49      REAL(wp), DIMENSION(:,:)  , ALLOCATABLE ::   calving         ! Calving mass rate  (into stored ice)         [kg/s]
50      REAL(wp), DIMENSION(:,:)  , ALLOCATABLE ::   calving_hflx    ! Calving heat flux [heat content of calving]  [W/m2]
51      REAL(wp), DIMENSION(:,:)  , ALLOCATABLE ::   floating_melt   ! Net melting rate to icebergs + bits      [kg/s/m^2]
52      INTEGER , DIMENSION(:,:)  , ALLOCATABLE ::   maxclass        ! maximum class number at calving source point
53      REAL(wp), DIMENSION(:,:)  , ALLOCATABLE ::   tmp             ! Temporary work space
54      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   stored_ice      ! Accumulated ice mass flux at calving locations [kg]
55      REAL(wp), DIMENSION(:,:)  , ALLOCATABLE ::   stored_heat     ! Heat content of stored ice                      [J]
56   END TYPE icebergs_gridded
57
58   TYPE, PUBLIC ::   point              !: properties of an individual iceberg (position, mass, size, etc...)
59      INTEGER  ::   year
60      REAL(wp) ::   xi , yj                                              ! iceberg coordinates in the (i,j) referential (global)
61      REAL(wp) ::   e1 , e2                                              ! horizontal scale factors at the iceberg position
62      REAL(wp) ::   lon, lat, day                                        ! geographic position
63      REAL(wp) ::   mass, thickness, width, length, uvel, vvel           ! iceberg physical properties
64      REAL(wp) ::   uo, vo, ui, vi, ua, va, ssh_x, ssh_y, sst, cn, hi    ! properties of iceberg environment
65      REAL(wp) ::   mass_of_bits, heat_density
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 ::   uo_e, vo_e
89   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   ff_e, tt_e, fr_e, hicth
90   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   ua_e, va_e
91   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   ssh_e
92#if defined key_lim2 || defined key_lim3 || defined key_cice
93   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   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   INTEGER , PUBLIC ::   nn_sample_rate                  !: Timesteps between sampling of position for trajectory storage
115   INTEGER , PUBLIC ::   nn_verbose_write                !: timesteps between verbose messages
116   REAL(wp), PUBLIC ::   rn_rho_bergs                    !: Density of icebergs
117   REAL(wp), PUBLIC ::   rn_LoW_ratio                    !: Initial ratio L/W for newly calved icebergs
118   REAL(wp), PUBLIC ::   rn_bits_erosion_fraction        !: Fraction of erosion melt flux to divert to bergy bits
119   REAL(wp), PUBLIC ::   rn_sicn_shift                   !: Shift of sea-ice concentration in erosion flux modulation (0<sicn_shift<1)
120   LOGICAL , PUBLIC ::   ln_operator_splitting           !: Use first order operator splitting for thermodynamics
121   LOGICAL , PUBLIC ::   ln_passive_mode                 !: iceberg - ocean decoupling
122   LOGICAL , PUBLIC ::   ln_time_average_weight          !: Time average the weight on the ocean    !!gm I don't understand that !
123   REAL(wp), PUBLIC ::   rn_speed_limit                  !: CFL speed limit for a berg
124   !
125   !                                     ! Mass thresholds between iceberg classes [kg]
126   REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_initial_mass      ! Fraction of calving to apply to this class [non-dim]
127   REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_distribution      ! Ratio between effective and real iceberg mass (non-dim)
128   REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_mass_scaling      ! Total thickness of newly calved bergs [m]
129   REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_initial_thickness !  Single instance of an icebergs type initialised in icebergs_init and updated in icebergs_run
130   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   src_calving, src_calving_hflx    !: accumulate input ice
131   INTEGER , PUBLIC             , SAVE                     ::   numicb                           !: iceberg IO
132   INTEGER , PUBLIC             , SAVE, DIMENSION(nkounts) ::   num_bergs                        !: iceberg counter
133   INTEGER , PUBLIC             , SAVE                     ::   nicbdi, nicbei, nicbdj, nicbej   !: processor bounds
134   REAL(wp), PUBLIC             , SAVE                     ::   ricb_left, ricb_right            !: cyclical bounds
135   INTEGER , PUBLIC             , SAVE                     ::   nicbpack                         !: packing integer
136   INTEGER , PUBLIC             , SAVE                     ::   nktberg, nknberg                 !: helpers
137   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   nicbfldpts                       !: nfold packed points
138   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   nicbflddest                      !: nfold destination proc
139   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   nicbfldproc                      !: nfold destination proc
140   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   nicbfldnsend                     !: nfold number of bergs to send to nfold neighbour
141   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   nicbfldexpect                    !: nfold expected number of bergs
142   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   nicbfldreq                       !: nfold message handle (immediate send)
143
144   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   :: griddata                           !: work array for icbrst
145
146   !!----------------------------------------------------------------------
147   !! NEMO/OPA 3.3 , NEMO Consortium (2011)
148   !! $Id: sbc_oce.F90 3340 2012-04-02 11:05:35Z sga $
149   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
150   !!----------------------------------------------------------------------
151CONTAINS
152   
153   INTEGER FUNCTION icb_alloc()
154      !!----------------------------------------------------------------------
155      !!                ***  ROUTINE icb_alloc  ***
156      !!----------------------------------------------------------------------
157      INTEGER ::   ill
158      !!----------------------------------------------------------------------
159      !
160      icb_alloc = 0
161      ALLOCATE( berg_grid, STAT=ill )
162      icb_alloc = icb_alloc + ill
163      ALLOCATE( berg_grid%calving    (jpi,jpj) , berg_grid%calving_hflx (jpi,jpj)          ,   &
164         &      berg_grid%stored_heat(jpi,jpj) , berg_grid%floating_melt(jpi,jpj)          ,   &
165         &      berg_grid%maxclass   (jpi,jpj) , berg_grid%stored_ice   (jpi,jpj,nclasses) ,   &
166         &      berg_grid%tmp        (jpi,jpj) , STAT=ill)
167      icb_alloc = icb_alloc + ill
168      !
169      ! expanded arrays for bilinear interpolation
170      ALLOCATE( uo_e(0:jpi+1,0:jpj+1) , ua_e(0:jpi+1,0:jpj+1) ,   &
171         &      vo_e(0:jpi+1,0:jpj+1) , va_e(0:jpi+1,0:jpj+1) ,   &
172#if defined key_lim2 || defined key_lim3 || defined key_cice
173         &      ui_e(0:jpi+1,0:jpj+1) ,                            &
174         &      vi_e(0:jpi+1,0:jpj+1) ,                            &
175#endif
176         &      ff_e(0:jpi+1,0:jpj+1) , fr_e(0:jpi+1,0:jpj+1)  ,   &
177         &      tt_e(0:jpi+1,0:jpj+1) , ssh_e(0:jpi+1,0:jpj+1) ,   &
178         &      hicth(0:jpi+1,0:jpj+1),                            &
179         &      first_width(nclasses) , first_length(nclasses) ,   &
180         &      src_calving (jpi,jpj) ,                            &
181         &      src_calving_hflx(jpi,jpj) , STAT=ill)
182      icb_alloc = icb_alloc + ill
183
184      ALLOCATE( nicbfldpts(jpi) , nicbflddest(jpi) , nicbfldproc(jpni) , &
185         &      nicbfldnsend(jpni), nicbfldexpect(jpni) , nicbfldreq(jpni), STAT=ill)
186      icb_alloc = icb_alloc + ill
187
188      ALLOCATE( griddata(jpi,jpj,1), STAT=ill )
189      icb_alloc = icb_alloc + ill
190
191      IF( lk_mpp        )   CALL mpp_sum ( icb_alloc )
192      IF( icb_alloc > 0 )   CALL ctl_warn('icb_alloc: allocation of arrays failed')
193      !
194   END FUNCTION icb_alloc
195
196   !!======================================================================
197END MODULE icb_oce
Note: See TracBrowser for help on using the repository browser.