Beautiful functional programming

Sure. We have input data as a sequence of sequences. This naturally leads to a Haskell representation as a List of Lists. Functional languages (since LISP) are excellent at elegantly iterating (recursing) over lists, carrying state as they go. Haskell is the world’s finest imperative programming language, after all.

And we have a dude Jose Valim who seems not to know how to describe programming problems or fit a data design to a requirement. Irrelevant.

Addit: in response to the comment just below

I wasn’t commenting on anybody’s program-writing. I’m commenting (as had several others before me [**]) on the statement of requirements; the data model; the design process by which a requirement uncovered late in the development wasn’t reflected back into the data model. Development isn’t all programming – indeed as I expect we’ve all experienced – programming alone can’t rescue a design that’s a poor fit to the use-case. (And the elegant Haskell programs shown here can only be elegant because the use-case isn’t a key-value store, contra the claims in the design doco.)

[**] Indeed all the criticisms here had already been made 2½ years ago in the YCombinator discussions that @ReleaseCandidate linked to. Including disagreeing with Jose’s claim that @simonpj’s intro repeats “an imperative solution just seems easier and more diret [sic] than a purely functional one”. In particular:

… when you’re stuck with a poorly defined data structure, …
The whole problem seems to be bizarrely defined when it comes to data structures.
I’m not sure the problem reflect anything, …
IMO The problem is poorly defined. Data structures should avoid control flow instructions like “reset_lesson_position”

The author is aware of the fact that mutability makes this kind of problem easier

Not clear from the spec that mutating rather than building a fresh output stream is required. (In situ mutating is what the example Python script seems to be doing – including inserting an extra tagged value.) But to suggest mutability means the input must be some sort of key-value store, not tackled as sequential JSON-to-fresh-JSON. I don’t see how the input JSON as given could represent contents of a key-value store. (There’s no keys.)

So why after all that feedback 2½ years ago is O.P. still at programming conferences hawking this as a meaningful exercise, and making claims that have been discredited about imperative solutions?

@AntC2 Let’s accept that there are people with different views on how to write programs and keep our criticism constructive with objective arguments instead of just saying other people are incompetent.

Edit: the comment this was referring to has now been edited.

9 Likes

Yes it is contrived but it’s fun to see how concise you can get it. mapAccumL was a good tip:

{-# LANGUAGE 
      DuplicateRecordFields 
    , RecordWildCards 
    #-}

module Lib where 

import Data.Text (Text)
import Data.List (mapAccumL) 
import GHC.Generics 
import Data.Aeson


data Chapter = Chapter {
      title :: Text
    , reset_lesson_position :: Bool
    , lessons :: [Lesson]
    , position :: Maybe Int
    } deriving (Generic)
instance FromJSON Chapter 
instance ToJSON Chapter

data Lesson = Lesson {
      name :: Text
    , position :: Maybe Int
    } deriving (Generic)
instance FromJSON Lesson
instance ToJSON Lesson

book :: [Chapter] -> [Chapter]
book = snd . mapAccumL fo (1,1) 
    where 
    fo :: (Int, Int) -> Chapter -> ((Int, Int) , Chapter)
    fo (p1, p2) c = 
        let p3 = if reset_lesson_position c then 1 else p2
        in ( (p1 + 1, p3 + (length . lessons $ c))
           , c { position = Just p1
              , lessons = lo p3 (lessons c)  
              }
           )
          
    lo :: Int -> [Lesson] -> [Lesson]
    lo p = snd . mapAccumL no p

    no :: Int -> Lesson -> (Int, Lesson)
    no p l = (p + 1, l { position = Just p })
3 Likes

What I am wondering about is what exactly the creator of Elixir said or claimed. Maybe @simonpj can reference the actual words of his statement, so that we understand what he felt was a daunting task for functional languages? Perhaps all this is a storm in a teacup because this person never intended to “defy” functional languages in the first place?

Total storm in teacup! Jose is a very interesting, clever, and thoughtful person. I was just jotting down (several weeks later) my probably-inaccurate recollection of a conversation over a beer. The problem spec I referred to is the best reference. Stick to that!

2 Likes

mapAccumL can be implemented with an actual accumulating parameter, with the same interface. I just assume it’ll be less efficient (benchmarks?) without the StateT.

If any use of local state can be represented by StateT, then any use of local state can be represented by accumulating parameters. Then even without State monad, every use of imperative code with local state (mainstream definition of pure) can be represented by “pure” closures.

I actually posted the origin of the challenge to show that it is a typical problem imposed by a less than ideal :wink: interface to some program that you have to work around. Because you can’t change it now for whatever reason, be it that it’s some 3rd party e-learning app/service/… or you just don’t have the time.
And I can guarantee you that everybody of us has either already produced some similar (or worse) code or will do so in the future. I certainly have.

3 Likes

I imagine it would be exactly the same. It should desugar to almost identical code, becoming identical after optimization.

Why not foldr?

data Ev course lesson
  = NewCourse Bool (Int -> [lesson] -> course)
  | NewLesson (Int -> lesson)

-- probably a very simple call to `concatMap` depending on your datatype
fromCourses :: YourInput -> [Ev YourCourseType YourLessonType]
fromCourses = undefined 

makeCourses :: [Ev course lesson] -> [course]
makeCourses xs = foldr go (\_ _ c ls -> c (ls [])) xs 1 1 (const id) id []
  where
    go ev k !courseIx !lessonIx makeCourse lessons = case ev of
      NewLesson l ->
        k courseIx (lessonIx + 1) makeCourse (lessons . (l lessonIx:))
      NewCourse p c ->
        makeCourse (lessons []) .
        k (courseIx + 1) (if p then 1 else lessonIx) (\ls -> (c courseIx ls:)) id

whilst this solution is meant as a joke rather than real code, I don’t think it’s a particularly absurd solution. Turn your input data into some sort of builder, and then write something to run that builder.

4 Likes

Golfed version using Dynamic and with a newtype for Object over HashMap Text Dynamic:

{-# LANGUAGE OverloadedStrings #-}

import qualified Data.HashMap.Strict as HM
import Data.HashMap.Strict ((!))
import Data.Text (Text)
import Data.Dynamic
import Data.Bifunctor (second)
import Data.Maybe (fromJust)

import Data.Vector (Vector)

import Data.Traversable (mapAccumL)

newtype Object = MkObject {unObj :: HM.HashMap Text Dynamic}

hiJose :: V.Vector Object -> V.Vector Object
hiJose = snd . mapAccumL go (1 :: Int)
  where
    go count (MkObject obj) =
        second (\lessons -> MkObject $ HM.insert "lessons" (toDyn lessons) obj)
      . mapAccumL numberLessons
      (if flip fromDyn False $ obj ! "reset_lesson_position"
        then 1 else count) . fromJust . fromDynamic $ obj ! "lessons"
      where
        numberLessons subCount vecObj =
            ( subCount + 1, toDyn . MkObject
            . HM.insert "position" (toDyn count) . unObj . fromJust $ fromDynamic vecObj )

Yes, Map.(!) and fromJust is partial, but it sort of highlights in how the original implementations a malformed data input can blow you up.

2 Likes

Some problems require imperative thinking, and in most cases imperative solution is often easier. Seems like this is one instance of the general circumstances.

1 Like

It’s just mapAccumLs instead of for loops, tbh. (Did you catch the thread mentioning that higher order functions are replacements for for loops?)

What makes this actually hard is getting the correct data structure down (even the lazy “let’s define it as an HashMap Text Dynamic” becomes painful when you consider the type-tetris, and the fromJust annoys me).

1 Like

“Maybe storm in a teacup” was meant to say that maybe Jose never claimed that this problem was more challenging for functional languages, is all. Since I don’t know what he said, I have no clue. Besides I have not understood why this problem might be more difficult for functional languages, but that’s on me for not understanding.

Hi everyone, I am José Valim, who brought this topic to Simon. :slight_smile:

For more context, the problem was presented to me by someone who was familiar with an imperative language and was attempting to port an existing imperative application to Elixir, which is a functional language. I did not design it but I did write the spec down, as it was currently defined. If the problem description sounds utterly imperative, it was because it was made by someone who “thinks imperatively”.

Therefore, I would ask you to think about how you would explain the solution to someone who is just beginning their functional programming journey (after several years of writing imperative code!).


:smiley: I am quite familiar with mapAccumL. That seems to be the “go-to” answer for other functional languages in the repository and how I would solve it in Elixir too!

For clarity, Elixir is functional and its data structures are immutable. So I wouldn’t be expecting anyone to be solving this problem in Elixir with mutability either.


I asked Simon’s opinion on a private conversation, legitimately interested on his input, and I did give him permission to share this problem with others (which he kindly asked). I am also not the person linked in the HN comments above.

While I do believe the Python solution is more accessible (to my personal interpretation of accessible), I don’t think that my opinion is relevant at all. I don’t claim it openly in events nor do I claim it to be universally true. Nor do I have a goal of pushing imperative solutions, although I am quite interested in learning whenever possible how to ease the migration from an imperative to functional mindset, and that includes helping users tackle “artificial problems”. :slight_smile:

It is disappointing you chose to inaccurately portray both my intentions and my claims instead of engaging with the problem.


To everyone else, thank you for posting your solutions, I am sure I will learn something new.

29 Likes

Thanks for the clarification, I think your description of the situation implies something that’s very useful, and I think I’m personally non-plussed that I can’t get a solution more concise than the Python.

I’ve made a hobby of translating Python code into Haskell, and in my experience, Haskell is hard-pressed when it comes to imperative / effectful code (due to lacking early return without resorting to certain effect types or exceptions). It usually pulls ahead when it comes to functional / effectless code, however. Thus, because this problem is fundamentally effect-free, it’s annoying that it’s hard to deliver a clean, functional solution that can beat the Python.

2 Likes

For what is worth, I think it is fair game to rewrite the data structures to proper Haskell data structures instead of using the generic JSON ones. This could be, in itself, a good example of better modelling your problem/domain with types.

It’s not a question of “Haskell data structures”: it’s a question of an appropriate data structure for the application requirements. That could/should be equally expressible in JSON or any other data description formalism, including Haskell data types.

  • This is not a ‘key-value data structure’ in any sense. That wording appears only on your (José’s) github description, not the HN discussion. Why?

  • mapAccumL is indeed a nice higher-order function for hiding implementation ugliness:

[mapAccumL] passing an accumulating parameter from left to right, and returning a final value of this accumulator together with the new structure.

  • What ugliness? “left to right” ugliness. I really don’t see that just because an elegant solution can be expressed in Haskell, that makes the “left to right” solution somehow not imperative. I get it that I’m quibbling over semantics.
  • A Traversable is not a random-access nor key-value access style of data structure. For example imagine trying to insert an extra lesson into the middle of the structure: we have to bump up the position of all the following lessons, including crossing into the next title grouping to at least check if it has reset_lesson_position = True; if False carry on bumping up – possibly across many following title groupings.
1 Like

Here’s a different question, what’s the data structure for? I’m sort of the village idiot here; I don’t have enough experience to guess out the broader problem for which you’d design the data structure.

Excellent question! And not at all a ‘dumb question’. Perhaps …

  • A data structure for showing off the power of mapAccumL.
  • A data structure for showing what can go wrong when you don’t capture the full requirements at first.
  • A data structure that can’t possibly be a key-value structure.
  • A data structure to demonstrate the limits of “left to right” thinking. (Suppose for example the lessons are to be numbered from 1 starting at the end, as a countdown to when the learner has completed the topic area. That should be easy to do with a key-value data structure.)
1 Like