/[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.2 - (hide annotations) (download)
Wed Jun 24 08:02:02 2009 UTC (14 years, 11 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint62, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.1: +3 -3 lines
 third and step of replacing 3D versions of UICE,VICE,HEFF,AREA by 2D
 versions.

1 mlosch 1.2 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_get_velocity.F,v 1.1 2007/04/04 02:40:42 jmc Exp $
2 jmc 1.1 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 mlosch 1.2 uLoc(i,j) = UICE(i,j,bi,bj)
69     vLoc(i,j) = VICE(i,j,bi,bj)
70 jmc 1.1 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