Why imperative code is worse than functional code

That seems to be saying the reason is libraries: volume of, complexity of. Sussman doesn’t mention models of computation.

Modern programming is not needing to understand at the level of data-items-through-processor (he’s saying); but rather what does this library do? (because it’s so humungous the docos are never adequate); what do these other libraries do? How do I plug the output from one into the input to another to get the solution? (I get the analogy of a 1,000-pin chip vs. individual capacitors and diodes, or even 12-pin ICs.)

So …? if LISP had plenty of libraries, MIT wouldn’t have switched? If Haskell – as a ‘glue’ language – could interface smoothly to Python libraries, he’d use Haskell? I fear Haskell’s laziness would remain as an insurmountable impedance mismatch.

…do try to remember that sentiment when you’re old! As for me…well, I prefer this depiction of certain CS luminaries:


…possibly, yes: it has been used to build entire operating systems.

…before giving up, perhaps we should see how another declarative language works with laziness:

Lazy Stream Programming in Prolog (2019).

I think the question shouldn’t be, “why is imperative code is worse than functional code”, but rather, “Is imperative code always worse than functional code, and if so, when is it better?”

That was essentially the point being made by Jose Valim / (maybe SPJ?) in the other thread.


As to whether imperative code is always worse; well, let’s say, we want a list of instructions; i.e, “wash the dishes, clean the sink, take out the trash”. The natural form of this list of instructions is, well, a list of sequential instructions. Should we specify instead “the house after the trash has been taken out, the sink has been cleaned, and the dishes have been washed” instead?

That is to say, there are some applications wherein by definition, imperative programming is better than functional programming because the problem is fundamentally imperative.


The other issue is that imperative programming is sort of played out, whereas functional programming still has a lot of life left in it for development and exploration. In my view, the Jose Valim question is basically just asking for better combinators (unconcat for lists, zipover, although most of these needs are already met by lens).

In the event that a good or better functional programming technique does yet not exist, imperative programming is better because you do not have to develop the alternative, and propagate the idiom to make it understandable.

Say, for instance, you’re working in a language without map or filter, and it’s not idiomatic to use such. In this case, you’d have to implement the map and filter functions yourself before use, which is unergonomic, and can help make your code less readable due to outside unfamiliarity with your idiom.


On the other hand, this does not mean that we should settle for C or Fortran in every language. Haskell, after all, is a research language.

We should be appreciating and looking forward to problems like the ones Jose Valim proposed, because it’s through problems that we find and push the limits of functional programming.

2 Likes
  • Say, for instance, you’re working in a language without map or filter, and it’s not idiomatic to use such. […]

    Hrm. Say you’re working in a language without convenient access to mutation e.g. Haskell, and it’s not idiomatic to use such a feature in said language…

    • (removeTrash . cleanSink . washDishes) :: House -> House

    • (removeTrash' <=< cleanSink' <=< washDishes') :: House' -> ST s House'

  • […] there are some applications [for] imperative programming because the problem is fundamentally imperative.

    • In the event that a good or better functional programming technique does yet not exist […]

    …and that’s where you would first try using encapsulated state (ST, runST and co.)

  • In my view, the Jose Valim question is basically just asking for better combinators […]

    “How many combinators does it take to screw in a light bulb?”

  • […] it’s through problems that we find and push the limits of functional programming.

    …you mean like the lack of adoption of nonstrict evaluation in newer languages such as Elixir?

1 Like
  • (removeTrash . cleanSink . washDishes) :: House -> House
  • (removeTrash' <=< cleanSink' <=< washDishes') :: House -> ST s House

Which poses a worse problem, no? This is a chain of function applications, and the first problem is that it’s (.), not (>>>). The bigger problem is that you can think of function applications imperatively, i.e, you are working in a pipeline, taking the action of transforming values from a → b, and so on. Church-Turing, no?

Given that ST / runST perform worse than State.Strict.State with modify’ in many cases, it might not be a good idea. Accumulating parameters and Strict State give enough access to essentially imperative thinking.

There’s also the question of, well, since statements in Haskell (check Haskell Report 2010) are values in do notation, whether it’s more convenient and flexible to have access to:

[ washDishes
, cleanSink
, removeTrash
]

wherein it’s possible to sequence_ the operations together, as well as reverse, foldr, and so on on the [HouseAction]. A bit Lispy I guess.


My own stance is, well, generally, the four cases where essentially imperative code are acceptable are:

  • You are throwing effects, and Conal Elliott’s ask for a better alternative to IO and monads hasn’t been fully fulfilled, despite monad transformers, free monad interpreters, and effect libraries.
  • You need more precise control over performance, or just better performance.
  • You’re limiting your idiom to make the codebase easier to onboard onto.
  • You don’t have a better functional solution available.

My real opposition here is against the desire to “declare victory” and be done with it. The last I checked, no one had managed to get a zip solution that was more succinct than the Python, and I suspect this can’t be done without lenses (after which it’s roughly a 2-3 liner; the real issue with this problem for Haskell I think is that Haskell runs on ADTs, not objects, and you either cheat with the datatype, sacrificing fidelity, or resort to lenses, which exist to make this problem go away, but do so at the cost of readability).

2 Likes

No.

If you allow mutation in a programming language, you are immediately confronted with a choice: sequencing or nondeterminism. Furthermore if you allow mutation to be accessed from (potentially) everywhere in that language, then the choice of sequencing or nondeterminism will also apply everywhere.

My first example - (removeTrash . cleanSink . washDishes) is only sequential: no mutation involved.

As for the second example, let’s assume the worst: House House' is STRef-based and therefore relies on mutation. Now for that choice - we don’t want nondeterminism so we must choose sequencing, which the monadic ST type provides. But fortunately for us, there’s also runST, which allows us to keep the use of mutation (and the need for sequencing) private: nice!


…and given it’s similarity to (strict) ST in GHC, is IO also affected?


Considering that Haskell continues to require mutation (and therefore sequencing) for I/O, after the better longer part of three decades, I suspect that such a declaration will not be happening any time soon. So our functional programs will continue to be boats in an imperative sea, and we will have to keep watch for, and reseal leaking hulls:

https://discourse.haskell.org/t/an-epic-future-for-spj/3573/9

Implicitly, RW, no? Remove trash, clean sink, wash dishes, these are actions outputting to a global state. So there is an implicit form of mutation occurring because we are jumping from the semantics of a functional programming language to a real world; i.e, in Haskell, House would be a wrapper, effect system, or monad transformer stack over IO.

So perhaps we’re misunderstanding each other.


As to IO vs ST, I’ve seen cases wherein IORefs seem to optimize better than pure code (IORef is used as a data carrier here for unsafePerformIO).


As to declaring victory, accumulating parameter might be “simulating” state or having state be handled by the compiler, but it’s still effectively stateful in that state is being stored in a function argument. That’s why I kept on going back to the Jose Valim problem; I kept on trying to get a Lens-based solution out of it that would avoid the need for quasi- or crypto-imperative State Monad.

1 Like

[…] perhaps we’re misunderstanding each other.

…yes, I was. I was thinking too abstractly :-D

For real houses, then only the second example is valid Haskell:

(removeTrash'' <=< cleanSink'' <=< washDishes'') :: House'' -> IO House''

…with the correct type/s, of course. And those would be actions outputting to a global/shared state, namely the set of I/O registers of the computer running the “cleaning program”.

Because that mutable resource (those I/O registers) is potentially available everywhere in the program, there’s no (legitimate!) way to encapsulate its use. So that choice to use sequencing now spreads out to all definitions which rely on I/O, all the way up to Main.main.

I think trying to avoid state is a mistake. You have a dependency on previous results. Any solution that “avoids state”, is going to be state in disguise, probably just using the previous result and an extraction function to hide it (e.g instead of (Int, Int) -> (Section, (Int, Int)) or State (Int, Int) Section, it’ll be Section -> Section and a function Section -> (Int, Int))

1 Like

Never mind snippets, there was a whole methodology: Jackson Structured Programming. And a technique ‘Common Action Tail’. (You can even apply JSP to C++ – section 1.1.2. Take a stiff drink before looking there.)

The idea was that after a many-branching case analysis to deal with your business logic, there’s often a need for some sort of ‘tidy up’ to return the answer plus clear out any temp file access or records/variables. Rather than calling some common routine (with all that unnecessary stack-handling) just jump/goto the tail of the module. There is one place to guarantee the tidiness.

That is the whole point of Haskell and similar languages, make those implicit assumptions explicit in signatures.

foo :: StdGen -> (a, a) -> (StdGen, a)

Now you can — among other things — use a simple substitution model to reason about your function, test it thoroughly in isolation, etc. It would be not so easy with

foo :: (a, a) -> a

Do we though? The main seemingly sequential part of the original problem was the generation of the sequence of natural numbers [1..]. But you can do that in parallel chunks:

concatMap (\i -> [i, i + 1 .. i + k - 1]) [1, 1 + k ..]

Using this approach we could number an array of lessons in parallel.

But it gets more complicated for the case of nested lists like this simplified version of the problem I suggested in the other thread:

Define f :: [[a]] -> [[(Int, a)]] such that for all a :: Type and x :: [[a]] we have map fst (concat (f x)) == [1 .. length x].

Then we would like to split the generated list of natural numbers into lists that are the same length as the sublists of the input:

f xs = zipWith zip (_split_ nats) xs

Again, we can do that relatively efficiently if the lessons are stored in arrays which can report their length in constant time.

What about introducing

reStructure :: [[a]] -> [b] -> [[b]]
reStructure [] _ = []
reStructure _ [] = []
reStructure ([]:xss) ys = []: reStructure xss ys
reStructure ((x:xs):xss) (y:ys) = 
  case reStructure (xs:xss) ys of
    [] -> [[y]]
    (ys':yss') -> (y:ys'):yss'

which basically copy the structure of double list so that reStructure ["abc","d", "ef"] [1..] return [[1, 2, 3], [4], [5,6]]. Is that a state in disguise ?

Let’s have this little helper

breakOn :: (a -> Bool) -> [a] -> [[a]]
breakOn f = groupBy (const $ not . f)

Which split a list (without removing the separator), I couldn’t find it in the prelude.

Let’s also decouple finding the positions and updating the initial result in two different problem.
The first problem "Fiding the lesson number becomes

lessonPosititions :: [Section a] -> [[Int]]
lessonPosititions sections = 
    concatMap (flip reStructure [1..] . map lessons)  $ breakOn resetLessonPosition sections

This is my functional answer to the initial problem
Note, that it only uses helper functions which have nothing to do with the initial problem and could be in Base somewhere.

Finding the sessiong number is just zip [1..].

The ugly bit is to update the data (that’s where Haskell is not great

updatePositions :: [Section a] -> [(Int, [Int])] -> [Section Int]
updatePositions =
  zipWith (\s (sp, poss) -> s {sposition = sp
                              , lessons = zipWith (\l p -> l { lposition = p})
                                                  (lessons s)
                                                  poss
                              }

Mixing both becomes

    updatePositions sections (zip [1..] $ lessonPosititions sections)

(full code inspired from @tomjaguarpaw gist).

You’ve defined breakOn in terms of groupBy. groupBy is defined in terms of span which has the following type

span :: (a -> Bool) -> [a] -> ([a], [a])

or, equivalently

span :: (a -> Bool) -> State [a] [a]

In fact, we can use this to give an alternative formulation of groupBy which at first glance looks very different, but is actually pretty much the same as the definition in base.

{-# LANGUAGE LambdaCase #-}
import Control.Monad.State
import Data.Coerce
import Data.Functor.Identity -- to coerce through `Identity`

-- A little helper
next :: forall a . State [a] (Maybe a)
next = coerce @([a] -> (Maybe a, [a])) $ \case
  [] -> (Nothing, [])
  (x:xs) -> (Just x, xs)

groupBy' :: (a -> a -> Bool) -> State [a] [[a]]
groupBy' eq = next >>= \case
  Nothing -> pure []
  Just x -> do
    ys <- coerce $ span (eq x) -- it really is State [a] [a]
    ((x:ys):) <$> groupBy' eq

groupBy'' :: forall a . (a -> a -> Bool) -> [a] -> [[a]]
groupBy'' eq = fst @_ @[a] . coerce (groupBy' eq)

At the end of the day, you’re still using the “state monad” to solve this problem.

edit: add groupBy'' to demonstrate groupBy' is actually close in type to groupBy

So is zip (or spiritual equivalents) hiding state?

Instead of an accumulator holding a temporary state, we’re holding a list whose starting point is clipped by zip.

Is (enumFromTo ‘a’ ‘z’ `zip` enumFromTo 1 26) stateful?


Since, in my mind, the stateless solution to this is based on zips. If we consider zip stateful, then, perhaps it’s impossible to have a stateless solution to this problem.

1 Like

Wow, that’s a long shot.

Got rid of the spans here.

{-# LANGUAGE ScopedTypeVariables #-}

chunkUntil :: forall a. (a -> Bool) -> [a] -> [[a]]
chunkUntil cond [] = []
chunkUntil cond list = case chunk of
    [] -> remainder
    a -> a : remainder
  where
    chunk :: [a]
    chunk = takeWhile (not . cond) list
    
    remainder :: [[a]]
    remainder = case rawRemainder of
        (a:as) -> case chunkUntil cond as of
            [[]] -> [[a]]
            [] -> [[a]]
            ((b:bs):cs) -> (a:b:bs):cs
            (([]):cs) -> [a]:cs
        [] -> []
        
    rawRemainder :: [a]
    rawRemainder = dropWhile (not . cond) list

Still got hidden state?

I’ll also remark, the takeWith / dropWith is hideously unperformant (I can’t expect GHC to optimize this into a single loop), so the spans implementation of groupBy is fine on the “performance” argument for use of imperative / stateful code in Haskell.

1 Like

Now that you’ve got me thinking, how do you like this zipWith based solution?

data Section n = Section
  { sname :: String
  , lessons :: [Lesson n]
  , restart :: Bool
  , sectionNum :: n
  } deriving Show

data Lesson n = Lesson
  { lname :: String
  , lessonNum :: n
  } deriving Show

numberSections :: [Section ()] -> [Section Int]
numberSections secs = result
  where
    awaitNumber :: Section () -> (Int, Int) -> Section Int
    awaitNumber sec (sn, ln) = sec
      { sectionNum = sn
      , lessons = zipWith (\l n -> l { lessonNum = n }) (lessons sec) [if restart sec then 1 else ln ..]
      }
    cursor :: Section Int -> (Int, Int)
    cursor sec = (sectionNum sec + 1, last (1:map lessonNum (lessons sec)) + 1)
    result :: [Section Int]
    result = zipWith ($) (map awaitNumber secs) ((1,1): map cursor result)
1 Like

My thing about state was mainly spawned by you calling the “state monad” imperative. If you’re happy with it, I guess it doesn’t matter. I wasn’t suggesting that you avoid state, I was trying to see if I could convince you that it’s not inherently “imperative”.

Your zipWith sort of includes state via iterating the map cursor result and creating a quasi state that gets updated (cursor).

Unless, perhaps, what we are really looking to do is:

-Establish a stateless version of the algorithm, that is not necessarily performant.
-Establish a stateful version of the algorithm that may be cleaner, and may be more performant.
-Use equational reasoning to prove that they have the same semantics, if not implementation, then go with the stateful version for pragmatic reasons?


Perhaps that’s the dog bone we need to throw to purity?


TBH, this comes down to “are anamorphisms not functional because they generate a seed state which they effectively mutate”? And I guess that’s going too far. Point made.