/[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.2 - (show annotations) (download)
Tue Oct 23 13:20:49 2012 UTC (12 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64a, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64c, checkpoint64g, checkpoint64f
Changes since 1.1: +22 -21 lines
- remove statement that prevents S/R to compile with pgf77
- remove tab ; add CVS header and name.

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

  ViewVC Help
Powered by ViewVC 1.1.22