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

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

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


Revision 1.4 - (hide annotations) (download)
Mon Oct 20 03:20:57 2014 UTC (10 years, 9 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65g
Changes since 1.3: +4 -1 lines
- ECCO_OPTIONS.h is needed when including ecco_cost.h, ecco.h
- AUTODIFF_OPTIONS.h is needed when including tamc.h, tamc_keys.h
- CTRL_OPTIONS.h is needed when including ctrl.h, etc

- pkg/seaice/seaice_cost*.F : clean up CPP brackets
- SEAICE_SIZE.h : replace ALLOW_AUTODIFF_TAMC with ALLOW_AUTODIFF to
  avoid needing AUTODIFF_OPTIONS.h anytime SEAICE_SIZE.h is included
  (it seems that THSICE_SIZE.h, PTRACERS_SIZE.h have the same issue...)

1 gforget 1.4 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_itd_pickup.F,v 1.3 2013/05/04 17:31:44 jmc Exp $
2 jmc 1.2 C $Name: $
3 heimbach 1.1
4     #include "SEAICE_OPTIONS.h"
5 gforget 1.4 #ifdef ALLOW_AUTODIFF
6     # include "AUTODIFF_OPTIONS.h"
7     #endif
8 heimbach 1.1
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 jmc 1.2 C | on the mean ice thickness and a standard decviation
30 heimbach 1.1 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 jmc 1.2 C local variables for picking up ITD from single category pickup file
84 heimbach 1.1 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 jmc 1.3 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 heimbach 1.1 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     IF (simpleSchemeFlag) THEN
105     C-- Put all ice into one bin:
106     C
107     DO bj=myByLo(myThid),myByHi(myThid)
108     DO bi=myBxLo(myThid),myBxHi(myThid)
109     DO j=1-OLy,sNy+OLy
110     DO i=1-OLx,sNx+OLx
111     AREAITD(i,j,1,bi,bj) = AREA(i,j,bi,bj)
112     HEFFITD(i,j,1,bi,bj) = HEFF(i,j,bi,bj)
113     HSNOWITD(i,j,1,bi,bj) = HSNOW(i,j,bi,bj)
114     ENDDO
115     ENDDO
116     ENDDO
117     ENDDO
118    
119     C---+-|--1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
120     ELSE
121     C-- Assume log-normal ITD:
122    
123     DO bj=myByLo(myThid),myByHi(myThid)
124     DO bi=myBxLo(myThid),myBxHi(myThid)
125     DO j=1-OLy,sNy+OLy
126     DO i=1-OLx,sNx+OLx
127     C
128     C initialize log-normal distribution
129 jmc 1.2 LND_mu = log(HEFF(i,j,bi,bj)/AREA(i,j,bi,bj))
130 heimbach 1.1 & - 0.5*LND_sigma*LND_sigma
131 jmc 1.2 LND_x(1) = 0.+LND_dx/2.
132 heimbach 1.1 C make thickness bins
133 jmc 1.2 DO LND_i=2,LND_iend
134     LND_x(LND_i)=LND_x(LND_i-1)+LND_dx
135     ENDDO
136 heimbach 1.1 C log-normal distribution:
137 jmc 1.2 DO LND_i=2,LND_iend
138     LND_tmp = log(LND_x(LND_i))-LND_mu
139     LND_pdf(LND_i)= 1.
140     & / (LND_x(LND_i)*LND_sigma*sqrt(2*3.1416))
141 heimbach 1.1 & * exp( -(LND_tmp*LND_tmp)
142     & / (2*LND_sigma*LND_sigma) )
143     & * AREA(i,j,bi,bj)
144 jmc 1.2 ENDDO
145 heimbach 1.1 C assign bins to ice thickness categories
146     k=1
147 jmc 1.2 DO LND_i=1,LND_iend
148     IF ( LND_x(LND_i).GT.Hlimit(k) ) k=k+1
149 heimbach 1.1 AREAITD(i,j,k,bi,bj) = AREAITD(i,j,k,bi,bj)
150     & + LND_pdf(LND_i)*LND_dx
151     HEFFITD(i,j,k,bi,bj) = HEFFITD(i,j,k,bi,bj)
152     & + LND_pdf(LND_i)*LND_x(LND_i)*LND_dx
153 jmc 1.2 ENDDO
154 heimbach 1.1 C
155     ENDDO
156 jmc 1.2 ENDDO
157 heimbach 1.1 ENDDO
158 jmc 1.2 ENDDO
159 heimbach 1.1
160     ENDIF
161    
162     C---+-|--1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
163 jmc 1.2 C finally sort into correct ice thickness category
164     C and compute bulk variables
165 heimbach 1.1 C (needed for dynamic solver at beginning of seaice_model.F)
166     DO bj=myByLo(myThid),myByHi(myThid)
167     DO bi=myBxLo(myThid),myBxHi(myThid)
168     CALL SEAICE_ITD_REDIST( bi, bj, dummyTime, myIter, myThid)
169     CALL SEAICE_ITD_SUM( bi, bj, dummyTime, myIter, myThid)
170     ENDDO
171     ENDDO
172    
173     C---+-|--1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
174     #endif /* SEAICE_ITD */
175     RETURN
176 jmc 1.2 END

  ViewVC Help
Powered by ViewVC 1.1.22