[Haskell-cafe] Re: Type and State Confusion

Hans van Thiel hthiel.char at zonnet.nl
Mon Mar 12 12:51:23 EDT 2007


Albert,

Thanks very much for your explanation. I see now that I confused the
state function with the f, but it's still not quite clear. 

data MyState a b = MyStateC ([a] -> ([a], b))

This defines an algebraic data type (...why is it called algebraic?)
with two type variables and a unary constructor.
         
         instance Monad (MyState a) where
            return x = MyStateC (\tb -> (tb, x))
            (MyStateC st) >>= f =  
                MyStateC (\tb -> let                       
                                   (newtb, y) = st tb
                                   (MyStateC trans) = f y 
                                 in trans newtb )
        
        Now, if the instantiated a has type String, Int or whatever, I
        would understand, but the type of the Monad seems to be built up
        from two types.
        
        You write:
        ...y has type String. In more detail: in order for
           foo >>= toMyState
        to make sense, these must be the types:
           foo :: MyState String String
           st :: [String] -> ([String], String)
        y is forced to have type String for the sake of toMyState.
        
        But how do the two occurrences of String in the foo type, in
        general a and b, match to the single a in the instance
        declaration? In particular when I have:
        
        toMyState :: String -> MyState String Int   
        toMyState x = MyStateC (f x)
        
        This is mapped onto a list of strings, on which the Prelude
        sequence is applied.
        
        sequence :: Monad m => [m a] -> m [a]
        
        You write:
        The >>= used by sequence is the same >>= in the MyState monad,
        since you instantiate m to MyState String. Therefore, sequence
        performs all the state transformations correctly, since >>= is
        correct.
        
        So the m becomes MyState String, and therefore the list elements
        have type (MyState String Int), or the other way around. I
        understand, from your explanation, how this works from there on,
        but I'm still confused about what the Monad is. Is it MyState
        which takes two types, or (MyState String) which takes one type?
        Or neither? Does it involve some 'sort of currying' of type
        parameters?
        
        Thanks again,
        
        Hans
        
        
        
        
        
        



More information about the Haskell-Cafe mailing list