/[MITgcm]/MITgcm/verification/tutorial_global_oce_latlon/code/ptracers_forcing_surf.F
ViewVC logotype

Contents of /MITgcm/verification/tutorial_global_oce_latlon/code/ptracers_forcing_surf.F

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


Revision 1.1 - (show annotations) (download)
Fri Jul 14 20:35:22 2006 UTC (17 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58q_post, checkpoint59a, checkpoint59, checkpoint58o_post, checkpoint58y_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58m_post
copied from global_ocean.90x40x15 (now becomes tutorial_global_oce_latlon)

1 C $Header: /u/gcmpack/MITgcm/verification/global_ocean.90x40x15/code/ptracers_forcing_surf.F,v 1.2 2006/05/24 01:16:32 jmc Exp $
2 C $Name: $
3
4 #include "PTRACERS_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: PTRACERS_FORCING_SURF
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE PTRACERS_FORCING_SURF(
11 I bi, bj, iMin, iMax, jMin, jMax,
12 I myTime,myIter,myThid )
13
14 C !DESCRIPTION:
15 C Precomputes surface forcing term for pkg/ptracers.
16 C Precomputation is needed because of non-local KPP transport term,
17 C routine KPP_TRANSPORT_PTR.
18
19 C !USES: ===============================================================
20 IMPLICIT NONE
21 #include "SIZE.h"
22 #include "EEPARAMS.h"
23 #include "PARAMS.h"
24 #include "GRID.h"
25 #include "SURFACE.h"
26 #include "FFIELDS.h"
27 c #include "DYNVARS.h"
28 #include "PTRACERS_SIZE.h"
29 #include "PTRACERS.h"
30
31 C !INPUT PARAMETERS: ===================================================
32 C bi,bj :: tile indices
33 C myTime :: model time
34 C myIter :: time-step number
35 C myThid :: thread number
36 INTEGER bi, bj, iMin, iMax, jMin, jMax
37 _RL myTime
38 INTEGER myIter
39 INTEGER myThid
40
41 #ifdef ALLOW_PTRACERS
42
43 C !LOCAL VARIABLES: ====================================================
44 C i,j :: loop indices
45 C iTrc :: tracer index
46 C ks :: surface level index
47 INTEGER i, j
48 INTEGER iTrc, ks
49 CEOP
50
51 IF ( usingPCoords ) THEN
52 ks = Nr
53 ELSE
54 ks = 1
55 ENDIF
56
57 C Example of how to add forcing at the surface
58 DO iTrc=1,PTRACERS_numInUse
59 DO j = jMin, jMax
60 DO i = iMin, iMax
61 surfaceForcingPtr(i,j,bi,bj,iTrc) =
62 & surfaceForcingS(i,j,bi,bj)
63 c & 0. _d 0
64 ENDDO
65 ENDDO
66 ENDDO
67
68 #ifdef EXACT_CONSERV
69 IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
70 & .AND. useRealFreshWaterFlux ) THEN
71
72 DO iTrc=1,PTRACERS_numInUse
73
74 c- NonLin_FrSurf and RealFreshWaterFlux : PmEpR effectively changes
75 c the water column height ; temp., salt, (tracer) flux associated
76 c with this input/output of water is added here to the surface tendency.
77 c
78 IF (PtRACERS_EvPrRn(iTrc).NE.UNSET_RL) THEN
79 DO j = jMin, jMax
80 DO i = iMin, iMax
81 surfaceForcingPtr(i,j,bi,bj,iTrc) =
82 & surfaceForcingPtr(i,j,bi,bj,iTrc)
83 & + PmEpR(i,j,bi,bj)
84 & *( PTRACERS_EvPrRn(iTrc) - pTracer(i,j,ks,bi,bj,iTrc) )
85 & *convertEmP2rUnit
86 ENDDO
87 ENDDO
88 ENDIF
89
90 ENDDO
91 ENDIF
92 #endif /* EXACT_CONSERV */
93
94 #endif /* ALLOW_PTRACERS */
95
96 RETURN
97 END

  ViewVC Help
Powered by ViewVC 1.1.22