<p><b>mpetersen@lanl.gov</b> 2011-02-23 09:55:38 -0700 (Wed, 23 Feb 2011)</p><p>Add tracer1, tracer2, and solid boundary in x to basin.F, for double-gyre basin.<br>
</p><hr noshade><pre><font color="gray">Modified: branches/ocean_projects/basin/src/basin.F
===================================================================
--- branches/ocean_projects/basin/src/basin.F        2011-02-23 16:47:26 UTC (rev 743)
+++ branches/ocean_projects/basin/src/basin.F        2011-02-23 16:55:38 UTC (rev 744)
@@ -51,8 +51,8 @@
real, dimension(25) :: dz
! Step 1: Set the number of Vertical levels, and Tracers
-integer, parameter :: nVertLevelsMOD = 1
-integer, parameter :: nTracersMod = 2
+integer, parameter :: nVertLevelsMOD = 20
+integer, parameter :: nTracersMod = 4
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! basin-mod
@@ -66,12 +66,12 @@
! Step 2: Set if the grid is on a sphere or not, and it's radius
-character (len=16) :: on_a_sphere = 'YES '
+!character (len=16) :: on_a_sphere = 'YES '
!real*8, parameter :: sphere_radius = 6.37122e6
-real*8, parameter :: sphere_radius = 1.0
+!real*8, parameter :: sphere_radius = 1.0
-!character (len=16) :: on_a_sphere = 'NO '
-!real*8, parameter :: sphere_radius = 0.0
+character (len=16) :: on_a_sphere = 'NO '
+real*8, parameter :: sphere_radius = 0.0
logical, parameter :: real_bathymetry=.false.
@@ -79,9 +79,9 @@
real (kind=8), parameter :: &
h_total_max = 2000.0, &
u_max = 0.0, &
- u_src_max = 0.1, & ! max wind stress, N/m2
- beta = 1.4e-11, &
- f0 = -1.1e-4, &
+ u_src_max = 10.0, & ! max wind stress, N/m2
+ beta = 2.0e-11, &
+ f0 = 1.4e-4, &
omega = 7.29212e-5
real (kind=8) :: ymid, ytmp, ymax, xmid, xloc, yloc, pert, ymin, distance, r, c1(3), c2(3)
@@ -108,7 +108,7 @@
real, allocatable, dimension(:) :: fEdgeNew, fVertexNew, h_sNew
real, allocatable, dimension(:,:) :: u_srcNew
real, allocatable, dimension(:,:,:) :: uNew, vNew, hNew, vhNew
-real, allocatable, dimension(:,:,:) :: circulationNew, vorticityNew, keNew, rhoNew, temperatureNew, salinityNew
+real, allocatable, dimension(:,:,:) :: circulationNew, vorticityNew, keNew, rhoNew, temperatureNew, salinityNew, tracer1, tracer2
real, allocatable, dimension(:,:,:,:) :: tracersNew
! mapping variables
@@ -293,8 +293,8 @@
hNew(1,3,:) = 3250.0
h_sNew(:) = -( hNew(1,1,:) + hNew(1,2,:) + hNew(1,3,:) )
else
- hNew(1,1,:) = 3250.0
- h_sNew(:) = -( hNew(1,1,:) )
+! hNew(1,1,:) = 3250.0
+! h_sNew(:) = -( hNew(1,1,:) )
endif
! basin-mod
@@ -358,6 +358,7 @@
endif
enddo
else
+ if(nVertLevelsMOD .eq. 3) then
ymin = minval(yCellNew)
ymax = maxval(yCellNew)
r = 3.0e5
@@ -366,16 +367,29 @@
ytmp = yCellNew(i)
pert = exp(-(ytmp-ymid)**2/((0.1*r)**2))
k=1
- if(nVertLevelsMOD .eq. 3) then
- salinityNew(1,k,:) = pert
- pert = exp(-(ytmp-ymid)**2/((1.0*r)**2))
- k=2
- salinityNew(1,k,:) = pert
- pert = exp(-(ytmp-ymid)**2/((10.0*r)**2))
- k=3
- salinityNew(1,k,:) = pert
- endif
+ salinityNew(1,k,:) = pert
+ pert = exp(-(ytmp-ymid)**2/((1.0*r)**2))
+ k=2
+ salinityNew(1,k,:) = pert
+ pert = exp(-(ytmp-ymid)**2/((10.0*r)**2))
+ k=3
+ salinityNew(1,k,:) = pert
enddo
+ else
+
+ ! Set tracer info for double-gyre basin:
+ do k=1,nVertLevelsMod
+ temperatureNew(1,k,:) = 31-k
+ salinityNew(1,k,:) = 32 + k*0.32
+ enddo
+ tracer1=1.0
+ tracer2=1.0
+ tracer1(1,1:10,:) = 0.0
+ do k=1,nVertLevelsMod,2
+ tracer2(1, k ,:) = 0.
+ enddo
+ endif
+
endif
! basin-mod
@@ -964,7 +978,7 @@
rhoNew, &
tracersNew, &
temperatureNew, &
- salinityNew &
+ salinityNew,tracer1,tracer2 &
)
call write_netcdf_finalize
@@ -994,7 +1008,7 @@
real (kind=4), allocatable, dimension(:) :: x,y, work_kmt
real (kind=4), allocatable, dimension(:,:) :: ztopo
integer :: nx, ny, inx, iny, ix, iy
-real :: pi, dtr, zdata, rlon, rlat, r, ymin, ymax
+real :: pi, dtr, zdata, rlon, rlat, r, ymin, ymax, xmin, xmax
real :: latmin, latmax, lonmin, lonmax
logical :: flag, kmt_flag
pi = 4.0*atan(1.0)
@@ -1018,12 +1032,22 @@
where(lonCell.lt.lonmin) kmt = 0
where(lonCell.gt.lonmax) kmt = 0
else
+ ! solid boundary in y
ymin = minval(yCell)
write(6,*) ' minimum yCell ', ymin
ymax = maxval(yCell)
write(6,*) ' maximum yCell ', ymax
where(yCell.lt.1.001*ymin) kmt = 0
where(yCell.gt.0.999*ymax) kmt = 0
+
+ ! solid boundary in x
+ xmin = minval(xCell)
+ write(6,*) ' minimum xCell ', xmin
+ xmax = maxval(xCell)
+ write(6,*) ' maximum xCell ', xmax
+ where(xCell.lt.1.001*xmin) kmt = 0
+ where(xCell.gt.0.999*xmax) kmt = 0
+
endif
@@ -1232,6 +1256,8 @@
allocate(tracersNew(1,nTracersNew,nVertLevelsNew,nCellsNew))
allocate(temperatureNew(1,nVertLevelsNew,nCellsNew))
allocate(salinityNew(1,nVertLevelsNew,nCellsNew))
+allocate(tracer1(1,nVertLevelsNew,nCellsNew))
+allocate(tracer2(1,nVertLevelsNew,nCellsNew))
xCellNew=0; yCellNew=0; zCellNew=0; latCellNew=0; lonCellNew=0
xEdgeNew=0; yEdgeNew=0; zEdgeNew=0; latEdgeNew=0; lonEdgeNew=0
Modified: branches/ocean_projects/basin/src/module_write_netcdf.F
===================================================================
--- branches/ocean_projects/basin/src/module_write_netcdf.F        2011-02-23 16:47:26 UTC (rev 743)
+++ branches/ocean_projects/basin/src/module_write_netcdf.F        2011-02-23 16:55:38 UTC (rev 744)
@@ -64,6 +64,8 @@
integer :: wrVarIDtracers
integer :: wrVarIDtemperature
integer :: wrVarIDsalinity
+ integer :: wrVarIDtracer1
+ integer :: wrVarIDtracer2
integer :: wrLocalnCells
integer :: wrLocalnEdges
@@ -275,6 +277,14 @@
dimlist( 2) = wrDimIDnCells
dimlist( 3) = wrDimIDTime
nferr = nf_def_var(wr_ncid, 'salinity', NF_DOUBLE, 3, dimlist, wrVarIDsalinity)
+ dimlist( 1) = wrDimIDnVertLevels
+ dimlist( 2) = wrDimIDnCells
+ dimlist( 3) = wrDimIDTime
+ nferr = nf_def_var(wr_ncid, 'tracer1', NF_DOUBLE, 3, dimlist, wrVarIDtracer1)
+ dimlist( 1) = wrDimIDnVertLevels
+ dimlist( 2) = wrDimIDnCells
+ dimlist( 3) = wrDimIDTime
+ nferr = nf_def_var(wr_ncid, 'tracer2', NF_DOUBLE, 3, dimlist, wrVarIDtracer2)
nferr = nf_put_att_text(wr_ncid, NF_GLOBAL, 'on_a_sphere', 16, on_a_sphere)
@@ -339,7 +349,7 @@
rho, &
tracers, &
temperature, &
- salinity &
+ salinity,tracer1,tracer2 &
)
implicit none
@@ -400,6 +410,8 @@
real (kind=8), dimension(:,:,:,:), intent(in) :: tracers
real (kind=8), dimension(:,:,:), intent(in) :: temperature
real (kind=8), dimension(:,:,:), intent(in) :: salinity
+ real (kind=8), dimension(:,:,:), intent(in) :: tracer1
+ real (kind=8), dimension(:,:,:), intent(in) :: tracer2
integer :: nferr
integer, dimension(1) :: start1, count1
@@ -668,6 +680,18 @@
count3( 2) = wrLocalnCells
count3( 3) = 1
nferr = nf_put_vara_double(wr_ncid, wrVarIDsalinity, start3, count3, salinity)
+
+ start3(3) = time
+ count3( 1) = wrLocalnVertLevels
+ count3( 2) = wrLocalnCells
+ count3( 3) = 1
+ nferr = nf_put_vara_double(wr_ncid, wrVarIDtracer1, start3, count3, tracer1)
+
+ start3(3) = time
+ count3( 1) = wrLocalnVertLevels
+ count3( 2) = wrLocalnCells
+ count3( 3) = 1
+ nferr = nf_put_vara_double(wr_ncid, wrVarIDtracer2, start3, count3, tracer2)
end subroutine write_netcdf_fields
</font>
</pre>