Skip to content

Commit

Permalink
Remove orca grid (CICE-Consortium#986)
Browse files Browse the repository at this point in the history
Deprecate ORCA/CPOM grid functionality as it is not uses in CICE6. The model will abort if orca_halogrid = .true. or gridtype='cpom_grid' in the namelist.

Fix gadi test submission
  • Loading branch information
anton-seaice authored Nov 7, 2024
1 parent d619592 commit 8707e16
Show file tree
Hide file tree
Showing 7 changed files with 67 additions and 253 deletions.
22 changes: 18 additions & 4 deletions cicecore/cicedyn/general/ice_init.F90
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ subroutine input_data
diag_file, print_global, print_points, latpnt, lonpnt, &
debug_model, debug_model_step, debug_model_task, &
debug_model_i, debug_model_j, debug_model_iblk
use ice_domain, only: close_boundaries, orca_halogrid
use ice_domain, only: close_boundaries
use ice_domain_size, only: &
ncat, nilyr, nslyr, nblyr, nfsd, nfreq, &
n_iso, n_aero, n_zaero, n_algae, &
Expand Down Expand Up @@ -174,6 +174,7 @@ subroutine input_data
logical (kind=log_kind) :: tr_pond_lvl, tr_pond_topo
integer (kind=int_kind) :: numin, numax ! unit number limits
logical (kind=log_kind) :: lcdf64 ! deprecated, backwards compatibility
logical (kind=log_kind) :: orca_halogrid !deprecated

integer (kind=int_kind) :: rplvl, rptopo
real (kind=dbl_kind) :: Cf, ksno, puny, ice_ref_salinity, Tocnfrz
Expand Down Expand Up @@ -382,7 +383,7 @@ subroutine input_data
grid_atm = 'A' ! underlying atm forcing/coupling grid
grid_ocn = 'A' ! underlying atm forcing/coupling grid
gridcpl_file = 'unknown_gridcpl_file'
orca_halogrid = .false. ! orca haloed grid
orca_halogrid = .false. ! orca haloed grid - deprecated
bathymetry_file = 'unknown_bathymetry_file'
bathymetry_format = 'default'
use_bathymetry = .false.
Expand Down Expand Up @@ -1266,7 +1267,7 @@ subroutine input_data
endif
abort_list = trim(abort_list)//":1"
endif

if (history_format /= 'cdf1' .and. &
history_format /= 'cdf2' .and. &
history_format /= 'cdf5' .and. &
Expand Down Expand Up @@ -1829,6 +1830,20 @@ subroutine input_data
endif
endif

if (orca_halogrid) then
if (my_task == master_task) then
write(nu_diag,*) subname//' ERROR: orca_halogrid has been deprecated'
endif
abort_list = trim(abort_list)//":63"
endif

if (trim(grid_type) == 'cpom_grid') then
if (my_task == master_task) then
write(nu_diag,*) subname//" ERROR: grid_type = 'cpom_grid' has been deprecated"
endif
abort_list = trim(abort_list)//":64"
endif

ice_IOUnitsMinUnit = numin
ice_IOUnitsMaxUnit = numax

Expand Down Expand Up @@ -2579,7 +2594,6 @@ subroutine input_data
if (trim(kmt_type) == 'file') &
write(nu_diag,1031) ' kmt_file = ', trim(kmt_file)
endif
write(nu_diag,1011) ' orca_halogrid = ', orca_halogrid

write(nu_diag,1011) ' conserv_check = ', conserv_check

Expand Down
3 changes: 1 addition & 2 deletions cicecore/cicedyn/infrastructure/ice_domain.F90
Original file line number Diff line number Diff line change
Expand Up @@ -64,8 +64,7 @@ module ice_domain
maskhalo_remap , & ! if true, use masked halo updates for transport
maskhalo_bound , & ! if true, use masked halo updates for bound_state
halo_dynbundle , & ! if true, bundle halo update in dynamics
landblockelim , & ! if true, land block elimination is on
orca_halogrid ! if true, input fields are haloed as defined by orca grid
landblockelim ! if true, land block elimination is on

!-----------------------------------------------------------------------
!
Expand Down
114 changes: 2 additions & 112 deletions cicecore/cicedyn/infrastructure/ice_grid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -498,8 +498,6 @@ subroutine init_grid2
call latlongrid ! lat lon grid for sequential CESM (CAM mode)
return
#endif
elseif (trim(grid_type) == 'cpom_grid') then
call cpomgrid ! cpom model orca1 type grid
else
call rectgrid ! regular rectangular grid
endif
Expand Down Expand Up @@ -643,9 +641,7 @@ subroutine init_grid2
!-----------------------------------------------------------------
! Compute ANGLE on T-grid
!-----------------------------------------------------------------
if (trim(grid_type) == 'cpom_grid') then
ANGLET(:,:,:) = ANGLE(:,:,:)
else if (.not. (l_readCenter)) then
if (.not. (l_readCenter)) then
ANGLET = c0

!$OMP PARALLEL DO PRIVATE(iblk,i,j,ilo,ihi,jlo,jhi,this_block, &
Expand Down Expand Up @@ -675,7 +671,7 @@ subroutine init_grid2
enddo
enddo
!$OMP END PARALLEL DO
endif ! cpom_grid
endif

if (trim(grid_type) == 'regional' .and. &
(.not. (l_readCenter))) then
Expand Down Expand Up @@ -1833,112 +1829,6 @@ subroutine grid_boxislands_kmt (work)

end subroutine grid_boxislands_kmt

!=======================================================================

! CPOM displaced pole grid and land mask. \\
! Grid record number, field and units are: \\
! (1) ULAT (degrees) \\
! (2) ULON (degrees) \\
! (3) HTN (m) \\
! (4) HTE (m) \\
! (7) ANGLE (radians) \\
!
! Land mask record number and field is (1) KMT.
!
! author: Adrian K. Turner, CPOM, UCL, 09/08/06

subroutine cpomgrid

integer (kind=int_kind) :: &
i, j, iblk, &
ilo,ihi,jlo,jhi ! beginning and end of physical domain

logical (kind=log_kind) :: diag

real (kind=dbl_kind), dimension(:,:), allocatable :: &
work_g1

real (kind=dbl_kind), dimension (nx_block,ny_block,max_blocks) :: &
work1

real (kind=dbl_kind) :: &
rad_to_deg

type (block) :: &
this_block ! block information for current block

character(len=*), parameter :: subname = '(cpomgrid)'

call icepack_query_parameters(rad_to_deg_out=rad_to_deg)
call icepack_warnings_flush(nu_diag)
if (icepack_warnings_aborted()) call abort_ice(error_message=subname, &
file=__FILE__, line=__LINE__)

call ice_open(nu_grid,grid_file,64)
call ice_open(nu_kmt,kmt_file,32)

diag = .true. ! write diagnostic info

! topography
call ice_read(nu_kmt,1,work1,'ida4',diag)

hm (:,:,:) = c0
kmt(:,:,:) = c0
!$OMP PARALLEL DO PRIVATE(iblk,i,j,ilo,ihi,jlo,jhi,this_block)
do iblk = 1, nblocks
this_block = get_block(blocks_ice(iblk),iblk)
ilo = this_block%ilo
ihi = this_block%ihi
jlo = this_block%jlo
jhi = this_block%jhi

do j = jlo, jhi
do i = ilo, ihi
kmt(i,j,iblk) = work1(i,j,iblk)
if (kmt(i,j,iblk) >= c1) hm(i,j,iblk) = c1
enddo
enddo
enddo
!$OMP END PARALLEL DO

allocate(work_g1(nx_global,ny_global))

! lat, lon, cell dimensions, angles
call ice_read_global(nu_grid,1,work_g1, 'rda8',diag)
call scatter_global(ULAT, work_g1, master_task, distrb_info, &
field_loc_NEcorner, field_type_scalar)

call ice_read_global(nu_grid,2,work_g1, 'rda8',diag)
call scatter_global(ULON, work_g1, master_task, distrb_info, &
field_loc_NEcorner, field_type_scalar)

call ice_read_global(nu_grid,3,work_g1, 'rda8',diag)
work_g1 = work_g1 * m_to_cm
call primary_grid_lengths_HTN(work_g1) ! dxU, dxT, dxN, dxE

call ice_read_global(nu_grid,4,work_g1, 'rda8',diag)
work_g1 = work_g1 * m_to_cm
call primary_grid_lengths_HTE(work_g1) ! dyU, dyT, dyN, dyE

call ice_read_global(nu_grid,7,work_g1,'rda8',diag)
call scatter_global(ANGLE, work_g1, master_task, distrb_info, &
field_loc_NEcorner, field_type_scalar)

! fix units
ULAT = ULAT / rad_to_deg
ULON = ULON / rad_to_deg

deallocate(work_g1)

if (my_task == master_task) then
close (nu_grid)
close (nu_kmt)
endif

write(nu_diag,*) subname," min/max HTN: ", minval(HTN), maxval(HTN)
write(nu_diag,*) subname," min/max HTE: ", minval(HTE), maxval(HTE)

end subroutine cpomgrid

!=======================================================================

Expand Down
Loading

0 comments on commit 8707e16

Please sign in to comment.