next up previous
Next: WRITEMAP - write Up: FORTRAN Examples Previous: READBIGIO - read

READMAP - read a map from a big image

*+  READMAP - read a map from a big image
      SUBROUTINE READMAP ( STATUS )
*    Description :
*     Read and print a rectangular area from a SuperCOSMOS mapping data set.
*    Invocation :
*     CALL READMAP ( STATUS )
*    Parameters :
*     STATUS=INTEGER (given and returned)
*           global status
*    Method :
*     Open the bigimage, extract a rectangular area and list its contents.
*    Authors :
*     B.D.Kelly (ROE)
*    History :
*     24.01.1995: original (BDK)
*    endhistory
*    Type Definitions :
      IMPLICIT NONE
*    Global constants :
      INCLUDE 'SAE_PAR'

*    Status :
      INTEGER STATUS

*    Local variables :
      CHARACTER*132 MAPNAME   ! name of directory to hold bigimage
      INTEGER BD              ! bigimage descriptor
      INTEGER*2 VALUES(200)   ! values read from the bigimage
      INTEGER J               ! loop counter
      INTEGER I               ! loop counter
      CHARACTER*80 OUTBUFF    ! output print buffer
      CHARACTER*132 ERRMSG    ! buffer for error messages
*-

      IF ( STATUS .NE. SAI__OK ) RETURN

*
*   Initialise the input array 
*
      DO J = 1, 200
         VALUES(J) = 0
      ENDDO
*
*   Get the mapname, which is the name of the directory to hold the
*   bigimage 
*
      CALL PAR_GET0C ( 'MAPNAME', MAPNAME, STATUS )
*
*   Open the bigimage, extract a 2-D rectangular map from it, and print
*   out the map 
*
      CALL COSMAP_OPEN ( MAPNAME, 'update', BD, STATUS )
      IF ( STATUS .NE. SAI__OK ) THEN
         CALL COSMAP_ERRTRAN ( ERRMSG, STATUS )
         CALL ERR_REP ( ' ', ERRMSG, STATUS )
      ELSE
         CALL COSMAP_GETMAP ( BD, 5, 5, 14, 24, VALUES, STATUS )
         DO J = 1, 20
            WRITE ( OUTBUFF, '(10I3)' ) (VALUES((J-1)*10+I),I=1,10)
            CALL MSG_OUT ( ' ', OUTBUFF, STATUS )
         ENDDO
         IF ( STATUS .NE. SAI__OK ) THEN
            CALL COSMAP_ERRTRAN ( ERRMSG, STATUS )
            CALL ERR_REP ( ' ', ERRMSG, STATUS )
         ENDIF
      ENDIF

      END



SuperCOSMOS development
Tue Aug 20 12:02:13 BST 1996