/[MITgcm]/MITgcm/pkg/seaice/seaice_itd_pickup.F
ViewVC logotype

Contents of /MITgcm/pkg/seaice/seaice_itd_pickup.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.5 - (show annotations) (download)
Fri Apr 29 14:28:38 2016 UTC (9 years, 2 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65w, HEAD
Changes since 1.4: +24 -10 lines
fix picking up from a single category model by re-initialising
heff/area/hsnowITD = 0. for safety

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_itd_pickup.F,v 1.4 2014/10/20 03:20:57 gforget Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5 #ifdef ALLOW_AUTODIFF
6 # include "AUTODIFF_OPTIONS.h"
7 #endif
8
9 C !ROUTINE: SEAICE_ITD_PICKUP
10
11 C !INTERFACE: ==========================================================
12 SUBROUTINE SEAICE_ITD_PICKUP(
13 I myIter, myThid )
14
15 C !DESCRIPTION: \bv
16 C *===========================================================*
17 C | SUBROUTINE SEAICE_ITD_PICKUP
18 C | o called in case pickup file does not contain
19 C | ITD variables but mean ice thickness and concentration
20 C |
21 C | o choose between two schemes:
22 C |
23 C | a) a simple scheme where the mean values are just put
24 C | into the first ITD category and then redustributed
25 C | into the correct category by SEAICE_ITD_REDIST
26 C | -> simpleSchemeFlag = .TRUE.
27 C |
28 C | b) a scheme that assumes a log-normal distribution based
29 C | on the mean ice thickness and a standard decviation
30 C | of LND_sigma=0.25
31 C | -> simpleSchemeFlag = .FALSE.
32 C |
33 C | Torge Martin, Mai 2012, torge@mit.edu
34 C *===========================================================*
35 C \ev
36
37 C !USES: ===============================================================
38 IMPLICIT NONE
39
40 C === Global variables needed ===
41 C AREA :: total sea ice area fraction
42 C HEFF :: mean in-situ sea ice thickness
43 C HSNOW :: mean in-situ snow layer depth
44 C
45 C === Global variables to be changed ===
46 C AREAITD :: sea ice area by category
47 C HEFFITD :: sea ice thickness by category
48 C HSNOWITD :: snow thickness by category
49 C
50 #include "SIZE.h"
51 #include "EEPARAMS.h"
52 #include "PARAMS.h"
53 #include "GRID.h"
54 #include "SEAICE_SIZE.h"
55 #include "SEAICE_PARAMS.h"
56 #include "SEAICE.h"
57
58 #ifdef ALLOW_AUTODIFF_TAMC
59 # include "tamc.h"
60 #endif
61
62 C !INPUT PARAMETERS: ===================================================
63 C === Routine arguments ===
64 C myIter :: iteration number
65 C myThid :: Thread no. that called this routine.
66 INTEGER myIter
67 INTEGER myThid
68 CEndOfInterface
69
70 #ifdef SEAICE_ITD
71
72 C !LOCAL VARIABLES: ====================================================
73 C === Local variables ===
74 C i,j,bi,bj,k :: Loop counters
75 C nITD :: number of sea ice thickness categories
76 C
77 INTEGER i, j, bi, bj, k
78 #ifdef ALLOW_AUTODIFF_TAMC
79 INTEGER itmpkey
80 #endif /* ALLOW_AUTODIFF_TAMC */
81 _RL dummyTime
82
83 C local variables for picking up ITD from single category pickup file
84 INTEGER LND_i, LND_iend
85 C parameters for log-normal distribution (LND)
86 _RL LND_sigma, LND_mu
87 PARAMETER(LND_sigma=0.25)
88 _RL LND_dx
89 _RL LND_tmp
90 C bin width of distribution
91 PARAMETER( LND_iend = 1000 )
92 PARAMETER( LND_dx = 100.D0 / LND_iend )
93 c PARAMETER(LND_dx=0.1)
94 c PARAMETER(LND_iend=INT(100./LND_dx))
95 _RL LND_x (LND_iend)
96 _RL LND_pdf(LND_iend)
97 C flag for pickup scheme
98 LOGICAL simpleSchemeFlag
99
100 simpleSchemeFlag = .TRUE.
101 dummyTime = 1.0
102
103 C---+-|--1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
104 C reset ITD variables to zero for safety
105 DO k = 1, nITD
106 DO bj=myByLo(myThid),myByHi(myThid)
107 DO bi=myBxLo(myThid),myBxHi(myThid)
108 DO j=1-OLy,sNy+OLy
109 DO i=1-OLx,sNx+OLx
110 AREAITD(i,j,k,bi,bj) = 0. _d 0
111 HEFFITD(i,j,k,bi,bj) = 0. _d 0
112 HSNOWITD(i,j,k,bi,bj) = 0. _d 0
113 ENDDO
114 ENDDO
115 ENDDO
116 ENDDO
117 ENDDO
118 IF (simpleSchemeFlag) THEN
119 C-- Put all ice into one bin:
120 C
121 DO bj=myByLo(myThid),myByHi(myThid)
122 DO bi=myBxLo(myThid),myBxHi(myThid)
123 DO j=1-OLy,sNy+OLy
124 DO i=1-OLx,sNx+OLx
125 AREAITD(i,j,1,bi,bj) = AREA(i,j,bi,bj)
126 HEFFITD(i,j,1,bi,bj) = HEFF(i,j,bi,bj)
127 HSNOWITD(i,j,1,bi,bj) = HSNOW(i,j,bi,bj)
128 ENDDO
129 ENDDO
130 ENDDO
131 ENDDO
132
133 C---+-|--1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
134 ELSE
135 C-- Assume log-normal ITD:
136
137 DO bj=myByLo(myThid),myByHi(myThid)
138 DO bi=myBxLo(myThid),myBxHi(myThid)
139 DO j=1-OLy,sNy+OLy
140 DO i=1-OLx,sNx+OLx
141 C
142 C initialize log-normal distribution
143 LND_mu = log(HEFF(i,j,bi,bj)/AREA(i,j,bi,bj))
144 & - 0.5*LND_sigma*LND_sigma
145 LND_x(1) = 0.+LND_dx/2.
146 C make thickness bins
147 DO LND_i=2,LND_iend
148 LND_x(LND_i)=LND_x(LND_i-1)+LND_dx
149 ENDDO
150 C log-normal distribution:
151 DO LND_i=2,LND_iend
152 LND_tmp = log(LND_x(LND_i))-LND_mu
153 LND_pdf(LND_i)= 1.
154 & / (LND_x(LND_i)*LND_sigma*sqrt(2*3.1416))
155 & * exp( -(LND_tmp*LND_tmp)
156 & / (2*LND_sigma*LND_sigma) )
157 & * AREA(i,j,bi,bj)
158 ENDDO
159 C assign bins to ice thickness categories
160 k=1
161 DO LND_i=1,LND_iend
162 IF ( LND_x(LND_i).GT.Hlimit(k) ) k=k+1
163 AREAITD(i,j,k,bi,bj) = AREAITD(i,j,k,bi,bj)
164 & + LND_pdf(LND_i)*LND_dx
165 HEFFITD(i,j,k,bi,bj) = HEFFITD(i,j,k,bi,bj)
166 & + LND_pdf(LND_i)*LND_x(LND_i)*LND_dx
167 ENDDO
168 C
169 ENDDO
170 ENDDO
171 ENDDO
172 ENDDO
173
174 ENDIF
175
176 C---+-|--1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
177 C finally sort into correct ice thickness category
178 C and compute bulk variables
179 C (needed for dynamic solver at beginning of seaice_model.F)
180 DO bj=myByLo(myThid),myByHi(myThid)
181 DO bi=myBxLo(myThid),myBxHi(myThid)
182 CALL SEAICE_ITD_REDIST( bi, bj, dummyTime, myIter, myThid)
183 CALL SEAICE_ITD_SUM( bi, bj, dummyTime, myIter, myThid)
184 ENDDO
185 ENDDO
186
187 C---+-|--1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
188 #endif /* SEAICE_ITD */
189 RETURN
190 END

  ViewVC Help
Powered by ViewVC 1.1.22