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
        [EMAIL PROTECTED]

You can reach the person managing the list at
        [EMAIL PROTECTED]

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


Today's Topics:

   1. Re:  Re: pattern for tree traversel with a state
      (Andreas-Christoph Bernstein)
   2. Re:  Re: pattern for tree traversel with a state (Jan Jakubuv)
   3.  Re: Type problems with IOArray (apfelmus)
   4. Re:  Re: pattern for tree traversel with a state (Brent Yorgey)
   5.  Function composition with more than 1 parameter (Glurk)
   6. Re:  Function composition with more than 1        parameter (Jason Dusek)
   7.  Re: Function composition with more than 1        parameter (apfelmus)
   8.  Re: Function composition with more than  1       parameter (Glurk)
   9. Re:  Re: Function composition with more than 1    parameter
      (Daniel Fischer)


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

Message: 1
Date: Thu, 23 Oct 2008 19:38:10 +0200
From: Andreas-Christoph Bernstein
        <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Re: pattern for tree traversel with a
        state
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

apfelmus wrote:
> Andreas-Christoph Bernstein wrote:
>  
>> Is there a pattern for tree traversal with a state ?
>>
>> I am developing a small scenegraph represented by a tree. To draw a
>> scenegraph one traverses over the graph starting with a global state.
>> Inner Nodes can overwrite the inherited state for their subtree (e.g.
>> Transformations are accumulated). The accumulated state is then either
>> used immediately to draw the geometry in the leaf nodes, or a secondary
>> data structure is build. This secondary data structure (a list or a
>> tree) can then be sorted for optimal drawing performance.
>>
>> So i want to do the second and create a list of all leaves with the
>> accumulated global state. To illustrate my problem i appended some code.
>> The idea similar applies to a scenegraph.
>>
>> So my Question is: Is there already a pattern for traversal with a 
>> state ?
>>     
>
> Yes. I'm not sure whether state is really necessary for your problem,
> i.e. whether there is a more elegant formulation, but your algorithm
> fits a well-known pattern, namely the one in  Data.Traversable
>
>   import Data.Traversable
>   import Data.Foldable
>
>   import qualified Control.Monad.State
>
>
>   data BTree a = Fork a (BTree a) (BTree a) | Leaf a deriving Show
>
>      -- main functionality
>   instance Traversable BTree where
>      traverse f (Leaf x)     = Leaf <$> f x
>      traverse f (Fork x l r) = Fork <$>
>                                f x <*> traverse f l <*> traverse f r
>
>      -- derived examples
>   instance Foldable BTree where
>      foldMap = foldMapDefault
>   instance Functor  BTree where
>      fmap    = fmapDefault
>
>   flattenTree = toList
>
>      -- state example
>   data StateMod = ModInt | ModString | ModNop deriving Show
>   type State    = (Int, String)
>
>   modState :: StateMod -> State -> State
>   modState ModInt    (x,w) = (x+1,w)
>   modState ModNop    s     = s
>   modState ModString (x,w) = (x,'b':w)
>
>   startState = (0,"a")
>
>   newTree :: BTree StateMod -> BTree State
>   newTree = flip evalState startState
>           . Data.Traversable.mapM (modify' . modState)
>      where
>      modify' f = Control.Monad.State.modify f >> Control.Monad.State.get
>
>
>   
Hi,

Thanks for the quick reply. But it is not quite what i expect. If i 
apply your
solution to an exampletree i get the following result:

tree :: BTree StateMod
tree = Fork ModNop
             (Fork ModInt (Leaf ModInt) (Leaf ModNop))
              (Leaf ModNop)

flattenTree (newTree tree )

which produces:
[(0,"a"),(1,"a"),(2,"a"),(2,"a"),(2,"a")]

But what i need is
[(0,"a"),(1,"a"),(2,"a"),(1,"a"),(0,"a")]

So state changes should affect only their subtree, not the rest of the 
tree to the right.

Kind regards,
Andreas


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

Message: 2
Date: Thu, 23 Oct 2008 23:47:43 +0100
From: "Jan Jakubuv" <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Re: pattern for tree traversel with a
        state
To: beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=ISO-8859-1

2008/10/23 Andreas-Christoph Bernstein <[EMAIL PROTECTED]>:
> apfelmus wrote:
>>
>
> But what i need is
> [(0,"a"),(1,"a"),(2,"a"),(1,"a"),(0,"a")]
>
> So state changes should affect only their subtree, not the rest of the tree
> to the right.
>

It seems to me that you are looking for the Reader monad. Try the following:

import Control.Monad.Reader

t :: (a -> b -> b) -> BTree a -> Reader b (BTree b)
t f (Leaf x) = do
   s <- ask
   return (Leaf (f x s))
t f (Fork x l r) = do
   s <- ask
   l' <- local (f x) (t f l)
   r' <- local (f x) (t f r)
   return (Fork (f x s) l' r')

new = runReader (t modState sampleTree) globalState

Then,

flattenTree new

gives you

[(0,"a"),(1,"a"),(2,"a"),(1,"a"),(0,"a")]

I think that the Reader monad is a standard way to this. When you want
the state to affect also the rest of the tree then use the State
monad.

Sincerely,
 jan.


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

Message: 3
Date: Fri, 24 Oct 2008 18:25:23 +0200
From: apfelmus <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] Re: Type problems with IOArray
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=ISO-8859-1

Xuan Luo wrote:
> I am having lots of trouble using polymorphic mutable IOArrays. Here
> is an example program:
> 
> import Data.Array.MArray
> import Data.Array.IO
> 
> foo x = do a <- newArray (0, 4) x
>            readArray a 2
> 
> main = foo 42 >>= print
> 
> So there is a function "foo" which makes an array of polymorphic type
> initialized with a value, then returns one of the elements of the
> array.

Note that there are no arrays with "polymorphic element type", it's
rather that your  foo  can be used to create an array with elements the
same type as  x . So, if  x  is an integer,  foo  creates an array with
integer elements etc.

> What the heck is this? I looked through a lot of stuff online and
> eventually found that this works:
> 
> {-# LANGUAGE ScopedTypeVariables #-}
> import Data.Array.MArray
> import Data.Array.IO
> 
> foo :: forall a. a -> IO a
> foo x = do a <- newArray (0, 4) x :: IO (IOArray Int a)
>            readArray a 2
> 
> main = foo 42 >>= print
> 
> So I had to add some weird "forall" stuff to my function signature and
> enable some language extension flag(?). This seems way too
> complicated.

The  forall  is not weird :). In fact, the type signature

  foo :: a -> IO a

should be seen as an abbreviation for

  foo :: forall a. a -> IO a

See also

  http://en.wikibooks.org/wiki/Haskell/Polymorphism


Here, the  forall a  introduces  a  as type variable so that  IOArray
Int a  refers to the same type  a . You need an extension for that
because for some odd reason, Haskell98 offers no way to do that; it will
likely be included in the next version of the Haskell language.


Regards,
apfelmus



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

Message: 4
Date: Fri, 24 Oct 2008 14:18:40 -0400
From: Brent Yorgey <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Re: pattern for tree traversel with a
        state
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=us-ascii

On Thu, Oct 23, 2008 at 11:47:43PM +0100, Jan Jakubuv wrote:
> 2008/10/23 Andreas-Christoph Bernstein <[EMAIL PROTECTED]>:
> > apfelmus wrote:
> >>
> >
> > But what i need is
> > [(0,"a"),(1,"a"),(2,"a"),(1,"a"),(0,"a")]
> >
> > So state changes should affect only their subtree, not the rest of the tree
> > to the right.
> >
> 
> It seems to me that you are looking for the Reader monad. Try the following:
> 
> import Control.Monad.Reader
> 
> t :: (a -> b -> b) -> BTree a -> Reader b (BTree b)
> t f (Leaf x) = do
>    s <- ask
>    return (Leaf (f x s))
> t f (Fork x l r) = do
>    s <- ask
>    l' <- local (f x) (t f l)
>    r' <- local (f x) (t f r)
>    return (Fork (f x s) l' r')
> 
> new = runReader (t modState sampleTree) globalState
> 
> Then,
> 
> flattenTree new
> 
> gives you
> 
> [(0,"a"),(1,"a"),(2,"a"),(1,"a"),(0,"a")]
> 
> I think that the Reader monad is a standard way to this. When you want
> the state to affect also the rest of the tree then use the State
> monad.

Just to elaborate on Jan's code, the Reader monad represents an
*immutable* state---that is, a read-only "environment" that gets
threaded through your computation which you can access at any time
(using "ask").  However, using the "local" function, you can run
subcomputations within a different environment, obtained by applying
some function to the current environment.  So this does exactly what
you want---after the subcomputation is finished, its locally defined
environment goes out of scope and you are back to the original
environment.  Using the Reader monad in this way is a common idiom for
representing recursive algorithms with state that can change on the
way down the call stack, but "unwinds" as you come back up, so
recursive calls can only affect recursive calls below them, not ones
that come afterwards.

-Brent


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

Message: 5
Date: Sat, 25 Oct 2008 07:00:08 +0000 (UTC)
From: Glurk <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] Function composition with more than 1
        parameter
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=us-ascii

Hi,

Is it possible to use function composition with a function that takes more 
than 1 parameter ?

For example, I have a function that finds all the matches of an element within 
a list :-

matches x xs = [ m | m <- xs, x == m ]

So, matches 'e' "qwertyee" will return "eee"

I now want a function that will work out how many times the element occurs in 
the list, easily written as :-

howMany x xs = length $ matches x xs

So, howMany 5 [1,2,3,4,5,5,5,5,5,6,6,6,7]
will return 5

However, I'm thinking I want to try to use function composition to write 
something like :-

howMany = length . matches

...which would be nice and clean :)
I thought this would work, as the output of matches is a list, and the input 
required by length is a list.

This doesn't work though, failng with the error :-

Type error in application
*** Expression     : length . matches
*** Term           : length
*** Type           : [b] -> Int
*** Does not match : ([a] -> [a]) -> Int

Which I can't quite make out what it means.
Ok, it's telling me lengt has a type [b] -> Int which makes sense,
but it says it expected a different type, ([a] -> [a]) -> Int
What I can't understand is why it wants something of that type ?

Is it possibly something to do with the higher precedence of function 
application over function composition ?
I've tried various things, like putting brackets around (length . matches)
and changing my function to take in a tuple of (element, list), instead of 2 
parameters (which I thought I had working at some stage ! but which now I 
can't get to work)

Any advice appreciated !

thanks :)




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

Message: 6
Date: Sat, 25 Oct 2008 00:48:38 -0700
From: "Jason Dusek" <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Function composition with more than 1
        parameter
To: Glurk <[EMAIL PROTECTED]>
Cc: beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=UTF-8

  You can easily have

    howMany x = length . matches x

  I poked around in 'Control.Applicative' (briefly) and didn't
  find anything that really stood out as answer.

--
_jsn


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

Message: 7
Date: Sat, 25 Oct 2008 11:10:03 +0200
From: apfelmus <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] Re: Function composition with more than 1
        parameter
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=ISO-8859-1

Glurk wrote:
> Is it possible to use function composition with a function that takes more 
> than 1 parameter ?
> 
> For example, I have a function that finds all the matches of an element 
> within 
> a list :-
> 
> matches x xs = [ m | m <- xs, x == m ]
> 
> So, matches 'e' "qwertyee" will return "eee"
> 
> I now want a function that will work out how many times the element occurs in 
> the list, easily written as :-
> 
> howMany x xs = length $ matches x xs

The lambdabot on #haskell has a plugin named "pointless" that can
transform this into a definition that doesn't mention  x  and  xs
anymore. I think it will propose

  howMany = (length .) . matches

And with

  matches x xs = filter (x==) xs

  matches x    = filter (x==)

  matches      = filter . (==)

we have

  howMany = (length .) . filter . (==)

> I've tried various things, like putting brackets around (length . matches)
> and changing my function to take in a tuple of (element, list), instead of 2 
> parameters (which I thought I had working at some stage ! but which now I 
> can't get to work)

  howMany = curry (length . uncurry matches)


Regards,
apfelmus



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

Message: 8
Date: Sat, 25 Oct 2008 10:34:23 +0000 (UTC)
From: Glurk <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] Re: Function composition with more than    1
        parameter
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=us-ascii

> The lambdabot on #haskell has a plugin named "pointless" that can
> transform this into a definition that doesn't mention  x  and  xs
> anymore. I think it will propose
> 
>   howMany = (length .) . matches
> 
> And with
> 
>   matches x xs = filter (x==) xs
> 
>   matches x    = filter (x==)
> 
>   matches      = filter . (==)
> 
> we have
> 
>   howMany = (length .) . filter . (==)

> 
>   howMany = curry (length . uncurry matches)


Thanks apfelmus,

unfortunately, none of those suggested changes seem to work !
I get errors like :-

Unresolved top-level overloading
*** Binding             : howMany2
*** Outstanding context : Eq b

I'm using WinHugs - do you get them to work in some other environment ?

Thanks ! :)



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

Message: 9
Date: Sat, 25 Oct 2008 12:48:53 +0200
From: Daniel Fischer <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Re: Function composition with more
        than 1  parameter
To: Glurk <[EMAIL PROTECTED]>, beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain;  charset="iso-8859-1"

Am Samstag, 25. Oktober 2008 12:34 schrieb Glurk:
> > The lambdabot on #haskell has a plugin named "pointless" that can
> > transform this into a definition that doesn't mention  x  and  xs
> > anymore. I think it will propose
> >
> >   howMany = (length .) . matches
> >
> > And with
> >
> >   matches x xs = filter (x==) xs
> >
> >   matches x    = filter (x==)
> >
> >   matches      = filter . (==)
> >
> > we have
> >
> >   howMany = (length .) . filter . (==)
> >
> >
> >   howMany = curry (length . uncurry matches)
>
> Thanks apfelmus,
>
> unfortunately, none of those suggested changes seem to work !
> I get errors like :-
>
> Unresolved top-level overloading
> *** Binding             : howMany2
> *** Outstanding context : Eq b
>
> I'm using WinHugs - do you get them to work in some other environment ?

Did you give a type signature for these?
Then you would of course have to include the context Eq b, since (==) is used.
If you don't give any type signatures, all above versions should work in all 
environments, otherwise it would be a serious bug.
>
> Thanks ! :)
>



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

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


End of Beginners Digest, Vol 4, Issue 13
****************************************

Reply via email to