Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Scoping within arrow notation (using HXT)? (Michael Alan Dorman)
   2. Re:  Scoping within arrow notation (using HXT)?
      (Ertugrul S?ylemez)


----------------------------------------------------------------------

Message: 1
Date: Fri, 08 Jun 2012 11:48:23 -0400
From: Michael Alan Dorman <mdor...@ironicdesign.com>
Subject: [Haskell-beginners] Scoping within arrow notation (using
        HXT)?
To: beginners@haskell.org
Message-ID: <87vcj1vm7s....@ironicdesign.com>
Content-Type: text/plain

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)))




------------------------------

Message: 2
Date: Fri, 8 Jun 2012 18:20:13 +0200
From: Ertugrul S?ylemez <e...@ertes.de>
Subject: Re: [Haskell-beginners] Scoping within arrow notation (using
        HXT)?
To: beginners@haskell.org
Message-ID: <20120608182013.5ffd1...@angst.streitmacht.eu>
Content-Type: text/plain; charset="us-ascii"

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 <mdor...@ironicdesign.com> wrote:

> 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/
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120608/f596dfd6/attachment-0001.pgp>

------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 48, Issue 16
*****************************************

Reply via email to