1 | MODULE isfload |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE isfload *** |
---|
4 | !! isfload module : compute ice shelf load (needed for the hpg) |
---|
5 | !!====================================================================== |
---|
6 | !! History : 4.1 ! 2019-09 (P. Mathiot) original code |
---|
7 | !!---------------------------------------------------------------------- |
---|
8 | |
---|
9 | !!---------------------------------------------------------------------- |
---|
10 | !! isfload : compute ice shelf load |
---|
11 | !!---------------------------------------------------------------------- |
---|
12 | |
---|
13 | USE isf ! ice shelf variables |
---|
14 | USE dom_oce ! vertical scale factor |
---|
15 | USE in_out_manager ! |
---|
16 | USE eosbn2 ! eos routine |
---|
17 | USE lib_mpp ! ctl_stop routine |
---|
18 | |
---|
19 | IMPLICIT NONE |
---|
20 | |
---|
21 | PRIVATE |
---|
22 | |
---|
23 | PUBLIC isf_load |
---|
24 | |
---|
25 | CONTAINS |
---|
26 | |
---|
27 | SUBROUTINE isf_load ( pisfload ) |
---|
28 | !!-------------------------------------------------------------------- |
---|
29 | !! *** SUBROUTINE isf_load *** |
---|
30 | !! |
---|
31 | !! ** Purpose : compute the ice shelf load |
---|
32 | !! |
---|
33 | !!-------------------------------------------------------------------- |
---|
34 | !!-------------------------- OUT ------------------------------------- |
---|
35 | REAL(wp), DIMENSION(jpi,jpj), INTENT( out) :: pisfload |
---|
36 | !!-------------------------- IN ------------------------------------- |
---|
37 | !!---------------------------------------------------------------------- |
---|
38 | ! |
---|
39 | ! quality test: ice shelf in a stratify/uniform ocean should not drive any flow. |
---|
40 | ! the smaller the residual flow is, the better it is. |
---|
41 | ! |
---|
42 | ! ice shelf cavity |
---|
43 | SELECT CASE ( cn_isfload ) |
---|
44 | CASE ( 'isomip' ) |
---|
45 | CALL isf_load_isomip ( pisfload ) |
---|
46 | CASE DEFAULT |
---|
47 | CALL ctl_stop('STOP','method cn_isfload to compute ice shelf load does not exist (isomip), check your namelist') |
---|
48 | END SELECT |
---|
49 | ! |
---|
50 | END SUBROUTINE isf_load |
---|
51 | |
---|
52 | SUBROUTINE isf_load_isomip( pisfload ) |
---|
53 | !!-------------------------------------------------------------------- |
---|
54 | !! *** SUBROUTINE isf_load *** |
---|
55 | !! |
---|
56 | !! ** Purpose : compute the ice shelf load |
---|
57 | !! |
---|
58 | !! ** Method : The ice shelf is assumed to be in hydro static equilibrium |
---|
59 | !! in water at -1.9 C and 34.4 PSU. Weight of the ice shelf is |
---|
60 | !! integrated from top to bottom. |
---|
61 | !! |
---|
62 | !!-------------------------------------------------------------------- |
---|
63 | !!-------------------------- OUT ------------------------------------- |
---|
64 | REAL(wp), DIMENSION(jpi,jpj), INTENT( out) :: pisfload |
---|
65 | !!-------------------------- IN ------------------------------------- |
---|
66 | !!-------------------------------------------------------------------- |
---|
67 | INTEGER :: ji, jj, jk |
---|
68 | INTEGER :: ikt |
---|
69 | REAL(wp) :: znad ! |
---|
70 | REAL(wp), DIMENSION(jpi,jpj) :: zrhdtop_isf ! water density displaced by the ice shelf (at the interface) |
---|
71 | REAL(wp), DIMENSION(jpi,jpj,jpts) :: zts_top ! water properties displaced by the ice shelf |
---|
72 | REAL(wp), DIMENSION(jpi,jpj,jpk) :: zrhd ! water density displaced by the ice shelf |
---|
73 | !!---------------------------------------------------------------------- |
---|
74 | ! |
---|
75 | ! print |
---|
76 | IF(lwp) WRITE(numout,*) |
---|
77 | IF(lwp) WRITE(numout,*) ' ice shelf case: set the ice-shelf load following isomip case' |
---|
78 | ! |
---|
79 | znad = 1._wp !- To use density and not density anomaly |
---|
80 | ! |
---|
81 | ! !- assume water displaced by the ice shelf is at T=-1.9 and S=34.4 (rude) |
---|
82 | zts_top(:,:,jp_tem) = -1.9_wp ; zts_top(:,:,jp_sal) = 34.4_wp |
---|
83 | ! |
---|
84 | DO jk = 1, jpk !- compute density of the water displaced by the ice shelf |
---|
85 | CALL eos( zts_top(:,:,:), gdept_n(:,:,jk), zrhd(:,:,jk) ) |
---|
86 | END DO |
---|
87 | ! |
---|
88 | ! !- compute rhd at the ice/oce interface (ice shelf side) |
---|
89 | CALL eos( zts_top , risfdep, zrhdtop_isf ) |
---|
90 | ! |
---|
91 | ! !- Surface value + ice shelf gradient |
---|
92 | risfload(:,:) = 0._wp ! compute pressure due to ice shelf load |
---|
93 | DO jj = 1, jpj ! (used to compute hpgi/j for all the level from 1 to miku/v) |
---|
94 | DO ji = 1, jpi ! divided by 2 later |
---|
95 | ikt = mikt(ji,jj) |
---|
96 | ! |
---|
97 | IF ( ikt > 1 ) THEN |
---|
98 | ! |
---|
99 | ! top layer of the ice shelf |
---|
100 | risfload(ji,jj) = risfload(ji,jj) + (znad + zrhd(ji,jj,1) ) * e3w_n(ji,jj,1) |
---|
101 | ! |
---|
102 | ! core layers of the ice shelf |
---|
103 | DO jk = 2, ikt-1 |
---|
104 | risfload(ji,jj) = risfload(ji,jj) + (2._wp * znad + zrhd(ji,jj,jk-1) + zrhd(ji,jj,jk)) * e3w_n(ji,jj,jk) |
---|
105 | END DO |
---|
106 | ! |
---|
107 | ! deepest part of the ice shelf (between deepest T point and ice/ocean interface |
---|
108 | risfload(ji,jj) = risfload(ji,jj) + (2._wp * znad + zrhdtop_isf(ji,jj) + zrhd(ji,jj,ikt-1)) & |
---|
109 | & * ( risfdep(ji,jj) - gdept_n(ji,jj,ikt-1) ) |
---|
110 | ! |
---|
111 | END IF |
---|
112 | END DO |
---|
113 | END DO |
---|
114 | ! |
---|
115 | END SUBROUTINE isf_load_isomip |
---|
116 | |
---|
117 | END MODULE isfload |
---|