The infinity of the series isn't much of a problem: any Turing-complete language can deal with infinities. In procedural languages this tends to require rather ugly loop constructs. It's much nicer in lazy functional languages, the most prominent being Haskell.
As for the algorithm itself – you can do something usable (if somewhat boring; the solution you quoted allows a bit more jazzy stuff) quite easily, based on resolving dominants.
module PiMelody where
import Data.List
data MelodyNote = Gs | A | B | C' | D' | E' | F' | Gs' | A' | B'
deriving (Eq, Show, Enum)
type Melody = [MelodyNote] -- Assume simple all-quavers rythm.
piMelody :: Melody
piMelody = map toEnum piDigits
data Chord = Am | Dm | C | G7 | E
deriving (Eq, Show, Enum)
type Composition = [(Melody, Chord)]
-- (Infinite) list of pairs: a melody chunk, and what chord to go with it.
chordMNotes :: Chord -> [MelodyNote] -- Without suspensions.
chordMNotes Am = [A , C', E', A']
chordMNotes Dm = [A , D', F', A']
chordMNotes E = [Gs, B , D', E', Gs', B', F'] -- Minor dominant may also be diminished-7th.
chordMNotes C = [C', E']
chordMNotes G7 = [B , D', F', B']
resolves :: Chord -> [Chord]
resolves E = [Am, E] -- Dominants should resolve to their tonic, if at all.
resolves G7 = [C, G7, Am, E] -- For major dominant, allow also resolving to minor parallels.
resolves _ = [Am .. E] -- Non-dominant chord can resolve to anything.
accompany :: Melody -> Composition -- Choose suitable chords for a melody.
accompany melody = acc Am melody
where acc :: Chord -> Melody -> Composition
acc lastChord (n1:n2:ml) -- Try to find a chord that fits over two melody notes
| (Just nextChord) -- and works with the previous (possibly dominant) chord.
all(`elem` chordMNotes ch) [n1,n2]) $ resolves lastChord
= ([n1,n2], nextChord) : acc nextChord ml
-- If two melody notes don't fit in one chord, use two.
| (Just c1)
(Code as a GitHub Gist)
It can be used thus:
$ ghci PiMelody.hs
GHCi, version 7.6.2: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling PiMelody ( PiMelody.hs, interpreted )
Ok, modules loaded: PiMelody.
*PiMelody> take 24 $ accompany piMelody
[([C',A],Am),([D',A],Dm),([E',B'],E),([B,F'],E),([E',C'],Am),([E',A'],Am),([B',Gs'],E),([B'],E),([C'],Am),([B],G7),([C'],C),([A',D'],Dm),([F',B],G7),([F',D'],G7),([C',C'],C),([A',C'],Am),([B,Gs'],E),([B',E'],E),([Gs,B],E),([A',A'],Am),([D',A],Dm),([B',Gs'],E),([A],Am),([F'],Dm)]
Here's a demo on Ideone.com, producing thousands of notes until time-out.