next up previous 231
Next: More advanced header access
Up: More advanced image access
Previous: Creating multiple images


Handling ``bad'' data

In practice, astronomical images will often contain values that are unreliable (or unknown) and should be ignored. For example, you might not be able to compute a result for every element of an image array (say where a divide by zero would occur), or your detector system may not generate sensible values everywhere. These missing data are usually flagged by setting them to a unique number that allows them to be recognised, and this is known as the ``bad'' data value.2

Unfortunately, unless you have complete control over your data, you cannot usually ignore the possibility that an image may contain some of these ``bad'' values. If you did, and processed the numbers as if they were valid data, you would at best get the wrong answer. More probably, your program would crash.

To prevent you being baffled by this pitfall, IMG will normally check whether your input images contain any bad values and will issue a warning if any are found. Then at least you know why your program crashed!

You can deal with bad data values in one of two ways. The simplest is to use a suitable program to detect them and replace them with a sensible alternative value (for example, the KAPPA - SUN/95 - program NOMAGIC will do this). Alternatively, you can modify your IMG program to take proper account of them.

If you decide to modify your program, you'll probably want to inhibit the checks that IMG makes. This is done by appending an exclamation mark (!) to the parameter name of each affected image. So, for instance:

      CALL IMG_IN( 'BIAS!,FLAT!,RAW!', NX, NY, IP, ISTAT )
inhibits bad data value checking for all the input images.

The following example is a version of the mean.f program (see §[*]) that shows the sort of changes needed to deal with bad data:

      SUBROUTINE MEAN( ISTAT )

*  Access an input image. Inhibit checks for bad pixels.
      CALL IMG_IN( 'IN!', NX, NY, IP, ISTAT )                 [1]

*  Derive the mean and write it out.
      CALL DOSTAT( %VAL( IP ), NX, NY, ISTAT )

*  Free the input image.
      CALL IMG_FREE( 'IN', ISTAT )
      END

      SUBROUTINE DOSTAT( IMAGE, NX, NY, ISTAT )
      INCLUDE 'SAE_PAR'
      INCLUDE 'PRM_PAR'                                       [2]
      REAL IMAGE( NX, NY )

      IF ( ISTAT .NE. SAI__OK ) RETURN

*  Initialise the sum and loop over all elements of the image, checking
*  that every data value is not bad.
      SUM = 0.0
      N = 0
      DO 1 J = 1, NY
         DO 2 I = 1, NX
            IF ( IMAGE( I, J ) .NE. VAL__BADR ) THEN          [3]
               SUM = SUM + IMAGE( I, J )
               N = N + 1
            END IF
 2       CONTINUE
 1    CONTINUE

*  Write out the mean value.
      IF ( N .GT. 0 ) THEN
         WRITE( *, * ) 'Mean of ', N, ' values = ', SUM / REAL( N )
      ELSE
         WRITE( *, * ) 'Error: all data values are bad'
      END IF
      END
The following notes refer to the numbered statements:
1.
An input image is accessed without performing any checks for the presence of bad data.

2.
The file `PRM_PAR' is included. This defines Fortran parameters for the values used to flag bad data (it should be used by all programs that handle bad data). The parameter names are type-dependent and have the form VAL__BAD[x], where [x] is replaced by the character code for the data type you're processing. These codes are the same as those used when accessing images of different data types - see here. So, for instance, with REAL data you would use VAL__BADR, while with INTEGER data you would use VAL__BADI, etc. Before compiling a program that includes this file you should execute the command prm_dev, which creates a soft link to the include file.

3.
Since every input value may now potentially be bad, each one must be checked before use. As the data type being processed is REAL, the bad data value we test against is VAL__BADR.

If your program accesses more than one input image, you must be careful to check each of them. For instance if you were adding two images together you'd need to do something like the following:

      DO 1 I = 1, NX
         IF ( A( I ) .NE. VAL__BADI .AND. B( I ) .NE. VAL__BADI ) THEN
            C( I ) = A( I ) + B( I )
         ELSE
            C( I ) = VAL__BADI
         END IF
 1    CONTINUE

Where A and B are the ``images'' to be added and C is the image to store the result (in this case the images are really 1-D INTEGER spectra). Note how a bad value is assigned to the output image if we are unable to calculate a result.

If you need to know more about how to handle bad data you should consult SUN/33.



next up previous 231
Next: More advanced header access
Up: More advanced image access
Previous: Creating multiple images

IMG Simple Image Data Access
Starlink User Note 160
P.W. Draper
R.F. Warren-Smith
3 March 2003
E-mail:P.W.Draper@durham.ac.uk

Copyright © 2000-2003 Council for the Central Laboratory of the Research Councils