Skip to content

Commit

Permalink
adding all fortran sources
Browse files Browse the repository at this point in the history
  • Loading branch information
pdicerbo committed May 31, 2016
1 parent bccc2c4 commit e542b60
Show file tree
Hide file tree
Showing 50 changed files with 10,728 additions and 0 deletions.
109 changes: 109 additions & 0 deletions bmd_str.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,109 @@
MODULE bmd_str

!---------------------------------------------------------------------------
! !
! Copyright 2007 Srdjan Dobricic, CMCC, Bologna !
! !
! This file is part of OceanVar. !
! !
! OceanVar is free software: you can redistribute it and/or modify. !
! it under the terms of the GNU General Public License as published by !
! the Free Software Foundation, either version 3 of the License, or !
! (at your option) any later version. !
! !
! OceanVar is distributed in the hope that it will be useful, !
! but WITHOUT ANY WARRANTY; without even the implied warranty of !
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the !
! GNU General Public License for more details. !
! !
! You should have received a copy of the GNU General Public License !
! along with OceanVar. If not, see <http://www.gnu.org/licenses/>. !
! !
!---------------------------------------------------------------------------

!-----------------------------------------------------------------------
! !
! Structure for the barotropic model !
! !
! Version 1: S.Dobricic 2007 !
!-----------------------------------------------------------------------

use set_knd

implicit none

public

TYPE bmd_t

INTEGER(i4) :: ncnt ! Maximum number of iterations in the implicit solver
REAL(r8) :: ovr ! Over-relaxation factor
REAL(r8) :: resem ! Stopping criteria
REAL(r8) :: bnm ! Number of sea points

REAL(r8) :: g ! Graviational acceleration
REAL(r8) :: dt ! Time step
INTEGER(i4) :: nstp ! Number of time steps per day
REAL(r8) :: ndy ! Number of simulation days
REAL(r8) :: ady ! Number of averaging days
INTEGER(i4) :: nstps ! Number of time steps of the main loop
INTEGER(i4) :: nstpa ! Number of time steps for averaging
REAL(r8) :: alp1 ! Weighting factor in the trapezoidal scheme
REAL(r8) :: alp2 ! Weighting factor in the trapezoidal scheme
REAL(r8) :: fc1 ! Friction intensity
REAL(r8) :: fc2 ! Friction intensity
REAL(r8) :: df1 ! Friction intensity
REAL(r8) :: df2 ! Friction intensity

INTEGER(i4), POINTER :: itr(:) ! Number of iterations in the solver
REAL(r8), POINTER :: mst(:,:) ! Sea-land mask on t points
REAL(r8), POINTER :: msu(:,:) ! Sea-land mask on u points
REAL(r8), POINTER :: msv(:,:) ! Sea-land mask on v points
REAL(r8), POINTER :: hgt(:,:) ! Depth on t points
REAL(r8), POINTER :: hgu(:,:) ! Depth on u points
REAL(r8), POINTER :: hgv(:,:) ! Depth on v points
REAL(r8), POINTER :: dxu(:,:) ! DX on u points
REAL(r8), POINTER :: dyu(:,:) ! DY on u points
REAL(r8), POINTER :: dxv(:,:) ! DX on v points
REAL(r8), POINTER :: dyv(:,:) ! DY on v points
REAL(r8), POINTER :: a1(:,:) ! Constant
REAL(r8), POINTER :: a2(:,:) ! Constant
REAL(r8), POINTER :: a3(:,:) ! Constant
REAL(r8), POINTER :: a4(:,:) ! Constant
REAL(r8), POINTER :: a0(:,:) ! Constant
REAL(r8), POINTER :: a00(:,:) ! Constant
REAL(r8), POINTER :: bx(:,:) ! Bouyancy gradient in x direction (vert. int.)
REAL(r8), POINTER :: by(:,:) ! Bouyancy gradient in y direction (vert. int.)
REAL(r8), POINTER :: b_x(:,:,:) ! Bouyancy gradient in x direction
REAL(r8), POINTER :: b_y(:,:,:) ! Bouyancy gradient in y direction
REAL(r8), POINTER :: dns(:,:,:) ! Density
REAL(r8), POINTER :: bxby(:,:) !
REAL(r8), POINTER :: rgh(:,:) !
REAL(r8), POINTER :: etb(:,:) ! Eta at t-1
REAL(r8), POINTER :: ub(:,:) ! U at t-1
REAL(r8), POINTER :: vb(:,:) ! V at t-1
REAL(r8), POINTER :: etn(:,:) ! Eta at t
REAL(r8), POINTER :: un(:,:) ! U at t
REAL(r8), POINTER :: vn(:,:) ! V at t
REAL(r8), POINTER :: eta(:,:) ! Eta at t+1
REAL(r8), POINTER :: ua(:,:) ! U at t+1
REAL(r8), POINTER :: va(:,:) ! V at t+1
REAL(r8), POINTER :: etm(:,:) ! Averaged eta
REAL(r8), POINTER :: um(:,:) ! Averaged u
REAL(r8), POINTER :: vm(:,:) ! Averaged v
REAL(r8), POINTER :: div(:,:) ! Divergence at t-1
REAL(r8), POINTER :: cu(:,:) ! Coriolis term on u points
REAL(r8), POINTER :: cv(:,:) ! Coriolis term on v points
REAL(r8), POINTER :: dux(:,:) ! Friction on U
REAL(r8), POINTER :: duy(:,:) ! Friction on U
REAL(r8), POINTER :: dvx(:,:) ! Friction on V
REAL(r8), POINTER :: dvy(:,:) ! Friction on V
REAL(r8), POINTER :: etx(:,:) ! Free surface gradient at t-1
REAL(r8), POINTER :: ety(:,:) ! Free surface gradient at t-1


END TYPE bmd_t

TYPE (bmd_t) :: bmd

END MODULE bmd_str
58 changes: 58 additions & 0 deletions cns_str.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,58 @@
MODULE cns_str

!---------------------------------------------------------------------------
! !
! Copyright 2006 Srdjan Dobricic, CMCC, Bologna !
! !
! This file is part of OceanVar. !
! !
! OceanVar is free software: you can redistribute it and/or modify. !
! it under the terms of the GNU General Public License as published by !
! the Free Software Foundation, either version 3 of the License, or !
! (at your option) any later version. !
! !
! OceanVar is distributed in the hope that it will be useful, !
! but WITHOUT ANY WARRANTY; without even the implied warranty of !
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the !
! GNU General Public License for more details. !
! !
! You should have received a copy of the GNU General Public License !
! along with OceanVar. If not, see <http://www.gnu.org/licenses/>. !
! !
!---------------------------------------------------------------------------

!-----------------------------------------------------------------------
! !
! Structure of constants !
! !
! Version 1: S.Dobricic 2006 !
!-----------------------------------------------------------------------

use set_knd

implicit none

public

TYPE rcf_t

INTEGER(i4) :: ntr ! No. of iterations (half of)
REAL(r8) :: dx ! Grid resolution (m)
REAL(r8) :: L ! Correlation radius
REAL(r8) :: E ! Norm
REAL(r8) :: alp ! Filter weight
INTEGER(i4) :: ntb ! Number of points in the table
REAL(r8) :: dsmn ! Minimum distance
REAL(r8) :: dsmx ! Maximum distance
REAL(r8) :: dsl ! Table increment
REAL(r8), POINTER :: al(:) ! Filter weights in the table
REAL(r8), POINTER :: sc(:) ! Filter scaling factors in the table
REAL(r8) :: scl ! Scaling factor
REAL(r8) :: efc ! Scaling factor for extended points
INTEGER(i4) :: kstp ! Step for extended points

END TYPE rcf_t

TYPE (rcf_t) :: rcf

END MODULE cns_str
67 changes: 67 additions & 0 deletions cnv_ctv.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,67 @@
subroutine cnv_ctv

!---------------------------------------------------------------------------
! !
! Copyright 2006 Srdjan Dobricic, CMCC, Bologna !
! !
! This file is part of OceanVar. !
! !
! OceanVar is free software: you can redistribute it and/or modify. !
! it under the terms of the GNU General Public License as published by !
! the Free Software Foundation, either version 3 of the License, or !
! (at your option) any later version. !
! !
! OceanVar is distributed in the hope that it will be useful, !
! but WITHOUT ANY WARRANTY; without even the implied warranty of !
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the !
! GNU General Public License for more details. !
! !
! You should have received a copy of the GNU General Public License !
! along with OceanVar. If not, see <http://www.gnu.org/licenses/>. !
! !
!---------------------------------------------------------------------------

!-----------------------------------------------------------------------
! !
! Convert from control to v !
! !
! Version 1: S.Dobricic 2006 !
!-----------------------------------------------------------------------


use set_knd
use grd_str
use ctl_str
use eof_str

implicit none

INTEGER(i4) :: i,j,k, kk
INTEGER(i4) :: jumpInd, indSupWP
! INTEGER(i4) mycounter
! kk = 0
! do k=1,ros%neof
! do j=1,grd%jm
! do i=1,grd%im
! kk = kk+1
! grd%ro(i,j,k) = ctl%x_c(kk)
! enddo
! enddo
! enddo
!mycounter = 0


do k=1,ros%neof
jumpInd = (k -1 )*nSurfaceWaterPoints
do indSupWP = 1,nSurfaceWaterPoints
i = SurfaceWaterPoints(1,indSupWP)
j = SurfaceWaterPoints(2,indSupWP)
kk = jumpInd + indSupWP
grd%ro(i,j,k) = ctl%x_c(kk)
enddo
enddo




end subroutine cnv_ctv
62 changes: 62 additions & 0 deletions cnv_ctv_ad.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,62 @@
subroutine cnv_ctv_ad

!---------------------------------------------------------------------------
! !
! Copyright 2006 Srdjan Dobricic, CMCC, Bologna !
! !
! This file is part of OceanVar. !
! !
! OceanVar is free software: you can redistribute it and/or modify. !
! it under the terms of the GNU General Public License as published by !
! the Free Software Foundation, either version 3 of the License, or !
! (at your option) any later version. !
! !
! OceanVar is distributed in the hope that it will be useful, !
! but WITHOUT ANY WARRANTY; without even the implied warranty of !
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the !
! GNU General Public License for more details. !
! !
! You should have received a copy of the GNU General Public License !
! along with OceanVar. If not, see <http://www.gnu.org/licenses/>. !
! !
!---------------------------------------------------------------------------

!-----------------------------------------------------------------------
! !
! Convert from control to v - adjoint !
! !
! Version 1: S.Dobricic 2006 !
!-----------------------------------------------------------------------


use grd_str
use ctl_str
use eof_str
use netcdf
implicit none

INTEGER(i4) :: i,j,k, kk
INTEGER(i4) :: jumpInd, indSupWP

! integer xid,yid,eofid, idvip, status, ncid,nSFid, nDIMS, SFid
! kk = 0
! do k=1,ros%neof
! do j=1,grd%jm
! do i=1,grd%im
! kk = kk+1
! ctl%g_c(kk) = grd%ro_ad(i,j,k)
! enddo
! enddo
! enddo

do k=1,ros%neof
jumpInd = (k -1 )* nSurfaceWaterPoints
do indSupWP=1,nSurfaceWaterPoints
i = SurfaceWaterPoints(1,indSupWP)
j = SurfaceWaterPoints(2,indSupWP)
kk = jumpInd + indSupWP
ctl%g_c(kk) = grd%ro_ad(i,j,k)
enddo
enddo

end subroutine cnv_ctv_ad
48 changes: 48 additions & 0 deletions cnv_inn.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,48 @@
subroutine cnv_inn

!---------------------------------------------------------------------------
! !
! Copyright 2006 Srdjan Dobricic, CMCC, Bologna !
! !
! This file is part of OceanVar. !
! !
! OceanVar is free software: you can redistribute it and/or modify. !
! it under the terms of the GNU General Public License as published by !
! the Free Software Foundation, either version 3 of the License, or !
! (at your option) any later version. !
! !
! OceanVar is distributed in the hope that it will be useful, !
! but WITHOUT ANY WARRANTY; without even the implied warranty of !
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the !
! GNU General Public License for more details. !
! !
! You should have received a copy of the GNU General Public License !
! along with OceanVar. If not, see <http://www.gnu.org/licenses/>. !
! !
!---------------------------------------------------------------------------

!-----------------------------------------------------------------------
! !
! Convert w to correction in physical space !
! !
! Version 1: S.Dobricic 2006 !
!-----------------------------------------------------------------------


use set_knd
use obs_str
use grd_str
use eof_str
use ctl_str
use drv_str

implicit none

drv%dda(drv%ktr) = drv%ddi(drv%ktr)

! --------
! Convert the control vector to v
call cnv_ctv
call ver_hor

end subroutine cnv_inn
Loading

0 comments on commit e542b60

Please sign in to comment.