[Haskell] Re: Simple IO Regions

Brandon Moore brandonm at yahoo-inc.com
Sat Jan 21 02:55:02 EST 2006


It seems the "Simple IO Regions" are insecure:

 > {-# OPTIONS -fglasgow-exts #-}
 >
 > module BreakIORegions where
 >
 > import IORegions
 > import Control.Monad

In particular, we can build actions involving a handle inside its scope, 
and execute them outside.

Look closely at the type error from Oleg's test 8:

IORegionsTest.lhs:36:53:
     Could not deduce (IORegions.IN mark marks1)
       from the context (IORegions.IN mark marks)
       arising from use of `qGetChar' at IORegionsTest.lhs:36:53-60
     Probable fix:
       add (IORegions.IN mark marks1) to the expected type of an expression
     In the first argument of `return', namely `(qGetChar q)'
     In a lambda abstraction: \ q -> return (qGetChar q)
     In the second argument of `withFile', namely `(\ q -> return 
(qGetChar q))'

The problem isn't anything about which marks are present - it's because
the application qGetChar q somehow ended up with a different type 
variable "marks1" than the marks variable used in this instance of IOM.

I don't understand why trying to use the returned action later on isn't
enough to force the types to unify, but maybe GHC is a little too eager
to figure out whether class constraints are satisfied.

Anyway, we can leak an action if we give it a little help in unifying 
the types, here with lexically scope type variables

 > test1 = let (body :: IOM marks Char) =
 >               do a <- withFile "/etc/motd"
 >                          (\q -> return (qGetChar q)
 >                                   :: IOM marks (IOM marks Char))
 >                  a
 >         in body
 > test1r = runIOM test1 >>= print

Or more compactly with join:

 > test = runIOM (join (withFile "/etc/motd" (return . qGetChar))) >>= print

Brandon Moore


More information about the Haskell mailing list