Browse Source

Merge branch 'experiments/parallelize-flux-calculator'

1.01.00
Sven Karsten 1 year ago
parent
commit
73abf04255
  1. 3
      src/flux_calculator.F90
  2. 48
      src/flux_calculator_io.F90

3
src/flux_calculator.F90

@ -272,9 +272,10 @@ ENDIF
i=0 ! present pe
j=1 ! present model
k=1 ! present task per model
WRITE(w_unit,*) "num_tasks_per_model(1): ", num_tasks_per_model(1)
DO WHILE (i < mype)
IF (k < num_tasks_per_model(j)) THEN
k=k+1; j=j+1; i=i+1
k=k+1; i=i+1
ELSE IF (k == num_tasks_per_model(j)) THEN
k=1; j=j+1; i=i+1
ENDIF

48
src/flux_calculator_io.F90

@ -42,6 +42,10 @@ MODULE flux_calculator_io
INTEGER :: nc ! NetCDF file id
INTEGER :: dimid_grid_size ! NetCDF dimension id
INTEGER :: varid ! NetCDF variable id
INTEGER :: i
INTEGER, DIMENSION(:), allocatable :: task
CALL hdlerr(NF90_OPEN(grid_filename, NF90_NOWRITE, nc), __LINE__ )
CALL hdlerr( NF90_INQ_DIMID(nc, 'grid_size' , dimid_grid_size), __LINE__ ) ! get variable id
@ -51,6 +55,7 @@ MODULE flux_calculator_io
ALLOCATE(grid_lat%field(grid_size_global,1)); grid_lat%allocated = .TRUE.
ALLOCATE(grid_area%field(grid_size_global,1)); grid_area%allocated = .TRUE.
CALL hdlerr( NF90_INQ_VARID(nc, 'grid_center_lon' , varid), __LINE__ ) ! get variable id
CALL hdlerr( NF90_GET_VAR (nc, varid, grid_lon%field(:,1), [1], [grid_size_global]), __LINE__ ) ! get variable values
CALL hdlerr( NF90_INQ_VARID(nc, 'grid_center_lat' , varid), __LINE__ )
@ -60,16 +65,54 @@ MODULE flux_calculator_io
CALL hdlerr(NF90_CLOSE(nc), __LINE__ )
! most simple case: single model, single task -> use full grid
IF (num_bottom_models == 1) THEN
! most simple case: single model, single task -> use full grid
IF (num_tasks_per_model(1) == 1) THEN
num_grid_cells = 0
num_grid_cells(1,1) = grid_size_global
grid_size = grid_size_global
grid_offset = 0
ENDIF
! single model, several tasks -> use only portion of the full grid
ELSEIF (num_tasks_per_model(1) > 1) THEN
! intialize variables with dummy values
num_grid_cells = 0
grid_size = 0
grid_offset = -1
! read task vector from exchange grid file
ALLOCATE(task(grid_size_global))
CALL hdlerr(NF90_OPEN(grid_filename, NF90_NOWRITE, nc), __LINE__ )
CALL hdlerr( NF90_INQ_VARID(nc, 'task' , varid), __LINE__ ) ! get variable id
CALL hdlerr( NF90_GET_VAR (nc, varid, task(:), [1], [grid_size_global]), __LINE__ ) ! get variable values
CALL hdlerr(NF90_CLOSE(nc), __LINE__ )
! go through the task vector and check which portion this intance will handle
DO i = 1, grid_size_global
IF (task(i) == mype) THEN
! count grid cells in this task
grid_size = grid_size + 1
! find grid offset (first index of this task - 1)
IF (grid_offset == -1) THEN
grid_offset = i-1
ENDIF
ENDIF
ENDDO
! task can also be empty
IF (grid_size == 0 .OR. grid_offset == -1) THEN
grid_size = 0
grid_offset = 0
ENDIF
num_grid_cells(1,mype + 1) = grid_size
! task vector is not needed anymore
DEALLOCATE(task)
ENDIF
ELSE
! this case is not yet implemented (but somehow prepared)
WRITE(*,*) "Only one bottom model is currently supported!"
ENDIF
END SUBROUTINE read_scrip_grid_dimensions
SUBROUTINE read_regridding_matrix(regridding_filename, &
@ -171,7 +214,6 @@ MODULE flux_calculator_io
CALL hdlerr( NF90_INQ_DIMID(nc, 'src_grid_rank' , varid), __LINE__ ) ! get variable id
CALL hdlerr( NF90_INQUIRE_DIMENSION(nc, varid, len=src_grid_rank), __LINE__ ) ! get variable values
WRITE (*,*) 'src_grid_rank ', src_grid_rank
CALL hdlerr( NF90_INQ_VARID(nc, 'src_grid_dims' , varid), __LINE__ ) ! get variable id
CALL hdlerr( NF90_GET_VAR (nc, varid, remapping_info%src_grid_dims(:), [1], [src_grid_rank]), __LINE__ ) ! get variable values

Loading…
Cancel
Save