[Haskell] getArgs, maxBound, float division: pure functions?

oleg at pobox.com oleg at pobox.com
Tue Oct 11 02:04:28 EDT 2005


The question of getArgs as a pure function has already been
debated on this list back in January:

  http://www.haskell.org/pipermail/haskell/2005-January/015184.html

The topic seems worth revisiting as it expands to a bigger, and
perhaps, a bleaker picture.

To recap, there were two arguments for getArgs to remain with the 
IO [String] type:

	1. getArgs is the function of the environment and does not
have a clear denotation. The value of getArgs may change from one
program run to another.

	2. The existence of System.Environment.withArgs

Regarding argument 1: the value of |maxBound :: Int| is also the
function of the environment. Haskell98 Report says [p82, Section
6.4]

   The finite-precision integer type Int covers at least the range 
   [ - 2^29 , 2^29 - 1 ]. As Int is an instance of the Bounded class, 
   maxBound and minBound can be used to determine the exact Int range
   defined by an implementation.

Thus, the value of |maxBound :: Int| may conceivably change from on
program run (under runhugs32 on an AMD64 platform) to another (under
runghc64 on the same platform). The Haskell98 Report, in section 6.4.6
defines other implementation-dependent functions: floatRadix,
floatDigits, and floatRange. The GHC documentation
[ghc6/libraries/base/Prelude.html#t%3ARealFloat] is particularly
revealing:

  floatRadix :: a -> Integer
  a constant function, returning the radix of the representation (often 2)

Some may find the phrase ``constant function that often [sic!]
has the value 2'' to be incompatible with the notion of a pure
function.

Regarding argument 2: the existence of System.Environment.withArgs
seems to doom getArgs to remain with the IO type. It cannot be a pure
function. The simple extension of the argument points however to
inconsistency with the floating-point facility. Haskell98 Report
permits an implementation to use IEEE FP for Haskell Floats and
Doubles. The Report specifically provides the class RealFrac to give a
program access to some aspects of the IEEE FP system. IEEE FP
computations are sensitive to the rounding mode, which is observable
in pure code. The rounding mode can be changed. The following simple
program shows

> {-# OPTIONS -fglasgow-exts #-}
> -- Tested on GHC 6.4 on on i686/Linux
>
> module FP where
> import Foreign.C
>
> eps ::Float = 2^^(1-24)
>
> -- from /usr/include/bits/fenv.h
>
> type FP_RND_T = CInt  -- fenv.h
>
> eFE_TONEAREST = 0
> eFE_DOWNWARD = 0x400
> eFE_UPWARD   = 0x800
> eFE_TOWARDZERO = 0xc00
>
> foreign import ccall "fenv.h fegetround" fegetround 
>   :: IO FP_RND_T
>
> foreign import ccall "fenv.h fesetround" fesetround
>   :: FP_RND_T -> IO FP_RND_T
>
> test1 = do
>         let tf () = 1 + eps/2
>         let tfe = tf ()
>         putStrLn "Rounding mode and the result"
>         fegetround >>= print
>         print $ tf ()
>         print $ tfe
>
>         old <- fesetround eFE_UPWARD
>         putStrLn "Rounding mode and the result"
>         fegetround >>= print
>         print $ tf ()
>         print $ tfe
>
>         fesetround old
>         putStrLn "Rounding mode and the result"
>         fegetround >>= print
>         print $ tf ()
>         print $ tfe
>         print "Done"

that the supposedly pure computation "1 + eps/2" is not, in fact,
referentially transparent. Should all floating-point computations be
put in the IO monad?

Granted, FP addition, among other operations, is not associative; so
one may even wonder if FP can be done in any monad at all. OTH, when
it comes to IO, the monad laws are usually stretched.



More information about the Haskell mailing list