PROGRAM READFPP ! ! Reads in pp files ! IMPLICIT NONE ! ! Variables ! INTEGER, PARAMETER :: N_TOTAL_MONTHS = 1536 ! Number of ppfields, equal to number of months INTEGER :: I, J ! Loop variables INTEGER, DIMENSION(45) :: IHEAD ! Integer header REAL, DIMENSION(19) :: RHEAD ! Real header REAL, ALLOCATABLE, DIMENSION(:) :: ALONG ! Array of longitudes REAL, ALLOCATABLE, DIMENSION(:) :: ALAT ! Array of latitudes REAL, ALLOCATABLE, DIMENSION(:,:) :: DATA ! Data array ! ! Open file ! OPEN( UNIT = 10, & ACTION = "READ", & FILE = "/clim_var/hc2100/OBS/marine/HadISST/karl/"// & "hadisstbc_sic_72x36_1871_1998.pp", & FORM = "UNFORMATTED", & STATUS = "OLD") ! ! Loop over the total number of months in the file ! DO I = 1, N_TOTAL_MONTHS ! ! Read the mixed integer/real header ! READ(UNIT = 10) IHEAD, RHEAD ! ! Allocate space for the longitude, latitude and data arrays using ! the number of longitudes (ihead(19)) and the number of latitudes ! (ihead(18)). ! IF (.NOT. ALLOCATED (ALONG)) THEN ALLOCATE (ALONG(IHEAD(19))) ELSE DEALLOCATE (ALONG) ALLOCATE (ALONG(IHEAD(19))) END IF ! IF (.NOT. ALLOCATED (ALAT)) THEN ALLOCATE (ALAT(IHEAD(18))) ELSE DEALLOCATE (ALAT) ALLOCATE (ALAT(IHEAD(18))) END IF ! IF (.NOT. ALLOCATED (DATA)) THEN ALLOCATE (DATA(IHEAD(19), IHEAD(18))) ELSE DEALLOCATE (DATA) ALLOCATE (DATA(IHEAD(19), IHEAD(18))) END IF ! ! Compute the longitude and latitude arrays from header data ! DO J = 1, IHEAD(19) ALONG(J) = RHEAD(16) + FLOAT(J)*RHEAD(17) ENDDO ! DO J = 1, IHEAD(18) ALAT(J) = RHEAD(14) + FLOAT(J)*RHEAD(15) ENDDO ! ! Read data array ! READ(UNIT = 10) DATA ! ! Quick check to see what we have got ! WRITE(6,*) IHEAD(1), IHEAD(2), ALONG(1), ALAT(1), DATA(1, 1) END DO ! CLOSE(10) ! END