/[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.1 - (show annotations) (download)
Mon Oct 22 21:14:07 2012 UTC (12 years, 9 months ago) by heimbach
Branch: MAIN
Step 1 of merging ice-thickness distribution (ITD) code from
MITgcm_contrib/torge/itd/code/ to main repository
(author: Torge Martin)

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

  ViewVC Help
Powered by ViewVC 1.1.22