PROGRAM Test_Datatypes USE Precision USE ISO_C_BINDING USE F2x_Emulation USE Composite_Datatypes USE Space_Embedded_Data IMPLICIT NONE TYPE :: Hourly_Record REAL (KIND=r_wp) :: temperature (3) = 0.0 LOGICAL (KIND=l_byte) :: synny = .TRUE. END TYPE TYPE :: Daily_Record TYPE (Hourly_Record), DIMENSION (24) :: hourly_records INTEGER (KIND=i_sp) :: sunrise = 7, sunset = 18 END TYPE TYPE :: Weekly_Record TYPE (Daily_Record), DIMENSION (7) :: daily_records REAL (KIND=r_sp) :: forecast_success (5) END TYPE INTEGER, PARAMETER :: n_x = 3, n_y = 3 TYPE (Weekly_Record), DIMENSION (n_x, n_y), TARGET :: weekly_records TYPE (Component_Pointer_r_sp), DIMENSION (5) :: components REAL (KIND=r_wp), DIMENSION (:, :, :, :, :), POINTER :: temperatures REAL (KIND=r_wp), DIMENSION (:, :), ALLOCATABLE :: buffer REAL (KIND=r_wp), DIMENSION (:, :), POINTER :: selected_temperatures INTEGER :: i, j, day, hour DO i = 1, n_x DO j = 1, n_y DO day = 1, 7 DO hour = 1, 24 weekly_records(i, j)%daily_records(day)%hourly_records(hour)%temperature(:) = 1E6 * i + 1E4 * j + 1E3 * day + & & 1E1 * hour + (/ 1, 2, 3 /) END DO END DO END DO END DO components(1)%component => weekly_records(1, 1)%daily_records(1)%hourly_records(1)%temperature(:) components(2)%component => weekly_records(1, 1)%daily_records(1)%hourly_records(:)%temperature(1) components(3)%component => weekly_records(1, 1)%daily_records(:)%hourly_records(1)%temperature(1) components(4)%component => weekly_records(:, 1)%daily_records(1)%hourly_records(1)%temperature(1) components(5)%component => weekly_records(1, :)%daily_records(1)%hourly_records(1)%temperature(1) CALL ExtractComponent (components=components, component_pointer=temperatures) WRITE (*,*) "Lower bounds:", LBOUND (temperatures) WRITE (*,*) "Upper bounds:", UBOUND (temperatures) selected_temperatures => temperatures (2, 9:15:6, 1:3:2, 1, 3) ALLOCATE (buffer(SIZE(selected_temperatures, DIM=1), SIZE(selected_temperatures, DIM=2))) buffer = selected_temperatures WRITE (*,*) "The buffer contents:", Int (buffer) DEALLOCATE (buffer) END PROGRAM Test_Datatypes