Basically, we need this list:
Blub : Zarg : [ Parg x y | {- `x`,`y` from all possible `Blurg` values -} ]
Well, actually you can write this out just like that in Haskell:
allBlurg :: [Blurg]
allBlurg = Blub : Zarg : [ Pargs x y | x<-allBlurg, y<-allBlurg ]
BTW this is not a function, though the definition is recursive. In Haskell, values can be recursive!
Perhaps the above is actually what was expected in the task. Trouble is, it's actually wrong: not all Blurg
values will be contained! The reason being, y<-allBlurg
has to work through an infinite list. It will never get to the end, therefore x
will stay forever at the first element. I.e., with that “solution”, you'll actually only get lists of the form
Pargs Blub . Pargs Blub . Pargs Blub . Pargs Blub ... Pargs Blub $ x
but never Pargs x y
with some x
apart from Blub
.
What's needed to solve this problem: enumerate combinations from two infinite lists. That's the Cantor pairing function, a Haskell implementation is available here.
{-# LANGUAGE MonadComprehensions #-}
import Control.Monad.Omega
allBlurg :: [Blurg]
allBlurg = Blub : Zarg : runOmega [ Pargs x y | x <- each allBlurg
, y <- each allBlurg ]
GHCi> :set -XMonadComprehensions
GHCi> :m +Control.Monad.Omega
GHCi> let allG = B : Z : runOmega [ P x y | x <- each allG, y <- each allG ]
GHCi> take 100 allG
[B, Z, P B B, P B Z, P Z B, P B (P B B), P Z Z, P (P B B) B,
P B (P B Z), P Z (P B B), P (P B B) Z, P (P B Z) B, P B (P Z B),
P Z (P B Z), P (P B B) (P B B), P (P B Z) Z, P (P Z B) B,
P B (P B (P B B)), P Z (P Z B), P (P B B) (P B Z), P (P B Z) (P B B),
P (P Z B) Z, P (P B (P B B)) B, P B (P Z Z), P Z (P B (P B B)),
P (P B B) (P Z B), P (P B Z) (P B Z), P (P Z B) (P B B),
P (P B (P B B)) Z, P (P Z Z) B, P B (P (P B B) B), P Z (P Z Z),
P (P B B) (P B (P B B)), P (P B Z) (P Z B), P (P Z B) (P B Z),
P (P B (P B B)) (P B B), P (P Z Z) Z, P (P (P B B) B) B,
P B (P B (P B Z)), P Z (P (P B B) B), P (P B B) (P Z Z),
P (P B Z) (P B (P B B)), P (P Z B) (P Z B), P (P B (P B B)) (P B Z),
P (P Z Z) (P B B), P (P (P B B) B) Z, P (P B (P B Z)) B,
P B (P Z (P B B)), P Z (P B (P B Z)), P (P B B) (P (P B B) B),
P (P B Z) (P Z Z), P (P Z B) (P B (P B B)), P (P B (P B B)) (P Z B),
P (P Z Z) (P B Z), P (P (P B B) B) (P B B), P (P B (P B Z)) Z,
P (P Z (P B B)) B, P B (P (P B B) Z), P Z (P Z (P B B)),
P (P B B) (P B (P B Z)), P (P B Z) (P (P B B) B), P (P Z B) (P Z Z),
P (P B (P B B)) (P B (P B B)), P (P Z Z) (P Z B),
P (P (P B B) B) (P B Z), P (P B (P B Z)) (P B B), P (P Z (P B B)) Z,
P (P (P B B) Z) B, P B (P (P B Z) B), P Z (P (P B B) Z),
P (P B B) (P Z (P B B)), P (P B Z) (P B (P B Z)),
P (P Z B) (P (P B B) B), P (P B (P B B)) (P Z Z),
P (P Z Z) (P B (P B B)), P (P (P B B) B) (P Z B),
P (P B (P B Z)) (P B Z), P (P Z (P B B)) (P B B), P (P (P B B) Z) Z,
P (P (P B Z) B) B, P B (P B (P Z B)), P Z (P (P B Z) B),
P (P B B) (P (P B B) Z), P (P B Z) (P Z (P B B)),
P (P Z B) (P B (P B Z)), P (P B (P B B)) (P (P B B) B),
P (P Z Z) (P Z Z), P (P (P B B) B) (P B (P B B)),
P (P B (P B Z)) (P Z B), P (P Z (P B B)) (P B Z),
P (P (P B B) Z) (P B B), P (P (P B Z) B) Z, P (P B (P Z B)) B,
P B (P Z (P B Z)), P Z (P B (P Z B)), P (P B B) (P (P B Z) B),
P (P B Z) (P (P B B) Z), P (P Z B) (P Z (P B B)),
P (P B (P B B)) (P B (P B Z)), P (P Z Z) (P (P B B) B)]
Now, actually this is still incomplete: it's actually just the list of all finite-depth Blurgs
. As zch remarks, most Blurg
s are uncomputable, there's no chance to actually enumerate all of them.