[Haskell-cafe] Re: Language support for imperative code. Was: Re: monad subexpressions

Isaac Dupree isaacdupree at charter.net
Sun Aug 12 15:49:45 EDT 2007


apfelmus wrote:
>   (3+)         :: Int -> Int
>   ([1,2]++)    :: [Int] -> [Int]
>   insert "x" 3 :: Map String Int -> Map String Int
> 
> Of course, from the purely functional point of view, this is hardly
> perceived as mutation since the original value is not changed at all and
> still available. In other words, the need to "change" a value doesn't
> imply the need to discard (and thus mutate) the old one.

Yes, and pure functions in Haskell often get funny imperative-sounding 
names like "insert" because of it - which is quite nice IMO.  I like 
perceiving it like mutation because 99% of the time these are used in 
the places that mutation normally needs to be used in imperative 
languages.  It is only occasionally that destructive mutation (for lack 
of a better name) is needed - for all I know, those situations may be a 
named "pattern" or something in imperative languages.

type Mutate a = a -> a
--I've also caught myself calling it Mon, Endo, IdF, Change ...
insert :: (Ord k) => k -> v -> Mutate (Map k v)

It's annoying when the arguments are in the wrong order, such as 
Data.Bits.shift. (perhaps for the flimsy excuse that they expected you 
to use it infix...)

> Mutable data structures in the sense of ephemeral (= not persistent = 
> update in-place) data structure indeed do introduce the need to work in 
> ST since the old version is - by definition - not available anymore. 

Not in the quantum/information-theoretic sense, not necessarily. Consider

import Control.Monad.ST
import Data.STRef
main = print (runST (do
    r <- newSTRef 1
    notUnavailable <- readSTRef r
    writeSTRef r 5
    return notUnavailable
  ))

Of course that's something you can do in imperative languages too, but 
it's still easier in Haskell where you don't have to worry about what 
something implicitly refers to, and can pass around anything (any data, 
functions, IO-actions) as first-class citizens :)  (including storing 
them in parametrically-polymorphic state-refs like STRef, and, even for 
non-polymorphic refs, you can get the value out and keep it after the 
mutatable state has changed)

See, the imperative paradigm has trouble scaling down to the quantum 
level, where information cannot be copied at will, too!  This proves why 
computers generate heat(entropy) from the unprincipled destruction of 
information.  Of course, computation near the quantum scale is a subject 
that has not nearly been thoroughly explored yet, but I suspect that 
(purely) functional languages are a little more likely to be easier to 
compile to such a type of machine, some decades from now...


Playfully,

Isaac


More information about the Haskell-Cafe mailing list