Skip to content

Commit

Permalink
Moving all code from a private repo
Browse files Browse the repository at this point in the history
  • Loading branch information
Arcomano1234 committed Aug 19, 2022
1 parent 700c14a commit 544c830
Show file tree
Hide file tree
Showing 95 changed files with 23,054 additions and 0 deletions.
7 changes: 7 additions & 0 deletions .gitignore
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
# ignore ALL .log files
*.log

*.o
*.mod
*.exe

2 changes: 2 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
@@ -1 +1,3 @@
# SPEEDY-ML

Fortran code for a hybrid model that combines an atmospheric general circulation model (SPEEDY) and a reservoir computing-based machine learning algorithm.
108 changes: 108 additions & 0 deletions src/at_gcm.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,108 @@
module speedy_main

contains

subroutine agcm_main(input_ndays,start_from_file,internal_state_vector)
use mod_tsteps, only: ndaysl, ihout, nmonts, sixhrrun
use mod_utilities, only : state_vector_type

implicit none

! program : agcm_main
integer, intent(in) :: input_ndays, start_from_file
type(state_vector_type), intent(inout), optional :: internal_state_vector

! experiment identifier
character(len=3) :: cexp = 'exp'
integer :: jday, ndays

! 1. initialization
! ndays = no. of integration days, set by agcm_init
if(present(internal_state_vector)) then
print *, 'starting with interal_state_vector'
call agcm_init(cexp, 0, 0, 0, ndays,start_from_file,internal_state_vector)
else
call agcm_init(cexp, 0, 0, 0, ndays,start_from_file,internal_state_vector)
endif

! 2. do loop over total no. of integration days
if(present(internal_state_vector)) then
ndays = input_ndays
endif

ndays = input_ndays
print *, 'integration length in days: ', ndays

if(present(internal_state_vector)) then
if(internal_state_vector%is_safe_to_run_speedy) then
do jday = 1, ndays
! 2.2 run atmospheric model for 1 day
call agcm_1day(jday, cexp)

! 2.1 exchange data with coupler
call agcm_to_coupler(jday)
call coupler_to_agcm(jday)

enddo
endif
else
do jday = 1, ndays
! 2.2 run atmospheric model for 1 day
call agcm_1day(jday, cexp)

! 2.1 exchange data with coupler
call agcm_to_coupler(jday)
call coupler_to_agcm(jday)

enddo
endif

! Restart dataset is only written at the end
!call restart(2)
end subroutine

subroutine agcm_1day(jday, cexp)
! subroutine agcm_1day (jday)
!
! perform atm. model integration for 1 day,
! post-proc. and i/o at selected times

use mod_tsteps, only: nsteps, idout, nstout, ihout
use mod_date, only: iyear, imonth, iday, ndaytot, newdate

implicit none

integer, intent(in) :: jday
character(len=3), intent(in) :: cexp
integer :: istep

if (iday == 1) print *, ' start of year/month = ', iyear, imonth

istep = 1 + (jday - 1) * nsteps

! 1. set forcing terms according to date
call fordate(1)

! 2. set daily-average flux arrays to zero
call dmflux(0)

! 3. integrate the atmospheric model for 1 day
call stloop(istep)

! 4. write daily-mean output
!call dmout(idout)

! 5. write time-mean output files and restart file at the end of selected
! months
!if (iday == 1) then
! write monthly-mean output for previous month
! if (ihout .eqv. .false.) then
! if (nstout < 0) call tmout(1)
! end if

! open new output files at the beginning of each year
! if (imonth == 1 .and. jday < ndaytot .and. (ihout .eqv. .false.)) call setgrd(1, cexp)
!endif
end subroutine

end module speedy_main
60 changes: 60 additions & 0 deletions src/cpl_bcinterp.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,60 @@
subroutine forint(ngp,imon,fmon,for12,for1)
! Aux. routine FORINT : linear interpolation of monthly-mean forcing

implicit none

integer, intent(in) :: ngp, imon
real, intent(in) :: fmon, for12(ngp,*)
real, intent(inout) :: for1(ngp)
integer :: imon2
real :: wmon

if (fmon.le.0.5) then
imon2 = imon-1
if (imon.eq.1) imon2 = 12
wmon = 0.5-fmon
else
imon2 = imon+1
if (imon.eq.12) imon2 = 1
wmon = fmon-0.5
end if

for1 = for12(:,imon) + wmon*(for12(:,imon2) - for12(:,imon))
end

subroutine forin5(ngp,imon,fmon,for12,for1)
! Aux. routine FORIN5 : non-linear, mean-conserving interpolation
! of monthly-mean forcing fields

implicit none

integer, intent(in) :: ngp, imon
real, intent(in) :: fmon, for12(ngp,12)
real, intent(inout) :: for1(ngp)
integer :: im1, im2, ip1, ip2
real :: c0, t0, t1, t2, t3, wm1, wm2, w0, wp1, wp2

im2 = imon-2
im1 = imon-1
ip1 = imon+1
ip2 = imon+2

if (im2.lt.1) im2 = im2+12
if (im1.lt.1) im1 = im1+12
if (ip1.gt.12) ip1 = ip1-12
if (ip2.gt.12) ip2 = ip2-12

c0 = 1./12.
t0 = c0*fmon
t1 = c0*(1.-fmon)
t2 = 0.25*fmon*(1-fmon)

wm2 = -t1 +t2
wm1 = -c0 +8*t1 -6*t2
w0 = 7*c0 +10*t2
wp1 = -c0 +8*t0 -6*t2
wp2 = -t0 +t2

for1 = wm2*for12(:,im2) + wm1*for12(:,im1) + w0*for12(:,imon) +&
& wp1*for12(:,ip1) + wp2*for12(:,ip2)
end
123 changes: 123 additions & 0 deletions src/cpl_land.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,123 @@
subroutine ini_land(istart)
! subroutine ini_land (istart)
!
! Input : istart = restart flag ( 0 = no, 1 = yes)

use mod_atparam
use mod_var_land, only: stlcl_ob, stl_lm

implicit none

integer, intent(in) :: istart

! 1. Compute climatological fields for initial date
call atm2land(0)

! 2. Initialize prognostic variables of land model
! in case of no restart or no coupling
if (istart.le.0 .or. istart == 2) then
stl_lm(:) = stlcl_ob(:) ! land sfc. temperature
end if

! 3. Compute additional land variables
call land2atm(0)
end

subroutine atm2land(jday)
use mod_cpl_flags, only: icland
use mod_atparam
use mod_cpl_land_model, only: vland_input
use mod_flx_land, only: hflux_l
use mod_cli_land, only: stl12, snowd12, soilw12
use mod_date, only: imont1, tmonth
use mod_var_land, only: stlcl_ob, snowdcl_ob, soilwcl_ob, stl_lm

implicit none

integer, intent(in) :: jday
integer, parameter :: nlon=ix, nlat=il, ngp=nlon*nlat

! 1. Interpolate climatological fields to actual date

! Climatological land sfc. temperature
call forin5(ngp,imont1,tmonth,stl12,stlcl_ob)

! Climatological snow depth
call forint(ngp,imont1,tmonth,snowd12,snowdcl_ob)

! Climatological soil water availability
call forint(ngp,imont1,tmonth,soilw12,soilwcl_ob)

if (jday.le.0) return

! 2. Set input variables for mixed-layer/ocean model
if (icland.gt.0) then
vland_input(:,1) = stl_lm(:)
vland_input(:,2) = hflux_l(:)
vland_input(:,3) = stlcl_ob(:)
end if

! 3. Call message-passing routines to send data (if needed)
end

subroutine land2atm(jday)
use mod_cpl_flags, only: icland
use mod_atparam
use mod_cpl_land_model, only: land_model, vland_output
use mod_var_land

implicit none

integer, intent(in) :: jday

if (jday.gt.0.and.icland.gt.0) then
! 1. Run ocean mixed layer or
! call message-passing routines to receive data from ocean model
call land_model

! 2. Get updated variables for mixed-layer/ocean model
stl_lm(:) = vland_output(:,1) ! land sfc. temperature
end if

! 3. Compute land-sfc. fields for atm. model
! 3.1 Land sfc. temperature
if (icland.le.0) then
! Use observed climatological field
stl_am(:) = stlcl_ob(:)
else
! Use land model sfc. temperature
stl_am(:) = stl_lm(:)
end if

! 3.2 Snow depth and soil water availability
snowd_am(:) = snowdcl_ob(:)
soilw_am(:) = soilwcl_ob(:)
end

subroutine rest_land(imode)
! subroutine rest_land (imode)

! Purpose : read/write land variables from/to a restart file
! Input : IMODE = 0 : read model variables from a restart file
! = 1 : write model variables to a restart file

use mod_cpl_flags, only: icland
use mod_atparam
use mod_var_land, only: stl_am, stl_lm

implicit none

integer, intent(in) :: imode

if (imode.eq.0) then
read (3) stl_lm(:) ! Land sfc. temperature
else
! Write land model variables from coupled runs,
! otherwise write fields used by atmospheric model
if (icland.gt.0) then
write (10) stl_lm(:)
else
write (10) stl_am(:)
end if
end if
end
59 changes: 59 additions & 0 deletions src/cpl_main_interface.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,59 @@
subroutine ini_coupler(istart)
!
! subroutine ini_coupler (istart)
!

use mod_atparam
use mod_cpl_land_model, only: land_model_init
use mod_surfcon, only: fmask, alb0
use mod_cli_land, only: fmask_l
use mod_cli_sea, only: fmask_s, deglat_s

implicit none

integer, intent(in) :: istart

! 1.1 initialize land model constants
call land_model_init(fmask_l,alb0)

! 1.2 initialize land model variables
call ini_land(istart)

! 2.1 initialize sea and ice model constants
call sea_model_init(fmask_s,deglat_s)

! 2.2 initialize sea and ice model variables
call ini_sea(istart)
end

subroutine agcm_to_coupler(jday)
!
! subroutine agcm_to_coupler (jday)
!

implicit none

integer, intent(in) :: jday

! 1. send fields to land model
call atm2land(jday)

! 2. send fields to sea and ice model
call atm2sea(jday)
end

subroutine coupler_to_agcm(jday)
!
! subroutine coupler_to_agcm (jday)
!

implicit none

integer, intent(in) :: jday

! 1. get updated fields from land model
call land2atm(jday)

! 2. get updated fields from sea and ice model
call sea2atm(jday)
end
Loading

0 comments on commit 544c830

Please sign in to comment.