Scoping within arrow notation (using HXT)?

Hey, Haskellers, I'm trying to use state threaded through an arrow in some HXT code to avoid passing explicit parameters through several layers of functions, but I think I'm not understanding quite what the arrow notation is doing, because when I try to use a value I'm extracting from the state, I'm getting a scope error. I had many ways I was prepared for the code to be wrong, but that one has me baffled. Any suggestions? Mike. {-# LANGUAGE Arrows, NoMonomorphismRestriction #-} module HXTTest () where import Text.XML.HXT.Core data Info = Info { value :: String } deriving (Show) info = Info { value = "foo" } html = "<html><head></head><body><div class='foo'>llama</div></body>"; -- print (runSLA (getState >>> arr value) info html) -- Div class is static, no reference to state findFoo = proc content -> do (deep (isElem >>> hasName "div" >>> hasAttrValue "class" (== "foo"))) -< content -- print (runSLA (hread >>> findFoo) info html) -- Extract class from state, but don't use it findFoo' = proc content -> do divName <- (getState >>> arr value) -< content content >- (deep (isElem >>> hasName "div" >>> hasAttrValue "class" (== "foo"))) -- print (runSLA (hread >>> findFoo') info html) -- Extract class from state, try to use it: "Not in scope: `divName'" -- findFoo'' = -- proc content -> do -- divName <- (getState >>> arr value) -< content -- content >- (deep (isElem >>> -- hasName "div" >>> -- hasAttrValue "class" (== divName)))

Hello there,
the structure of an arrow computation cannot depend on inputs. All
arrow variables (to the left of '<-' or '->') are inputs to following
computations. For instance:
proc x1 -> do
x2 <- c1 -< x1
x3 <- c2 -< x2
returnA -< f x2 x3
The variables x1, x2 and x3 are arrow variables and are out of scope
to the left of '-<', because if they were in scope, the structure of the
computation could depend on arrow variables, and you would in fact have
a monad instead of an arrow.
Note also that 'proc x -> c -< x' is the same as 'c', and 'do' notation
is an extension to 'proc' notation.
You may be interested in my (unfinished) arrow tutorial:
http://ertes.de/new/tutorials/arrows.html
Greets,
Ertugrul
Michael Alan Dorman
I'm trying to use state threaded through an arrow in some HXT code to avoid passing explicit parameters through several layers of functions, but I think I'm not understanding quite what the arrow notation is doing, because when I try to use a value I'm extracting from the state, I'm getting a scope error.
-- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/
participants (2)
-
Ertugrul Söylemez
-
Michael Alan Dorman