diff --git a/CMakeLists.txt b/CMakeLists.txt
index ac452ab4f..24dea3c93 100644
--- a/CMakeLists.txt
+++ b/CMakeLists.txt
@@ -24,6 +24,8 @@ option(FRENCTOOLS "Enable building fre-nctools.fd" ON)
option(GRIDTOOLS "Enable building grid_tools.fd" ON)
option(CHGRES "Enable building chgres_cube.fd" ON)
option(OROG_MASK_TOOLS "Enable building orog_mask_tools.fd" ON)
+# OROG_MASK_TOOLS must be ON for OROG_NETCDF_TOOLS to build.
+option(OROG_NETCDF_TOOLS "Enable building orog_netcdf_tools.fd" OFF)
option(SFC_CLIMO_GEN "Enable building sfc_climo_gen.fd" ON)
option(VCOORD_GEN "Enable building vcoord_gen.fd" ON)
option(FVCOMTOOLS "Enable building fvcom_tools.fd" ON)
diff --git a/docs/source/ufs_utils.rst b/docs/source/ufs_utils.rst
index 7810f3817..388ec4cf6 100644
--- a/docs/source/ufs_utils.rst
+++ b/docs/source/ufs_utils.rst
@@ -240,11 +240,11 @@ Program inputs and outputs
* The "grid" files (CRES_grid.tile#.nc) containing the geo-reference records for the grid - (NetCDF). Created by the make_hgrid or regional_esg_grid programs.
* Global 30-arc-second University of Maryland land cover data. Used to create the land-sea mask.
- * landcover30.fixed (unformatted binary). Located here `./fix/fix_orog `_.
+ * landcover.umd.30s.nc (NetCDF). Located here `./fix/fix_orog `_.
* Global 30-arc-second USGS GMTED2010 orography data.
- * gmted2010.30sec.int (unformatted binary). Located here `./fix/fix_orog `_.
+ * topography.gmted2010.30s.nc (NetCDF). Located here `./fix/fix_orog `_.
* 30-arc-second RAMP Antarctic terrain data (Radarsat Antarctic Mapping Project)
- * thirty.second.antarctic.new.bin (unformatted binary). Located here `./fix/fix_orog `_.
+ * topography.antarctica.ramp.30s.nc (NetCDF). Located here `./fix/fix_orog `_.
**Output data:**
diff --git a/sorc/orog_mask_tools.fd/CMakeLists.txt b/sorc/orog_mask_tools.fd/CMakeLists.txt
index 59f9635dd..75c483aa7 100644
--- a/sorc/orog_mask_tools.fd/CMakeLists.txt
+++ b/sorc/orog_mask_tools.fd/CMakeLists.txt
@@ -7,6 +7,11 @@ add_subdirectory(orog.fd)
add_subdirectory(orog_gsl.fd)
add_subdirectory(lake.fd)
add_subdirectory(inland.fd)
+if(OROG_NETCDF_TOOLS)
+ add_subdirectory(orog_netcdf_tools.fd/mask.fd)
+ add_subdirectory(orog_netcdf_tools.fd/topo.fd)
+ add_subdirectory(orog_netcdf_tools.fd/ramp.fd)
+endif()
# If doxygen documentation we enabled, build it.
if(ENABLE_DOCS)
diff --git a/sorc/orog_mask_tools.fd/orog.fd/mtnlm7_oclsm.F b/sorc/orog_mask_tools.fd/orog.fd/mtnlm7_oclsm.F
index 96e3b38d8..58b5ecb86 100644
--- a/sorc/orog_mask_tools.fd/orog.fd/mtnlm7_oclsm.F
+++ b/sorc/orog_mask_tools.fd/orog.fd/mtnlm7_oclsm.F
@@ -2,8 +2,8 @@
C> Terrain maker for global spectral model.
C> @author Mark Iredell @date 92-04-16
-C> This program creates 7 terrain-related files computed from the navy
-C> 10-minute terrain dataset. The model physics grid parameters and
+C> This program creates 7 terrain-related files computed from the
+C> GMTED2010 terrain dataset. The model physics grid parameters and
C> spectral truncation and filter parameters are read by this program as
C> input.
C>
@@ -49,13 +49,9 @@
C> SPECTRAL TRUNCATION (NM), RHOMBOIDAL FLAG (NR),
C> AND FIRST AND SECOND FILTER PARAMETERS (NF0,NF1).
C> RESPECTIVELY READ IN FREE FORMAT.
-C> - UNIT235 - GTOPO 30" AVR for ZAVG elevation
-C> - UNIT10 - 30" UMD land (lake) cover mask see MSKSRC switch
-C> - XUNIT11 - GTOPO AVR
-C> - XUNIT12 - GTOPO STD DEV
-C> - XUNIT13 - GTOPO MAX
-C> - UNIT14 - GTOPO SLM (10' NAVY if switched to get lakes
-C> - UNIT15 - GICE Grumbine 30" RAMP Antarctica orog IMNx3616
+C> - NCID - GMTED2010 USGS orography (NetCDF)
+C> - NCID - 30" UMD land cover mask. (NetCDF)
+C> - NCID - GICE Grumbine 30" RAMP Antarctica orog IMNx3601. (NetCDF)
C> - UNIT25 - Ocean land-sea mask on gaussian grid
C>
C> OUTPUT FILES:
@@ -203,9 +199,9 @@ SUBROUTINE TERSUB(IMN,JMN,IM,JM,NM,NR,NF0,NF1,NW,EFAC,BLAT,
real, PARAMETER :: PI=3.1415926535897931
integer, PARAMETER :: NMT=14
- integer :: efac,blat,zsave1,zsave2,itopo,kount
- integer :: kount2,islmx,jslmx,oldslm,msksrc,mskocn,notocn
- integer :: i,j,nx,ny,ncid,js,jn,iw,ie,k,it,jt,i1,error,id_dim
+ integer :: efac,blat,zsave1,zsave2
+ integer :: mskocn,notocn
+ integer :: i,j,nx,ny,ncid,js,jn,iw,ie,k,it,jt,error,id_dim
integer :: id_var,nx_in,ny_in,fsize,wgta,IN,INW,INE,IS,ISW,ISE
integer :: M,N,IMT,IRET,ios,iosg,latg2,istat,itest,jtest
integer :: i_south_pole,j_south_pole,i_north_pole,j_north_pole
@@ -278,17 +274,14 @@ SUBROUTINE TERSUB(IMN,JMN,IM,JM,NM,NR,NF0,NF1,NW,EFAC,BLAT,
DEGRAD = 180./PI
SPECTR = NM .GT. 0 ! if NM <=0 grid is assumed lat/lon
FILTER = .TRUE. ! Spectr Filter defaults true and set by NF1 & NF0
-! MSKSRC = 0 ! MSKSRC=0 navy 10 lake msk, 1 UMD 30, -1 no lakes
- MSKSRC = 1 ! MSKSRC=0 navy 10 lake msk, 1 UMD 30, -1 no lakes
REVLAT = BLAT .LT. 0 ! Reverse latitude/longitude for output
- ITOPO = 1 ! topo 30" read, otherwise tiles (opt offline)
MSKOCN = 1 ! Ocean land sea mask =1, =0 if not present
NOTOCN = 1 ! =1 Ocean lsm input reverse: Ocean=1, land=0
! --- The LSM Gaussian file from the ocean model sometimes arrives with
! --- 0=Ocean and 1=Land or it arrives with 1=Ocean and 0=land without
! --- metadata to distinguish its disposition. The AI below mitigates this.
- print *,' In TERSUB, ITOPO=',itopo
+ print *,' In TERSUB'
if (mskocn .eq. 1)then
print *,' Ocean Model LSM Present and '
print *, ' Overrides OCEAN POINTS in LSM: mskocn=',mskocn
@@ -296,71 +289,23 @@ SUBROUTINE TERSUB(IMN,JMN,IM,JM,NM,NR,NF0,NF1,NW,EFAC,BLAT,
print *,' Ocean LSM Reversed: NOTOCN=',notocn
endif
endif
-C
-C --- old S-Y. files
-C- OPEN(UNIT=11,FORM='FORMATTED',ERR=900) ! average
-C- OPEN(UNIT=12,FORM='FORMATTED',ERR=900) ! Std Dev
-C- OPEN(UNIT=13,FORM='FORMATTED',ERR=900) ! maximum
-C- OPEN(UNIT=14,FORM='FORMATTED',ERR=900) ! sea-land-lake-mask
-C
-! --- READ(11,11) ZAVG
-! --- READ(12,11) ZVAR
-! --- READ(13,11) ZMAX
-! --- 11 FORMAT(20I4)
-!
-! --- MSKSRC 0 navy 10' lake mask, =1 for 30" UMD lake mask,
-! --- MSKSRC internally set if above fails at -1 for no lakes
-! ---
- IF (MSKSRC .eq. 0 ) then
- READ(14,12,iostat=ios) ZSLMX
- 12 FORMAT(80I1)
- if (ios.ne.0) then
- MSKSRC=-1
- print *,' navy10 lake mask rd fail -- ios,MSKSRC:',ios,MSKSRC
- endif
- ELSE
- print *,' Attempt to open/read UMD 30" slmsk MSKSRC=',MSKSRC
-! --- not 0 so MSKSRC=1 and attempt to open/read UMD 30" slmsk
-! open(10,file=
-! &"/scratch2/portfolios/NCEPDEV/global/noscrub/Jordan.Alpert/wx23ja
-! &/terrain30/landcover30.fixed",
-! & recl=43200*21600, access='direct',iostat=istat)
- open(10,file="landcover30.fixed",
- & recl=43200*21600, access='direct',iostat=istat)
-
- IF (istat.ne.0) then
- MSKSRC=-1
- print *,' UMD lake mask open failed -- ios,MSKSRC:',istat,MSKSRC
- ELSE
-!
- read(10, rec=1,iostat=istat) UMD
- print *,' UMD lake mask opened OK -- ios,MSKSRC:',istat,MSKSRC
-!
- ENDIF
-! --------------
- IF (istat.ne.0) then
-! --- When UMD read fails attempt to read navy 10'
- print *,' UMD lake mask rd err -- trying navy 10',istat
- MSKSRC=0
- print *,' ***** MSKSRC set to 0 MSKSRC=',MSKSRC
- if (MSKSRC .eq. 0 ) then
- READ(14,12,iostat=ios) ZSLMX
- if (ios.ne.0) then
- MSKSRC=-1
- print *,' navy10 lake mask rd fail - ios,MSKSRC:',ios,MSKSRC
- endif
- endif
- ELSE
- print *,' UMD lake, UMD(50,50)=',UMD(50,50),MSKSRC
- ENDIF
-! --------------
-! --- good UMD land cover read and MSKSRC=1
- ENDIF
+
+ print *,' Attempt to open/read UMD 30sec slmsk.'
+
+ error=NF__OPEN("./landcover.umd.30s.nc",NF_NOWRITE,fsize,ncid)
+ call netcdf_err(error, 'Open file landcover.umd.30s.nc' )
+ error=nf_inq_varid(ncid, 'land_mask', id_var)
+ call netcdf_err(error, 'Inquire varid of land_mask')
+ error=nf_get_var_int1(ncid, id_var, UMD)
+ call netcdf_err(error, 'Inquire data of land_mask')
+ error = nf_close(ncid)
+
+ print *,' UMD lake, UMD(50,50)=',UMD(50,50)
C
C- READ_G for global 30" terrain
C
- print *,' About to call read_g, ITOPO=',ITOPO
- if ( ITOPO .ne. 0 ) call read_g(glob,ITOPO)
+ print *,' Call read_g to read global topography'
+ call read_g(glob)
! --- transpose even though glob 30" is from S to N and NCEP std is N to S
do j=1,jmn/2
do I=1,imn
@@ -400,82 +345,30 @@ SUBROUTINE TERSUB(IMN,JMN,IM,JM,NM,NR,NF0,NF1,NW,EFAC,BLAT,
! --- ZAVG initialize from glob
ZAVG=glob
- SELECTCASE(MSKSRC)
-C---- 30" sea land mask. 0 are water (lake or ocean)
- CASE(1)
-! --- transpose even though glob 30" is from S to N and NCEP std is N to S
- do j=1,jmn/2
- do I=1,imn
+! --- transpose mask even though glob 30" is from N to S and NCEP std is S to N
+ do j=1,jmn/2
+ do I=1,imn
jt=jmn - j + 1
i3save = UMD(I,j)
UMD(I,j)=UMD(I,jt)
UMD(I,jt) = i3save
- enddo
- enddo
+ enddo
+ enddo
! --- transpose UMD as USGS 30" is from dateline and NCEP std is 0
- do j=1,jmn
- do i=1,imn/2
+ do j=1,jmn
+ do i=1,imn/2
it=imn/2 + i
i3save = UMD(i,J)
UMD(i,J)=UMD(it,J)
UMD(it,J) = i3save
- enddo
- enddo
-! --- UMD slmsk with 30" lakes
- do j=1,jmn
- do i=1,imn
- if ( UMD(i,j) .eq. 0 ) ZSLM(i,j) = 0
- enddo
- enddo
-! --- Global land in slm plus lakes on 30" grid and elev set over globe
-! ---
-! --- When navy 10' mask is set MSKSRC=0
- CASE(0)
-! --- MSKSRC 0 navy 10' lake mask, =1 for 30" UMD lake mask, -1 no lakes
- print *,' NAVY 10 (8) slmsk for lakes, MSKSRC=',MSKSRC
- kount = 0
- kount2 = 0
- do j=1,jmn
- oldslm = ZSLM(IMN,j)
- do i=1,imn
- i1 = i + 1
-! --- slmsk with 10' lakes
- if ( glob(i,j) .eq. -9999 ) then
- ZSLM(i,j) = 0
- kount = kount + 1
- endif
- islmx=(i-1)/16 + 1
- jslmx=(j-1)/16 + 1
- if ( ZSLMX(islmx,jslmx) .eq. 0 ) then
- if ( j .gt. 8 .and. j .lt. JMN-8 ) then
- if (i1 .gt. IMN ) i1 = i1 - IMN
-! -----
- if(ZSLM(i,j).eq.1 .and. oldslm .eq. 1 .and. ZSLM(i1,j).eq.1)then
- if (i .ne. 1) oldslm = ZSLM(i,j)
- ZSLM(i,j) = 0
- kount2 = kount2 + 1
- endif
-! -----
- endif
- endif
- enddo
- enddo
-! ---
- CASE(-1)
- print *,' ***** set slm from 30" glob, MSKSRC=',MSKSRC
- kount = 0
- kount2 = 0
- do j=1,jmn
- do i=1,imn
- i1 = i + 1
-! --- UMD slmsk with 10' lakes and set ZAVG from 30" glob
- if ( glob(i,j) .eq. -9999 ) then
- ZSLM(i,j) = 0
- kount = kount + 1
- endif
- enddo
- enddo
- END SELECT
+ enddo
+ enddo
+! --- Non-land is 0.
+ do j=1,jmn
+ do i=1,imn
+ if ( UMD(i,j) .eq. 0 ) ZSLM(i,j) = 0
+ enddo
+ enddo
deallocate (ZSLMX,UMD,glob)
! ---
@@ -562,16 +455,27 @@ SUBROUTINE TERSUB(IMN,JMN,IM,JM,NM,NR,NF0,NF1,NW,EFAC,BLAT,
& ' Before GICE ZAVG(1,52)=',ZAVG(1,52),ZSLM(1,52)
print *,
& ' Before GICE ZAVG(1,112)=',ZAVG(1,JMN-112),ZSLM(1,112)
-! GICE: Grumbine 30" Antarctica orog IMNx3616 from S to N & wraped E-W.
-! NB: Zfields are S to N and W-E!
- iosg = 0
- READ(15,iostat=iosg) GICE
- if(iosg .ne. 0 ) then
+
+! Read 30-sec Antarctica RAMP data. Points scan from South
+! to North, and from Greenwich to Greenwich.
+
+! The error handling here needs to be cleaned up.
+ iosg = 0
+ error=NF__OPEN("./topography.antarctica.ramp.30s.nc",
+ & NF_NOWRITE,fsize,ncid)
+ call netcdf_err(error, 'Opening RAMP topo file' )
+ error=nf_inq_varid(ncid, 'topo', id_var)
+ call netcdf_err(error, 'Inquire varid of RAMP topo')
+ error=nf_get_var_real(ncid, id_var, GICE)
+ iosg=error
+ call netcdf_err(error, 'Inquire data of RAMP topo')
+ error = nf_close(ncid)
+
+ if(iosg .ne. 0 ) then
print *,' *** Err on reading GICE record, iosg=',iosg
print *,' exec continues but NO GICE correction done '
-! stop
- else
- print *,' GICE 30" Antarctica RAMP orog 43200x3616 read OK'
+ else
+ print *,' GICE 30" Antarctica RAMP orog 43201x3601 read OK'
print *,' Processing! '
print *,' Processing! '
print *,' Processing! '
@@ -591,7 +495,7 @@ SUBROUTINE TERSUB(IMN,JMN,IM,JM,NM,NR,NF0,NF1,NW,EFAC,BLAT,
&' orig:',i5,i4,' Lat=',f7.3,f8.2,'E',' GICE=',f8.1)
enddo
enddo
- endif
+ endif
deallocate (GICE)
@@ -1666,14 +1570,11 @@ SUBROUTINE MAKEMT(ZAVG,ZSLM,ORO,SLM,VAR,VAR4,
INTEGER ZAVG(IMN,JMN),ZSLM(IMN,JMN)
DIMENSION ORO(IM,JM),SLM(IM,JM),VAR(IM,JM),VAR4(IM,JM)
DIMENSION IST(IM,jm),IEN(IM,jm),JST(JM),JEN(JM),numi(jm)
- INTEGER mskocn,isave
LOGICAL FLAG, DEBUG
C==== DATA DEBUG/.TRUE./
DATA DEBUG/.FALSE./
C
! ---- OCLSM holds the ocean (im,jm) grid
-! --- mskocn=1 Use ocean model sea land mask, OK and present,
-! --- mskocn=0 dont use Ocean model sea land mask, not OK, not present
print *,' _____ SUBROUTINE MAKEMT '
C---- GLOBAL XLAT AND XLON ( DEGREE )
C
@@ -2578,7 +2479,7 @@ SUBROUTINE MAKEPC2(ZAVG,ZSLM,THETA,GAMMA,SIGMA,
integer i,j,i1,j1,i2,jst,jen,numx,i0,ip1,ijax
integer ilist(IMN)
logical inside_a_polygon
- LOGICAL FLAG, DEBUG
+ LOGICAL DEBUG
C=== DATA DEBUG/.TRUE./
DATA DEBUG/.FALSE./
C
@@ -3238,22 +3139,20 @@ SUBROUTINE MAKEOA2(ZAVG,zslm,VAR,GLAT,OA4,OL,IOA4,ELVMAX,
real XNSUM(IM,JM),XNSUM1(IM,JM),XNSUM2(IM,JM)
real XNSUM3(IM,JM),XNSUM4(IM,JM)
real VAR(IM,JM),OL(IM,JM,4)
- LOGICAL FLAG
integer i,j,ilist(IMN),numx,i1,j1,ii1
- integer KWD,II,npts
+ integer KWD
real LONO(4),LATO(4),LONI,LATI
real DELXN,HC,HEIGHT,XNPU,XNPD,T
integer NS0,NS1,NS2,NS3,NS4,NS5,NS6
logical inside_a_polygon
real lon,lat,dlon,dlat,dlat_old
real lon1,lat1,lon2,lat2
- real xnsum11,xnsum12,xnsum21,xnsum22,xnsumx
+ real xnsum11,xnsum12,xnsum21,xnsum22
real HC_11, HC_12, HC_21, HC_22
real xnsum1_11,xnsum1_12,xnsum1_21,xnsum1_22
real xnsum2_11,xnsum2_12,xnsum2_21,xnsum2_22
real get_lon_angle, get_lat_angle, get_xnsum
- integer ist, ien, jst, jen
- real xland,xwatr,xl1,xs1,oroavg,slm
+ integer jst, jen
C
C---- GLOBAL XLAT AND XLON ( DEGREE )
C
@@ -4421,51 +4320,32 @@ SUBROUTINE SPFFT1(IMAX,INCW,INCG,KMAX,W,G,IDIR)
!> Read input global 30-arc second orography data.
!!
!! @param[out] glob The orography data.
-!! @param[in] itopo Not used.
!! @author Jordan Alpert NOAA/EMC
- subroutine read_g(glob,ITOPO)
+ subroutine read_g(glob)
implicit none
-cc
- integer*2 glob(360*120,180*120)
-cc
- integer ix,jx
- integer ia,ja
-cc
- parameter (ix=40*120,jx=50*120)
- parameter (ia=60*120,ja=30*120)
-cc
- integer*2 idat(ix,jx)
- integer itopo
-cc
- integer i,j,inttyp
-cc
- real(kind=8) dloin,dlain,rlon,rlat
-cc
- open(235, file="./fort.235", access='direct', recl=43200*21600*2)
- read(235,rec=1)glob
- close(235)
-cc
+
+ include 'netcdf.inc'
+
+ integer*2, intent(out) :: glob(360*120,180*120)
+
+ integer :: ncid, error, id_var, fsize
+
+ fsize=65536
+
+ error=NF__OPEN("./topography.gmted2010.30s.nc",
+ & NF_NOWRITE,fsize,ncid)
+ call netcdf_err(error, 'Open file topography.gmted2010.30s.nc' )
+ error=nf_inq_varid(ncid, 'topo', id_var)
+ call netcdf_err(error, 'Inquire varid of topo')
+ error=nf_get_var_int2(ncid, id_var, glob)
+ call netcdf_err(error, 'Read topo')
+ error = nf_close(ncid)
+
print*,' '
call maxmin (glob,360*120*180*120,'global0')
-cc
-cc
- dloin=1.d0/120.d0
- dlain=1.d0/120.d0
-cc
- rlon= -179.995833333333333333333333d0
- rlat= 89.995833333333333333333333d0
-cc
- inttyp=-1 ! average rectangular subset
-ccmr inttyp= 1 ! take closest grid point value
-ccmr inttyp= 0 ! interpolate from four closest grid point values
-cc
-! call la2ga_gtopo30(glob,360*120,180*120,
-! & dloin,dlain,rlon,rlat,inttyp,
-! & .true.,glob,
-! & 0,lonf,latg)
-cc
+
return
- end
+ end subroutine read_g
!> Print the maximum, mininum, mean and
!! standard deviation of an array.
@@ -5036,7 +4916,6 @@ subroutine nanc(a,l,c)
data inaq4/x'FFFFFFFF'/
c
real(kind=8)a(l),rtc,t1,t2
- character*24 cn
character*(*) c
c t1=rtc()
cgwv print *, ' nanc call ',c
diff --git a/sorc/orog_mask_tools.fd/orog.fd/netcdf_io.F90 b/sorc/orog_mask_tools.fd/orog.fd/netcdf_io.F90
index 09d994b0b..7ff8ce725 100644
--- a/sorc/orog_mask_tools.fd/orog.fd/netcdf_io.F90
+++ b/sorc/orog_mask_tools.fd/orog.fd/netcdf_io.F90
@@ -25,7 +25,7 @@ subroutine write_netcdf(im, jm, slm, land_frac, oro, orf, hprime, ntiles, tile,
real, intent(in), dimension(im,jm) :: slm, oro, orf, geolon, geolat, land_frac
real, intent(in), dimension(im,jm,14):: hprime
character(len=128) :: outfile
- integer :: error, ncid, i
+ integer :: error, ncid
integer :: header_buffer_val = 16384
integer :: fsize=65536, inital = 0
integer :: dim1, dim2
@@ -245,7 +245,7 @@ subroutine write_mask_netcdf(im, jm, slm, land_frac, ntiles, tile, geolon, geola
integer, intent(in):: im, jm, ntiles, tile
real, intent(in), dimension(im,jm) :: slm, geolon, geolat, land_frac
character(len=128) :: outfile
- integer :: error, ncid, i
+ integer :: error, ncid
integer :: header_buffer_val = 16384
integer :: fsize=65536, inital = 0
integer :: dim1, dim2
diff --git a/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/README b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/README
new file mode 100644
index 000000000..14dd17579
--- /dev/null
+++ b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/README
@@ -0,0 +1,8 @@
+These utilities were used to convert input data to the
+orography code from binary to netcdf.
+
+ramp.fd - Convert Antarctic RAMP terrain data.
+
+orog.fd - Convert the GMTED2010 terrain data.
+
+mask.fd - Convert the UMD land mask data.
diff --git a/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/mask.fd/CMakeLists.txt b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/mask.fd/CMakeLists.txt
new file mode 100644
index 000000000..c9d6b34f2
--- /dev/null
+++ b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/mask.fd/CMakeLists.txt
@@ -0,0 +1,17 @@
+list(APPEND fortran_src
+ mask.f90
+)
+
+if(CMAKE_Fortran_COMPILER_ID MATCHES "^(Intel)$")
+ set(CMAKE_Fortran_FLAGS "${CMAKE_Fortran_FLAGS} -r8 -i4 -convert big_endian")
+elseif(CMAKE_Fortran_COMPILER_ID MATCHES "^(GNU)$")
+ set(CMAKE_Fortran_FLAGS "${CMAKE_Fortran_FLAGS} -fdefault-real-8")
+endif()
+
+set(exe_name mask.exe)
+add_executable(${exe_name} ${fortran_src})
+target_link_libraries(
+ ${exe_name}
+ NetCDF::NetCDF_Fortran)
+
+install(TARGETS ${exe_name})
diff --git a/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/mask.fd/mask.f90 b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/mask.fd/mask.f90
new file mode 100644
index 000000000..e83bc6932
--- /dev/null
+++ b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/mask.fd/mask.f90
@@ -0,0 +1,164 @@
+ program mask_netcdf
+
+! Convert the UMD land use data to netcdf.
+
+ use netcdf
+
+ implicit none
+
+ integer*4, parameter :: idim=43200
+ integer*4, parameter :: jdim=21600
+ integer*4, parameter :: idim_p1=43201
+ integer*4, parameter :: jdim_p1=21601
+
+ character(len=150) :: filenetcdf, fileraw
+
+ integer :: i, istat, ncid, status, dim_i, dim_j
+ integer :: dim_ip1, dim_jp1
+ integer :: id_lon, id_lat, id_data
+ integer :: id_lat_corner, id_lon_corner
+
+ integer(kind=1), allocatable :: mask(:,:)
+
+ real(kind=8), allocatable :: lats(:), lons(:)
+ real(kind=8), allocatable :: lats_corner(:), lons_corner(:)
+ real(kind=8) :: lat11, lon11, dx, dy
+
+ dx = 1.0_8/120.0_8
+ dy = -(1.0_8/120.0_8)
+
+ lat11 = 90.0_8 + dy*0.5_8
+ lon11 = -180.0_8 + dx*0.5_8
+
+ allocate(lons(idim),lats(jdim),mask(idim,jdim))
+ allocate(lons_corner(idim_p1),lats_corner(jdim_p1))
+
+ do i = 1, idim
+ lons(i) = real((i-1),8) * dx + lon11
+ print*,'lon ',i,lons(i)
+ enddo
+
+ do i = 1, jdim
+ lats(i) = real((i-1),8) * dy + lat11
+ print*,'lat ',i,lats(i)
+ enddo
+
+ lat11 = 90.0_8
+ lon11 = -180.0_8
+
+ do i = 1, idim_p1
+ lons_corner(i) = real((i-1),8) * dx + lon11
+ print*,'lon_corner ',i,lons_corner(i)
+ enddo
+
+ do i = 1, jdim_p1
+ lats_corner(i) = real((i-1),8) * dy + lat11
+ print*,'lat_corner ',i,lats_corner(i)
+ enddo
+
+ fileraw="/scratch1/NCEPDEV/global/glopara/fix/raw/orog/landcover30.fixed"
+
+ open(11, file=trim(fileraw), access='direct', recl=idim*jdim)
+ read(11, rec=1, iostat=istat) mask
+ if (istat /= 0) stop 99
+ close(11)
+
+ print*,'mask ', maxval(mask),minval(mask)
+ where(mask > 0) mask = 1
+
+ filenetcdf="./landcover.umd.30s.nc"
+
+ print*,"- CREATE FILE: ", trim(filenetcdf)
+ status=nf90_create(filenetcdf, IOR(NF90_NETCDF4,NF90_CLASSIC_MODEL), ncid)
+ if (status /= nf90_noerr) stop 1
+
+ status=nf90_def_dim(ncid, 'idim', idim, dim_i)
+ if (status /= nf90_noerr) stop 3
+
+ status=nf90_def_dim(ncid, 'jdim', jdim, dim_j)
+ if (status /= nf90_noerr) stop 2
+
+ status=nf90_def_dim(ncid, 'idim_p1', (idim+1), dim_ip1)
+ if (status /= nf90_noerr) stop 4
+
+ status=nf90_def_dim(ncid, 'jdim_p1', (jdim+1), dim_jp1)
+ if (status /= nf90_noerr) stop 5
+
+ status=nf90_put_att(ncid, nf90_global, 'source', 'Univ. of Maryland land use data')
+ if (status /= nf90_noerr) stop 6
+
+ status=nf90_put_att(ncid, nf90_global, 'reference', 'http://glcf.umiacs.umd.edu/data/landcover/data.shtml')
+ if (status /= nf90_noerr) stop 66
+
+ status=nf90_put_att(ncid, nf90_global, 'projection', 'regular lat/lon')
+ if (status /= nf90_noerr) stop 67
+
+ status=nf90_def_var(ncid, 'lat', nf90_double, dim_j, id_lat)
+ if (status /= nf90_noerr) stop 17
+
+ status=nf90_put_att(ncid, id_lat, 'long_name', 'grid cell center latitude')
+ if (status /= nf90_noerr) stop 10
+
+ status=nf90_put_att(ncid, id_lat, 'units', 'degrees')
+ if (status /= nf90_noerr) stop 65
+
+ status=nf90_def_var(ncid, 'lat_corner', nf90_double, dim_jp1, id_lat_corner)
+ if (status /= nf90_noerr) stop 37
+
+ status=nf90_put_att(ncid, id_lat_corner, 'long_name', 'grid cell corner latitude')
+ if (status /= nf90_noerr) stop 38
+
+ status=nf90_put_att(ncid, id_lat_corner, 'units', 'degrees')
+ if (status /= nf90_noerr) stop 68
+
+ status=nf90_def_var(ncid, 'lon', nf90_double, dim_i, id_lon)
+ if (status /= nf90_noerr) stop 16
+
+ status=nf90_put_att(ncid, id_lon, 'long_name', 'grid cell center longitude')
+ if (status /= nf90_noerr) stop 10
+
+ status=nf90_put_att(ncid, id_lon, 'units', 'degrees')
+ if (status /= nf90_noerr) stop 69
+
+ status=nf90_def_var(ncid, 'lon_corner', nf90_double, dim_ip1, id_lon_corner)
+ if (status /= nf90_noerr) stop 16
+
+ status=nf90_put_att(ncid, id_lon_corner, 'long_name', 'grid cell corner longitude')
+ if (status /= nf90_noerr) stop 40
+
+ status=nf90_put_att(ncid, id_lon_corner, 'units', 'degrees')
+ if (status /= nf90_noerr) stop 70
+
+ status=nf90_def_var(ncid, 'land_mask', nf90_byte, (/dim_i,dim_j/), id_data)
+ if (status /= nf90_noerr) stop 20
+
+ status=nf90_put_att(ncid, id_data, 'units', 'category')
+ if (status /= nf90_noerr) stop 75
+
+ status=nf90_put_att(ncid, id_data, 'Non-land', int((/0/)))
+ if (status /= nf90_noerr) stop 55
+
+ status=nf90_put_att(ncid, id_data, 'Land', int((/1/)))
+ if (status /= nf90_noerr) stop 59
+
+ status=nf90_enddef(ncid)
+ if (status /= nf90_noerr) stop 22
+
+ status=nf90_put_var(ncid, id_lon, lons)
+ if (status /= nf90_noerr) stop 19
+
+ status=nf90_put_var(ncid, id_lon_corner, lons_corner)
+ if (status /= nf90_noerr) stop 59
+
+ status=nf90_put_var(ncid, id_lat, lats)
+ if (status /= nf90_noerr) stop 20
+
+ status=nf90_put_var(ncid, id_lat_corner, lats_corner)
+ if (status /= nf90_noerr) stop 57
+
+ status=nf90_put_var(ncid, id_data, mask)
+ if (status /= nf90_noerr) stop 24
+
+ status=nf90_close(ncid)
+
+ end program mask_netcdf
diff --git a/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/mask.fd/runit.sh b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/mask.fd/runit.sh
new file mode 100755
index 000000000..8cc802868
--- /dev/null
+++ b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/mask.fd/runit.sh
@@ -0,0 +1,20 @@
+#!/bin/sh
+
+# Run on Hera.
+
+#SBATCH --ntasks=1 --nodes=1
+#SBATCH -t 0:03:00
+#SBATCH -A fv3-cpu
+#SBATCH -q debug
+#SBATCH -J fv3
+#SBATCH -o ./log
+#SBATCH -e ./log
+
+set -x
+
+source ../../../machine-setup.sh > /dev/null 2>&1
+module use ../../../../modulefiles
+module load build.$target.intel
+module list
+
+../../../../exec/mask.exe
diff --git a/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/ramp.fd/CMakeLists.txt b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/ramp.fd/CMakeLists.txt
new file mode 100644
index 000000000..384176eff
--- /dev/null
+++ b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/ramp.fd/CMakeLists.txt
@@ -0,0 +1,17 @@
+list(APPEND fortran_src
+ ramp.f90
+)
+
+if(CMAKE_Fortran_COMPILER_ID MATCHES "^(Intel)$")
+ set(CMAKE_Fortran_FLAGS "${CMAKE_Fortran_FLAGS} -r8 -i4 -convert big_endian")
+elseif(CMAKE_Fortran_COMPILER_ID MATCHES "^(GNU)$")
+ set(CMAKE_Fortran_FLAGS "${CMAKE_Fortran_FLAGS} -fdefault-real-8")
+endif()
+
+set(exe_name ramp.exe)
+add_executable(${exe_name} ${fortran_src})
+target_link_libraries(
+ ${exe_name}
+ NetCDF::NetCDF_Fortran)
+
+install(TARGETS ${exe_name})
diff --git a/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/ramp.fd/ramp.f90 b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/ramp.fd/ramp.f90
new file mode 100644
index 000000000..b897ddd16
--- /dev/null
+++ b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/ramp.fd/ramp.f90
@@ -0,0 +1,164 @@
+ program ramp_netcdf
+
+! Convert the antarctica RAMP data to netcdf.
+
+ use netcdf
+
+ implicit none
+
+ integer*4, parameter :: idim=43201
+ integer*4, parameter :: jdim=3601
+ integer*4, parameter :: idim_p1=43202
+ integer*4, parameter :: jdim_p1=3602
+
+ character(len=150) :: filenetcdf, fileraw
+
+ integer :: i, istat, ncid, status, dim_i, dim_j
+ integer :: dim_ip1, dim_jp1
+ integer :: id_lon, id_lat, id_data
+ integer :: id_lat_corner, id_lon_corner
+
+ real(kind=4), allocatable :: topo(:,:)
+
+ real(kind=8), allocatable :: lats(:), lons(:)
+ real(kind=8), allocatable :: lats_corner(:), lons_corner(:)
+ real(kind=8) :: lat11, lon11, dx, dy
+
+ dx = 1.0_8/120.0_8
+ dy = 1.0_8/120.0_8
+
+ lat11 = -(90.0_8) + dy*0.5_8
+ lon11 = 0.0_8 + dx*0.5_8
+
+ allocate(lons(idim),lats(jdim),topo(idim,jdim))
+ allocate(lons_corner(idim_p1),lats_corner(jdim_p1))
+
+ do i = 1, idim
+ lons(i) = real((i-1),8) * dx + lon11
+ if (lons(i) > 360.0_8) lons(i) = 360.0_8 - lons(i)
+ print*,'lon ',i,lons(i)
+ enddo
+
+ do i = 1, jdim
+ lats(i) = real((i-1),8) * dy + lat11
+ print*,'lat ',i,lats(i)
+ enddo
+
+ lat11 = -90.0_8
+ lon11 = 0.0_8
+
+ do i = 1, idim_p1
+ lons_corner(i) = real((i-1),8) * dx + lon11
+ if (lons_corner(i) > 360.0_8) lons_corner(i) = 360.0_8 - lons_corner(i)
+ print*,'lon_corner ',i,lons_corner(i)
+ enddo
+
+ do i = 1, jdim_p1
+ lats_corner(i) = real((i-1),8) * dy + lat11
+ print*,'lat_corner ',i,lats_corner(i)
+ enddo
+
+ fileraw="/scratch1/NCEPDEV/global/glopara/fix/raw/orog/thirty.second.antarctic.new.bin"
+
+ open(11, file=trim(fileraw), form='unformatted', access='sequential', iostat=istat)
+ print*,'iostat on open ',istat
+ read(11, iostat=istat) topo
+ print*,'iostat on read ',istat
+ if (istat /= 0) stop 99
+ close(11)
+
+ print*,'topo ', maxval(topo),minval(topo)
+
+ print*,'point 1/1 ',topo(1,1)
+ print*,'point idim/jdim ',topo(idim,jdim)
+
+ filenetcdf="./topography.antarctica.ramp.30s.nc"
+
+ print*,"- CREATE FILE: ", trim(filenetcdf)
+ status=nf90_create(filenetcdf, IOR(NF90_NETCDF4,NF90_CLASSIC_MODEL), ncid)
+ if (status /= nf90_noerr) stop 1
+
+ status=nf90_def_dim(ncid, 'idim', idim, dim_i)
+ if (status /= nf90_noerr) stop 3
+
+ status=nf90_def_dim(ncid, 'jdim', jdim, dim_j)
+ if (status /= nf90_noerr) stop 2
+
+ status=nf90_def_dim(ncid, 'idim_p1', (idim+1), dim_ip1)
+ if (status /= nf90_noerr) stop 4
+
+ status=nf90_def_dim(ncid, 'jdim_p1', (jdim+1), dim_jp1)
+ if (status /= nf90_noerr) stop 5
+
+ status=nf90_put_att(ncid, nf90_global, 'source', 'RADARSAT ANTARCTIC MAPPING PROJECT (RAMP) TOPOGRAPHY DATA')
+ if (status /= nf90_noerr) stop 6
+
+ status=nf90_put_att(ncid, nf90_global, 'projection', 'regular lat/lon')
+ if (status /= nf90_noerr) stop 67
+
+ status=nf90_def_var(ncid, 'lat', nf90_double, dim_j, id_lat)
+ if (status /= nf90_noerr) stop 17
+
+ status=nf90_put_att(ncid, id_lat, 'long_name', 'grid cell center latitude')
+ if (status /= nf90_noerr) stop 10
+
+ status=nf90_put_att(ncid, id_lat, 'units', 'degrees')
+ if (status /= nf90_noerr) stop 85
+
+ status=nf90_def_var(ncid, 'lat_corner', nf90_double, dim_jp1, id_lat_corner)
+ if (status /= nf90_noerr) stop 37
+
+ status=nf90_put_att(ncid, id_lat_corner, 'long_name', 'grid cell corner latitude')
+ if (status /= nf90_noerr) stop 38
+
+ status=nf90_put_att(ncid, id_lat_corner, 'units', 'degrees')
+ if (status /= nf90_noerr) stop 86
+
+ status=nf90_def_var(ncid, 'lon', nf90_double, dim_i, id_lon)
+ if (status /= nf90_noerr) stop 16
+
+ status=nf90_put_att(ncid, id_lon, 'long_name', 'grid cell center longitude')
+ if (status /= nf90_noerr) stop 10
+
+ status=nf90_put_att(ncid, id_lon, 'units', 'degrees')
+ if (status /= nf90_noerr) stop 87
+
+ status=nf90_def_var(ncid, 'lon_corner', nf90_double, dim_ip1, id_lon_corner)
+ if (status /= nf90_noerr) stop 16
+
+ status=nf90_put_att(ncid, id_lon_corner, 'long_name', 'grid cell corner longitude')
+ if (status /= nf90_noerr) stop 40
+
+ status=nf90_put_att(ncid, id_lon_corner, 'units', 'degrees')
+ if (status /= nf90_noerr) stop 88
+
+ status=nf90_def_var(ncid, 'topo', nf90_float, (/dim_i,dim_j/), id_data)
+ if (status /= nf90_noerr) stop 20
+
+ status=nf90_put_att(ncid, id_data, 'long_name', 'topography')
+ if (status /= nf90_noerr) stop 65
+
+ status=nf90_put_att(ncid, id_data, 'units', 'meters')
+ if (status /= nf90_noerr) stop 55
+
+ status=nf90_enddef(ncid)
+ if (status /= nf90_noerr) stop 22
+
+ status=nf90_put_var(ncid, id_lon, lons)
+ if (status /= nf90_noerr) stop 19
+
+ status=nf90_put_var(ncid, id_lon_corner, lons_corner)
+ if (status /= nf90_noerr) stop 59
+
+ status=nf90_put_var(ncid, id_lat, lats)
+ if (status /= nf90_noerr) stop 20
+
+ status=nf90_put_var(ncid, id_lat_corner, lats_corner)
+ if (status /= nf90_noerr) stop 57
+
+ status=nf90_put_var(ncid, id_data, topo)
+ if (status /= nf90_noerr) stop 24
+
+ status=nf90_close(ncid)
+
+ end program ramp_netcdf
diff --git a/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/ramp.fd/runit.sh b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/ramp.fd/runit.sh
new file mode 100755
index 000000000..f4739a1ff
--- /dev/null
+++ b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/ramp.fd/runit.sh
@@ -0,0 +1,20 @@
+#!/bin/sh
+
+# Run on Hera.
+
+#SBATCH --ntasks=1 --nodes=1
+#SBATCH -t 0:03:00
+#SBATCH -A fv3-cpu
+#SBATCH -q debug
+#SBATCH -J fv3
+#SBATCH -o ./log
+#SBATCH -e ./log
+
+set -x
+
+source ../../../machine-setup.sh > /dev/null 2>&1
+module use ../../../../modulefiles
+module load build.$target.intel
+module list
+
+../../../../exec/ramp.exe
diff --git a/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/topo.fd/CMakeLists.txt b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/topo.fd/CMakeLists.txt
new file mode 100644
index 000000000..e34d448ee
--- /dev/null
+++ b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/topo.fd/CMakeLists.txt
@@ -0,0 +1,17 @@
+list(APPEND fortran_src
+ topo.f90
+)
+
+if(CMAKE_Fortran_COMPILER_ID MATCHES "^(Intel)$")
+ set(CMAKE_Fortran_FLAGS "${CMAKE_Fortran_FLAGS} -r8 -i4 -convert big_endian")
+elseif(CMAKE_Fortran_COMPILER_ID MATCHES "^(GNU)$")
+ set(CMAKE_Fortran_FLAGS "${CMAKE_Fortran_FLAGS} -fdefault-real-8")
+endif()
+
+set(exe_name topo.exe)
+add_executable(${exe_name} ${fortran_src})
+target_link_libraries(
+ ${exe_name}
+ NetCDF::NetCDF_Fortran)
+
+install(TARGETS ${exe_name})
diff --git a/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/topo.fd/runit.sh b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/topo.fd/runit.sh
new file mode 100755
index 000000000..5e038c83d
--- /dev/null
+++ b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/topo.fd/runit.sh
@@ -0,0 +1,20 @@
+#!/bin/sh
+
+# Run on Hera.
+
+#SBATCH --ntasks=1 --nodes=1
+#SBATCH -t 0:03:00
+#SBATCH -A fv3-cpu
+#SBATCH -q debug
+#SBATCH -J fv3
+#SBATCH -o ./log
+#SBATCH -e ./log
+
+set -x
+
+source ../../../machine-setup.sh > /dev/null 2>&1
+module use ../../../../modulefiles
+module load build.$target.intel
+module list
+
+../../../../exec/topo.exe
diff --git a/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/topo.fd/topo.f90 b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/topo.fd/topo.f90
new file mode 100644
index 000000000..2674ae063
--- /dev/null
+++ b/sorc/orog_mask_tools.fd/orog_netcdf_tools.fd/topo.fd/topo.f90
@@ -0,0 +1,157 @@
+ program topo_netcdf
+
+! Convert the gmted20120 data to netcdf.
+
+ use netcdf
+
+ implicit none
+
+ integer*4, parameter :: idim=43200
+ integer*4, parameter :: jdim=21600
+ integer*4, parameter :: idim_p1=43201
+ integer*4, parameter :: jdim_p1=21601
+
+ character(len=150) :: filenetcdf, fileraw
+
+ integer :: i, istat, ncid, status, dim_i, dim_j
+ integer :: dim_ip1, dim_jp1
+ integer :: id_lon, id_lat, id_data
+ integer :: id_lat_corner, id_lon_corner
+
+ integer(kind=2), allocatable :: topo(:,:)
+
+ real(kind=8), allocatable :: lats(:), lons(:)
+ real(kind=8), allocatable :: lats_corner(:), lons_corner(:)
+ real(kind=8) :: lat11, lon11, dx, dy
+
+ dx = 1.0_8/120.0_8
+ dy = -(1.0_8/120.0_8)
+
+ lat11 = 90.0_8 + dy*0.5_8
+ lon11 = -180.0_8 + dx*0.5_8
+
+ allocate(lons(idim),lats(jdim),topo(idim,jdim))
+ allocate(lons_corner(idim_p1),lats_corner(jdim_p1))
+
+ do i = 1, idim
+ lons(i) = real((i-1),8) * dx + lon11
+ print*,'lon ',i,lons(i)
+ enddo
+
+ do i = 1, jdim
+ lats(i) = real((i-1),8) * dy + lat11
+ print*,'lat ',i,lats(i)
+ enddo
+
+ lat11 = 90.0_8
+ lon11 = -180.0_8
+
+ do i = 1, idim_p1
+ lons_corner(i) = real((i-1),8) * dx + lon11
+ print*,'lon_corner ',i,lons_corner(i)
+ enddo
+
+ do i = 1, jdim_p1
+ lats_corner(i) = real((i-1),8) * dy + lat11
+ print*,'lat_corner ',i,lats_corner(i)
+ enddo
+
+ fileraw="/scratch1/NCEPDEV/global/glopara/fix/raw/orog/gmted2010.30sec.int"
+
+ open(11, file=trim(fileraw), access='direct', recl=idim*jdim*2)
+ read(11, rec=1, iostat=istat) topo
+ if (istat /= 0) stop 99
+ close(11)
+
+ print*,'topo ', maxval(topo),minval(topo)
+
+ filenetcdf="./topography.gmted2010.30s.nc"
+
+ print*,"- CREATE FILE: ", trim(filenetcdf)
+ status=nf90_create(filenetcdf, IOR(NF90_NETCDF4,NF90_CLASSIC_MODEL), ncid)
+ if (status /= nf90_noerr) stop 1
+
+ status=nf90_def_dim(ncid, 'idim', idim, dim_i)
+ if (status /= nf90_noerr) stop 3
+
+ status=nf90_def_dim(ncid, 'jdim', jdim, dim_j)
+ if (status /= nf90_noerr) stop 2
+
+ status=nf90_def_dim(ncid, 'idim_p1', (idim+1), dim_ip1)
+ if (status /= nf90_noerr) stop 4
+
+ status=nf90_def_dim(ncid, 'jdim_p1', (jdim+1), dim_jp1)
+ if (status /= nf90_noerr) stop 5
+
+ status=nf90_put_att(ncid, nf90_global, 'source', 'USGS GMTED2010 TOPOGRAPHY DATA')
+ if (status /= nf90_noerr) stop 6
+
+ status=nf90_put_att(ncid, nf90_global, 'projection', 'regular lat/lon')
+ if (status /= nf90_noerr) stop 67
+
+ status=nf90_def_var(ncid, 'lat', nf90_double, dim_j, id_lat)
+ if (status /= nf90_noerr) stop 17
+
+ status=nf90_put_att(ncid, id_lat, 'long_name', 'grid cell center latitude')
+ if (status /= nf90_noerr) stop 10
+
+ status=nf90_put_att(ncid, id_lat, 'units', 'degrees')
+ if (status /= nf90_noerr) stop 85
+
+ status=nf90_def_var(ncid, 'lat_corner', nf90_double, dim_jp1, id_lat_corner)
+ if (status /= nf90_noerr) stop 37
+
+ status=nf90_put_att(ncid, id_lat_corner, 'long_name', 'grid cell corner latitude')
+ if (status /= nf90_noerr) stop 38
+
+ status=nf90_put_att(ncid, id_lat_corner, 'units', 'degrees')
+ if (status /= nf90_noerr) stop 86
+
+ status=nf90_def_var(ncid, 'lon', nf90_double, dim_i, id_lon)
+ if (status /= nf90_noerr) stop 16
+
+ status=nf90_put_att(ncid, id_lon, 'long_name', 'grid cell center longitude')
+ if (status /= nf90_noerr) stop 10
+
+ status=nf90_put_att(ncid, id_lon, 'units', 'degrees')
+ if (status /= nf90_noerr) stop 87
+
+ status=nf90_def_var(ncid, 'lon_corner', nf90_double, dim_ip1, id_lon_corner)
+ if (status /= nf90_noerr) stop 16
+
+ status=nf90_put_att(ncid, id_lon_corner, 'long_name', 'grid cell corner longitude')
+ if (status /= nf90_noerr) stop 40
+
+ status=nf90_put_att(ncid, id_lon_corner, 'units', 'degrees')
+ if (status /= nf90_noerr) stop 88
+
+ status=nf90_def_var(ncid, 'topo', nf90_short, (/dim_i,dim_j/), id_data)
+ if (status /= nf90_noerr) stop 20
+
+ status=nf90_put_att(ncid, id_data, 'long_name', 'topography')
+ if (status /= nf90_noerr) stop 65
+
+ status=nf90_put_att(ncid, id_data, 'units', 'meters')
+ if (status /= nf90_noerr) stop 55
+
+ status=nf90_enddef(ncid)
+ if (status /= nf90_noerr) stop 22
+
+ status=nf90_put_var(ncid, id_lon, lons)
+ if (status /= nf90_noerr) stop 19
+
+ status=nf90_put_var(ncid, id_lon_corner, lons_corner)
+ if (status /= nf90_noerr) stop 59
+
+ status=nf90_put_var(ncid, id_lat, lats)
+ if (status /= nf90_noerr) stop 20
+
+ status=nf90_put_var(ncid, id_lat_corner, lats_corner)
+ if (status /= nf90_noerr) stop 57
+
+ status=nf90_put_var(ncid, id_data, topo)
+ if (status /= nf90_noerr) stop 24
+
+ status=nf90_close(ncid)
+
+ end program topo_netcdf
diff --git a/ush/fv3gfs_make_orog.sh b/ush/fv3gfs_make_orog.sh
index a684cf6e4..6fcff6673 100755
--- a/ush/fv3gfs_make_orog.sh
+++ b/ush/fv3gfs_make_orog.sh
@@ -81,12 +81,9 @@ echo "indir = $indir"
cd $workdir
-cp ${indir}/thirty.second.antarctic.new.bin fort.15
-cp ${indir}/landcover30.fixed .
-# uncomment next line to use the old gtopo30 data.
-# cp ${indir}/gtopo30_gg.fine.nh fort.235
-# use gmted2020 data.
-cp ${indir}/gmted2010.30sec.int fort.235
+cp ${indir}/topography.antarctica.ramp.30s.nc .
+cp ${indir}/landcover.umd.30s.nc .
+cp ${indir}/topography.gmted2010.30s.nc .
if [ $inorogexist -eq 1 ]; then
cp $inputorog .
fi