Why can't I use IO constructor

后端 未结 3 1170
陌清茗
陌清茗 2021-02-04 05:39

Why can\'t I do this:

import Data.Char

getBool = do
  c <- getChar
  if c == \'t\' 
    then IO True 
    else IO False

instead of using

相关标签:
3条回答
  • 2021-02-04 06:00

    There is very little magic around IO and ST monads, much less than most people believes.

    The dreaded IO type is just a newtype defined in GHC.Prim:

    newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))
    

    First of all, as can be seen above the argument of IO constructor is not the same as the argument of return. You can get a better idea by looking at a naive implementation of State monad:

    newtype State s a = State (s -> (s, a))
    

    Secondly, IO is an abstract type: it's an intentional decision not to export the constructor so you can neither construct IO nor pattern match it. This allows Haskell to enforce referential transparency and other useful properties even in presence of input-output.

    0 讨论(0)
  • 2021-02-04 06:06

    You can use IO instead of return. But not such easy. And you also need to import some inner modules.

    Let's look at source of Control.Monad:

    instance  Monad IO  where
        {-# INLINE return #-}
        {-# INLINE (>>)   #-}
        {-# INLINE (>>=)  #-}
        m >> k    = m >>= \ _ -> k
        return    = returnIO
        (>>=)     = bindIO
        fail s    = failIO s
    
    returnIO :: a -> IO a
    returnIO x = IO $ \ s -> (# s, x #)
    

    But even to use IO instead of return, you need to import GHC.Types(IO(..)):

    newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))
    

    After this, you can write IO $ \ s -> (# s, True #) (IO is a State) instead of return True:

    Solution:

    {-# LANGUAGE UnboxedTuples #-}  -- for unboxed tuples (# a, b #)
    {-# LANGUAGE TupleSections #-}  -- then (,b) == \a -> (a, b)
    import GHC.Types (IO (..))
    import Data.Char
    
    getBool = do
      c <- getChar
      if c == 't' 
        then IO (# , True #)
        else IO (# , False #)
    
    0 讨论(0)
  • 2021-02-04 06:17

    Background

    I'll answer the slightly broader (and more interesting) question. This is because there is, at least from a semantical standpoint, more than one IO constructor. There is more than one "kind" of IO value. We can think that there is probably one kind of IO value for printing to the screen, one kind of IO value for reading from a file, and so on.

    We can imagine, for the sake of reasoning, IO being defined as something like

    data IO a = ReadFile a
              | WriteFile a
              | Network a
              | StdOut a
              | StdIn a
              ...
              | GenericIO a
    

    with one kind of value for every kind of IO action there is. (However, keep in mind that this is not actually how IO is implemented. IO is magic best not toyed with unless you are a compiler hacker.)

    Now, the interesting question – why have they made it so that we can't construct these manually? Why have they not exported these constructors, so that we can use them? This leads into a much broader question.

    Why would you want to not export constructors for a data type?

    And there are basically two reasons for this – the first one is probably the most obvious one.

    1. Constructors are also deconstructors

    If you have access to a constructor, you also have access to a de-constructor that you can do pattern matching on. Think about the Maybe a type. If I give you a Maybe value, you can extract whatever is "inside" that Maybe with pattern matching! It's easy.

    getJust :: Maybe a -> a
    getJust m = case m of
                  Just x -> x
                  Nothing -> error "blowing up!"
    

    Imagine if you could do this with IO. That would mean IO would stop being safe. You could just do the same thing inside a pure function.

    getIO :: IO a -> a
    getIO io = case io of
                 ReadFile s -> s
                 _ -> error "not from a file, blowing up!"
    

    This is terrible. If you have access to the IO constructors, you can create a function that turns an IO value into a pure value. That sucks.

    So that's one good reason to not export the constructors of a data type. If you want to keep some of the data "secret", you have to keep your constructors secret, or otherwise someone can just extract any data they want to with pattern matching.

    2. You don't want to allow any value

    This reason will be familiar to object-oriented programmers. When you first learn object-oriented programming, you learn that objects have a special method that is invoked when you create a new object. In this method, you can also initialise the values of the fields inside the object, and the best thing is – you can perform sanity checking on these values. You can make sure the values "make sense" and throw an exception if they don't.

    Well, you can do sort of the same thing in Haskell. Say you are a company with a few printers, and you want to keep track of how old they are and on which floor in the building they are located. So you write a Haskell program. Your printers can be stored like this:

    data Printer = Printer { name :: String
                           , age :: Int
                           , floor :: Int
                           }
    

    Now, your building only has 4 floors, and you don't want to accidentally say you have a printer on floor 14. This can be done by not exporting the Printer constructor, and instead having a function mkPrinter which creates a printer for you if all the parameters make sense.

    mkPrinter :: String -> Int -> Maybe Printer
    mkPrinter name floor =
      if floor >= 1 && floor <= 4
         then Just (Printer name 0 floor)
         else Nothing
    

    If you export this mkPrinter function instead, you know that nobody can create a printer on a non-existing floor.

    0 讨论(0)
提交回复
热议问题