Skip to content

Commit

Permalink
Merge pull request #1643 from GEOS-ESM/feature/mathomp4/1636-regrid-a…
Browse files Browse the repository at this point in the history
…ttribute

Fixes #1636. Add History regrid_method attribute
  • Loading branch information
mathomp4 authored Sep 1, 2022
2 parents bf826c7 + 01c07d6 commit 4a268b1
Show file tree
Hide file tree
Showing 3 changed files with 65 additions and 27 deletions.
1 change: 1 addition & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0
- Added member function get_global_var to FileMetadata
- Added option to build source tarfile when building MAPL standalone. By default this is `OFF`, but can be enabled with
`-DINSTALL_SOURCE_TARFILE=ON`
- Added `regrid_method` metadata to History output

### Changed

Expand Down
38 changes: 37 additions & 1 deletion base/RegridMethods.F90
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ module mapl_RegridMethods
public :: UNSPECIFIED_REGRID_METHOD
public :: TILING_METHODS
public :: get_regrid_method
public :: translate_regrid_method

enum, bind(c)
enumerator :: REGRID_METHOD_IDENTITY
Expand Down Expand Up @@ -59,7 +60,7 @@ function get_regrid_method(string_regrid_method) result(int_regrid_method)
case ("VOTE")
int_regrid_method = REGRID_METHOD_VOTE
case ("FRACTION")
int_regrid_method = REGRID_METHOD_FRACTION
int_regrid_method = REGRID_METHOD_FRACTION
case ("CONSERVE_2ND")
int_regrid_method = REGRID_METHOD_CONSERVE_2ND
case ("PATCH")
Expand All @@ -70,9 +71,44 @@ function get_regrid_method(string_regrid_method) result(int_regrid_method)
int_regrid_method = REGRID_METHOD_CONSERVE_MONOTONIC
case ("BILINEAR_MONOTONIC")
int_regrid_method = REGRID_METHOD_BILINEAR_MONOTONIC
case ("NEAREST_STOD")
int_regrid_method = REGRID_METHOD_NEAREST_STOD
case default
int_regrid_method = UNSPECIFIED_REGRID_METHOD
end select
end function

function translate_regrid_method(int_regrid_method) result(string_regrid_method)
integer, intent(in) :: int_regrid_method
character(len=:), allocatable :: string_regrid_method

select case (int_regrid_method)
case (REGRID_METHOD_IDENTITY)
string_regrid_method = "identity"
case (REGRID_METHOD_BILINEAR)
string_regrid_method = "bilinear"
case (REGRID_METHOD_BILINEAR_ROTATE)
string_regrid_method = "bilinear_rotate"
case (REGRID_METHOD_CONSERVE)
string_regrid_method = "conserve"
case (REGRID_METHOD_VOTE)
string_regrid_method = "vote"
case (REGRID_METHOD_FRACTION)
string_regrid_method = "fraction"
case (REGRID_METHOD_CONSERVE_2ND)
string_regrid_method = "conserve_2nd"
case (REGRID_METHOD_PATCH)
string_regrid_method = "patch"
case (REGRID_METHOD_CONSERVE_HFLUX)
string_regrid_method = "conserve_hflux"
case (REGRID_METHOD_CONSERVE_MONOTONIC)
string_regrid_method = "conserve_monotonic"
case (REGRID_METHOD_BILINEAR_MONOTONIC)
string_regrid_method = "bilinear_monotonic"
case (REGRID_METHOD_NEAREST_STOD)
string_regrid_method = "nearest_stod"
case default
string_regrid_method = "unspecified_regrid_method"
end select
end function
end module mapl_RegridMethods
53 changes: 27 additions & 26 deletions griddedio/GriddedIO.F90
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ module MAPL_GriddedIOMod
use, intrinsic :: iso_fortran_env, only: REAL64
use ieee_arithmetic, only: isnan => ieee_is_nan
implicit none

private

type, public :: MAPL_GriddedIO
Expand Down Expand Up @@ -92,7 +92,7 @@ function new_MAPL_GriddedIO(metadata,input_bundle,output_bundle,write_collection
type(GriddedIOitemVector), intent(in), optional :: items
integer, intent(out), optional :: rc

if (present(metadata)) GriddedIO%metadata=metadata
if (present(metadata)) GriddedIO%metadata=metadata
if (present(input_bundle)) GriddedIO%input_bundle=input_bundle
if (present(output_bundle)) GriddedIO%output_bundle=output_bundle
if (present(regrid_method)) GriddedIO%regrid_method=regrid_method
Expand Down Expand Up @@ -172,10 +172,10 @@ subroutine CreateFileMetaData(this,items,bundle,timeInfo,vdata,ogrid,global_attr
order = this%metadata%get_order(rc=status)
_VERIFY(status)
metadataVarsSize = order%size()

do while (iter /= this%items%end())
item => iter%get()
if (item%itemType == ItemTypeScalar) then
if (item%itemType == ItemTypeScalar) then
call this%CreateVariable(item%xname,rc=status)
_VERIFY(status)
else if (item%itemType == ItemTypeVector) then
Expand All @@ -186,7 +186,7 @@ subroutine CreateFileMetaData(this,items,bundle,timeInfo,vdata,ogrid,global_attr
end if
call iter%next()
enddo

if (this%itemOrderAlphabetical) then
call this%alphabatize_variables(metadataVarsSize,rc=status)
_VERIFY(status)
Expand All @@ -195,9 +195,9 @@ subroutine CreateFileMetaData(this,items,bundle,timeInfo,vdata,ogrid,global_attr
if (present(global_attributes)) then
s_iter = global_attributes%begin()
do while(s_iter /= global_attributes%end())
attr_name => s_iter%key()
attr_name => s_iter%key()
attr_val => s_iter%value()
call this%metadata%add_attribute(attr_name,attr_val,_RC)
call this%metadata%add_attribute(attr_name,attr_val,_RC)
call s_iter%next()
enddo
end if
Expand Down Expand Up @@ -303,7 +303,7 @@ subroutine CreateVariable(this,itemName,rc)
class (MAPL_GriddedIO), intent(inout) :: this
character(len=*), intent(in) :: itemName
integer, optional, intent(out) :: rc

integer :: status

type(ESMF_Field) :: field,newField
Expand Down Expand Up @@ -345,7 +345,7 @@ subroutine CreateVariable(this,itemName,rc)
vdims=grid_dims//",time"
else if (fieldRank==3) then
vdims=grid_dims//",lev,time"
else
else
_FAIL( 'Unsupported field rank')
end if
v = Variable(type=PFIO_REAL32,dimensions=vdims,chunksizes=this%chunking,deflation=this%deflateLevel)
Expand All @@ -360,6 +360,7 @@ subroutine CreateVariable(this,itemName,rc)
call v%add_attribute('add_offset',0.0)
call v%add_attribute('_FillValue',MAPL_UNDEF)
call v%add_attribute('valid_range',(/-MAPL_UNDEF,MAPL_UNDEF/))
call v%add_attribute('regrid_method', translate_regrid_method(this%regrid_method))
call factory%append_variable_metadata(v)
call this%metadata%add_variable(trim(varName),v,rc=status)
_VERIFY(status)
Expand All @@ -379,11 +380,11 @@ subroutine CreateVariable(this,itemName,rc)

end subroutine CreateVariable

subroutine modifyTime(this, oClients, rc)
subroutine modifyTime(this, oClients, rc)
class(MAPL_GriddedIO), intent(inout) :: this
type (ClientManager), optional, intent(inout) :: oClients
integer, optional, intent(out) :: rc

type(Variable) :: v
type(StringVariableMap) :: var_map
integer :: status
Expand All @@ -401,11 +402,11 @@ subroutine modifyTime(this, oClients, rc)

end subroutine modifyTime

subroutine modifyTimeIncrement(this, frequency, rc)
subroutine modifyTimeIncrement(this, frequency, rc)
class(MAPL_GriddedIO), intent(inout) :: this
integer, intent(in) :: frequency
integer, optional, intent(out) :: rc

integer :: status

call this%timeInfo%setFrequency(frequency, rc=status)
Expand All @@ -432,7 +433,7 @@ subroutine bundlepost(this,filename,oClients,rc)
this%times = this%timeInfo%compute_time_vector(this%metadata,rc=status)
_VERIFY(status)
ref = ArrayReference(this%times)
call oClients%stage_nondistributed_data(this%write_collection_id,trim(filename),'time',ref)
call oClients%stage_nondistributed_data(this%write_collection_id,trim(filename),'time',ref)

tindex = size(this%times)
if (tindex==1) then
Expand Down Expand Up @@ -578,7 +579,7 @@ subroutine RegridScalar(this,itemName,rc)
call MAPL_FieldGetPointer(OutField,outptr3d,rc=status)
_VERIFY(status)
else
allocate(outptr3d(0,0,0))
allocate(outptr3d(0,0,0))
end if
if (gridIn==gridOut) then
outPtr3d=Ptr3d
Expand Down Expand Up @@ -776,10 +777,10 @@ subroutine stage2DLatLon(this, fileName, oClients, rc)
integer, allocatable :: localStart(:),globalStart(:),globalCount(:)
logical :: hasll
class(Variable), pointer :: var_lat,var_lon

var_lon => this%metadata%get_variable('lons')
var_lat => this%metadata%get_variable('lats')

hasll = associated(var_lon) .and. associated(var_lat)
if (hasll) then
factory => get_factory(this%output_grid,rc=status)
Expand Down Expand Up @@ -809,7 +810,7 @@ subroutine stage2DLatLon(this, fileName, oClients, rc)

var_lon => this%metadata%get_variable('corner_lons')
var_lat => this%metadata%get_variable('corner_lats')

hasll = associated(var_lon) .and. associated(var_lat)
if (hasll) then
factory => get_factory(this%output_grid,rc=status)
Expand Down Expand Up @@ -838,8 +839,8 @@ subroutine stage2DLatLon(this, fileName, oClients, rc)
_RETURN(_SUCCESS)

end subroutine stage2DLatLon
subroutine stageData(this, field, fileName, tIndex, oClients, rc)

subroutine stageData(this, field, fileName, tIndex, oClients, rc)
class (MAPL_GriddedIO), intent(inout) :: this
type(ESMF_Field), intent(inout) :: field
character(len=*), intent(in) :: fileName
Expand Down Expand Up @@ -912,7 +913,7 @@ subroutine alphabatize_variables(this,nfixedVars,rc)
class (MAPL_GriddedIO), intent(inout) :: this
integer, intent(in) :: nFixedVars
integer, optional, intent(out) :: rc

type(StringVector) :: order
type(StringVector) :: newOrder
character(len=:), pointer :: v1
Expand All @@ -930,7 +931,7 @@ subroutine alphabatize_variables(this,nfixedVars,rc)
v1 => order%at(i)
if ( i > nFixedVars) temp(i)=trim(v1)
enddo

swapped = .true.
do while(swapped)
swapped = .false.
Expand All @@ -957,7 +958,7 @@ subroutine alphabatize_variables(this,nfixedVars,rc)
deallocate(temp)

_RETURN(_SUCCESS)

end subroutine alphabatize_variables

subroutine request_data_from_file(this,filename,timeindex,rc)
Expand Down Expand Up @@ -1045,7 +1046,7 @@ subroutine request_data_from_file(this,filename,timeindex,rc)
ref=factory%generate_file_reference3D(ptr3d,metadata=this%current_file_metadata%filemetadata)
allocate(localStart,source=[gridLocalStart,1,timeIndex])
allocate(globalStart,source=[gridGlobalStart,1,timeIndex])
allocate(globalCount,source=[gridGlobalCount,lm,1])
allocate(globalCount,source=[gridGlobalCount,lm,1])
end if
call i_Clients%collective_prefetch_data( &
this%read_collection_id, fileName, trim(names(i)), &
Expand All @@ -1063,7 +1064,7 @@ subroutine process_data_from_file(this,rc)
class(mapl_GriddedIO), intent(inout) :: this
integer, intent(out), optional :: rc

integer :: status
integer :: status
integer :: i,numVars
character(len=ESMF_MAXSTR), allocatable :: names(:)
type(ESMF_Field) :: field
Expand Down Expand Up @@ -1124,7 +1125,7 @@ subroutine swap_undef_value(this,fname,rc)
endif

fill_value = this%current_file_metadata%var_get_missing_value(fname,_RC)

call ESMF_FieldBundleGet(this%input_bundle,fname,field=field,_RC)
call ESMF_FieldBundleGet(this%input_bundle,grid=gridIn,_RC)
call ESMF_FieldGet(field,rank=fieldRank,_RC)
Expand Down

0 comments on commit 4a268b1

Please sign in to comment.