/[MITgcm]/MITgcm/pkg/thsice/thsice_get_velocity.F
ViewVC logotype

Annotation of /MITgcm/pkg/thsice/thsice_get_velocity.F

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


Revision 1.1 - (hide annotations) (download)
Wed Apr 4 02:40:42 2007 UTC (17 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint59, checkpoint58y_post, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61p, checkpoint61q
code to advect pkg/thSIce fields (testing is in progress).

1 jmc 1.1 C $Header: $
2     C $Name: $
3    
4     #include "THSICE_OPTIONS.h"
5     #ifdef ALLOW_SEAICE
6     # include "SEAICE_OPTIONS.h"
7     #endif /* ALLOW_SEAICE */
8    
9    
10     CBOP
11     C !ROUTINE: THSICE_GET_VELOCITY
12    
13     C !INTERFACE: ==========================================================
14     SUBROUTINE THSICE_GET_VELOCITY(
15     O uLoc, vLoc,
16     I bi, bj, myTime, myIter, myThid )
17    
18     C !DESCRIPTION: \bv
19     C *===========================================================*
20     C | SUBROUTINE THSICE_GET_VELOCITY
21     C | o load seaice velocity from pkg/seaice common block
22     C *===========================================================*
23     C \ev
24    
25     C !USES: ===============================================================
26     IMPLICIT NONE
27    
28     C === Global variables ===
29    
30     #include "SIZE.h"
31     #include "EEPARAMS.h"
32     #include "PARAMS.h"
33     c#include "THSICE_SIZE.h"
34     c#include "THSICE_PARAMS.h"
35     #ifdef ALLOW_SEAICE
36     c# include "SEAICE_PARAMS.h"
37     # include "SEAICE.h"
38     #endif /* ALLOW_SEAICE */
39    
40     C !INPUT PARAMETERS: ===================================================
41     C === Routine arguments ===
42     C uLoc/vLoc :: current ice velocity on C-grid [m/s]
43     C bi,bj :: Tile indices
44     C myTime :: Current time in simulation (s)
45     C myIter :: Current iteration number
46     C myThid :: My Thread Id number
47     _RL uLoc(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
48     _RL vLoc(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
49     INTEGER bi,bj
50     _RL myTime
51     INTEGER myIter
52     INTEGER myThid
53    
54     #ifdef ALLOW_THSICE
55     C !LOCAL VARIABLES: ====================================================
56     C === Local variables ===
57     C i,j, :: Loop counters
58     INTEGER i, j
59     CEOP
60    
61     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
62    
63    
64     #ifdef ALLOW_SEAICE
65     IF ( useSEAICE ) THEN
66     DO j=1-OLy,sNy+OLy
67     DO i=1-OLx,sNx+OLx
68     uLoc(i,j) = UICE(i,j,1,bi,bj)
69     vLoc(i,j) = VICE(i,j,1,bi,bj)
70     ENDDO
71     ENDDO
72     ELSE
73     #else /* ALLOW_SEAICE */
74     IF ( .TRUE. ) THEN
75     #endif /* ALLOW_SEAICE */
76     C- set ice velocity to zero
77     DO j=1-OLy,sNy+OLy
78     DO i=1-OLx,sNx+OLx
79     uLoc(i,j) = 0.
80     vLoc(i,j) = 0.
81     ENDDO
82     ENDDO
83     ENDIF
84    
85     #endif /* ALLOW_THSICE */
86    
87     RETURN
88     END

  ViewVC Help
Powered by ViewVC 1.1.22