Send Beginners mailing list submissions to
[email protected]
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: Traverse tree with computing current level using
Foldable instance. (Dmitriy Matrosov)
2. Re: Traverse tree with computing current level using
Foldable instance. (Chadda? Fouch?)
3. Most C++ compilers will not optimize x^2.0 as x*x but
instead will do an expensive ... (KC)
4. Re: Most C++ compilers will not optimize x^2.0 as x*x but
instead will do an expensive ... (Brandon Allbery)
5. Re: Most C++ compilers will not optimize x^2.0 as x*x but
instead will do an expensive ... (Bardur Arantsson)
6. Re: [Haskell-cafe] Most C++ compilers will not optimize
x^2.0 as x*x but instead will do an expensive ... (Brandon Allbery)
7. Re: [Haskell-cafe] Most C++ compilers will not optimize
x^2.0 as x*x but instead will do an expensive ... (Bardur Arantsson)
----------------------------------------------------------------------
Message: 1
Date: Wed, 23 May 2012 14:51:02 +0400
From: Dmitriy Matrosov <[email protected]>
Subject: Re: [Haskell-beginners] Traverse tree with computing current
level using Foldable instance.
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed
On 05/22/12 06:18, Brent Yorgey wrote:
>>
>> As you can see, this just selects all elements at particular tree level.
>>
>> So, my foldMapS2 looks similar to foldMap from Foldable, but i can't
>> figure out, how should i define instances of Foldable (and Monoid?)
>> to achieve the same functionality?
>
> You cannot. Foldable is not general enough; it does not allow you to
> define folds which can observe the *structure* of the container being
> folded over (such as the level in a tree, the number of children of a
> given node, etc.). It corresponds to simply "flattening" the
> structure into a list of elements, turning each of them into a value
> of some monoid, and then applying mconcat.
>
> However, you should be able to define a general fold for Tape, with
> type
>
> foldTape :: (a -> [b] -> b) -> Tape a -> b
>
> and then define foldMapS2 in terms of foldTape.
>
> -Brent
Hi, Brent, and thanks for the answer! I've tried to define foldTape and then
foldMapS2 using it, i've tried.. ugh, i think everything, with fold and with
map, but i still can't.
Well, this is the whole story. I repeat part of the previous message,
since i
refer to it later. Here is my tree definition, test tree and test function:
import Data.Monoid
import Control.Monad.State
type TpName = String
type TpLevel = Int
type TpState a = State TpLevel a
data Tape a = Tape a [Tape a]
-- Oldest first. I.e. tape "B" is older, than tape "D", etc.
testTape :: Tape TpName
testTape = Tape "A" [ Tape "B" [ Tape "C" []
, Tape "F" [Tape "G" [
Tape
"H" []]]
, Tape "E" []
]
, Tape "D" [ Tape "I" []]
]
testFoldMapS :: ((a -> TpState [a]) -> TpState (Tape a) -> TpState
[a]) ->
Int -> Tape a -> ([a], Int)
testFoldMapS foldMapS i t =
runState (foldMapS (\x -> get >>= \cs ->
if cs == i then return [x]
else return mempty)
(return t))
0
Test function invokes specified foldMapS with function, which adds
(mappends)
to list only elements at particular tree level.
Here is my previous foldMapS function for Tape tree, which counts tree level
using State monad:
foldMapS2 :: (Monoid m) =>
(a -> TpState m) -> TpState (Tape a) ->
TpState m
foldMapS2 f tt = do
t@(Tape name ts) <- tt
foldr (go f) (f name) ts
where
go :: (Monoid m) =>
(a -> TpState m) -> Tape a -> TpState m ->
TpState m
go f t mz = do
cs <- get
x <- foldMapS2 f (State (\s -> (t, s + 1)))
put cs
z <- mz
put cs
return (x `mappend` z)
First, i've tried to define foldTape like
foldTape :: (a -> [b] -> b) -> Tape a -> b
foldTape f (Tape name ts)
= f name $ map (foldTape f) ts
and then i've rewritten foldMapS2 using map and sequence instead of foldr:
foldMapSm3 :: (Monoid m) =>
(a -> TpState m) -> TpState (Tape a) ->
TpState m
foldMapSm3 f mt =
mt >>= \(Tape name ts) ->
get >>= \cs ->
sequenceS cs (f name)
$ map (\t -> foldMapSm3 f (State (\s -> (t, s + 1)))) ts
where
sequenceS :: (Monoid m) =>
s -> State s m -> [State s m] -> State s m
sequenceS cs z [] = z >>= \x ->
put cs >> return x
sequenceS cs z (mx : mxs)
= mx >>= \x ->
put cs >> sequenceS cs z mxs >>= \y ->
put cs >> return (x `mappend` y)
i need to redefine sequence, because library's sequence does not reset state
(with (put cs)), when bind-ing list elements.
and then i've tried to define foldMapSm3 using foldTape:
foldMapSt :: (Monoid m) =>
(a -> TpState m) -> TpState (Tape a) ->
TpState m
foldMapSt f mt =
mt >>= \t ->
get >>= \cs ->
foldTape (sequenceS cs) t
where
--sequenceS :: (Monoid m) => Int -> a -> [TpState m] ->
-- TpState m
sequenceS cs name [] = f name
sequenceS cs name (mx : mxs)
= mx >>= \x ->
put cs >> sequenceS cs name mxs >>= \y ->
put cs >> return (x `mappend` y)
but, as you may notice, it will not work. Result will be
> testFoldMapS foldMapSt 0 testTape
(["C","H","G","F","E","B","I","D","A"],0)
because in foldMapSt state change part, when recursively processing list of
Tape elements (childrens), is missed. I.e. in foldMapSm3 map will call
foldMapSm3 f (State (\s -> (t, s + 1)))
for each list element, but foldTape from foldMapSt will simple call itself
foldTape f
and then (sequenceS cs), which rely on someone setting cs
(current state) correctly.
Then i return again to foldMapS2 and try to split it into two functions,
like
so
foldTapeF :: (Monad m, Monoid b) => (a -> m b) ->
((a -> m b) -> Tape a -> m b -> m b) ->
m (Tape a) -> m b
foldTapeF f go mt = mt >>= \(Tape name ts) -> foldr (go f) (f
name) ts
foldTapeGo :: (Monoid m) =>
(a -> TpState m) -> Tape a -> TpState m ->
TpState m
foldTapeGo f t mz = do
cs <- get
x <- foldTapeF f foldTapeGo (State (\s -> (t, s + 1)))
put cs
z <- mz
put cs
return (x `mappend` z)
but.. umm, i don't think this code is better, than foldMapS2. There have
been
other attempts, but all of them are walking in a circle, and all of them
have
failed.
So, am i missing something? Or may be i should change tree definition?
Can you
give me more hints, please? :)
And, after all, what is idiomatic haskell way of folding tree, with
function, which should have access to tree level (depth)?
--
Dmitriy Matrosov
------------------------------
Message: 2
Date: Wed, 23 May 2012 18:48:27 +0200
From: Chadda? Fouch? <[email protected]>
Subject: Re: [Haskell-beginners] Traverse tree with computing current
level using Foldable instance.
To: Dmitriy Matrosov <[email protected]>
Cc: [email protected]
Message-ID:
<CANfjZRatM8PaXAxZZ0=qopp-5_m8tfunaxwny-verzauotz...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8
On Wed, May 23, 2012 at 12:51 PM, Dmitriy Matrosov <[email protected]> wrote:
> On 05/22/12 06:18, Brent Yorgey wrote:
>> However, you should be able to define a general fold for Tape, with
>> type
>>
>> ? foldTape :: (a -> ?[b] -> ?b) -> ?Tape a -> ?b
>>
So, you wrote it correctly :
> foldTape :: (a -> [b] -> b) -> Tape a -> b
> foldTape f (Tape x ts) = f x (map (foldTape f) ts)
This appears desperate since there's no mention of Int anywhere in
this function and the function applied stay the same whatever the
level : the initially given f parameter.
But there's a trick to this, we'll have to treat some of our type
variable like functions, here only b can vary freely (a is imposed by
the Tape a inputted), so let's see what it looks like if we make it a
functional type (with Int parameter):
> foldTape :: (a -> [Int -> b] -> (Int -> b)) -> Tape a -> (Int -> b)
much more promising wouldn't you say ? The solution now looks like that :
> foldTapeD :: (Monoid m) => (Int -> a -> m) -> Tape a -> m
> foldTapeD f t = (foldTape go t) 0
> where
> go x fs n = ....
I let you write your solution (if you didn't find before tomorrow
evening, I'll give you the answer).
You can then call foldTapeD thus :
> foldTapeD (\n x -> if n < 2 then [x] else []) testTape
(much nicer than your initial solution, is it not ?)
--
Jeda?
------------------------------
Message: 3
Date: Wed, 23 May 2012 18:47:31 -0700
From: KC <[email protected]>
Subject: [Haskell-beginners] Most C++ compilers will not optimize
x^2.0 as x*x but instead will do an expensive ...
To: haskell-cafe <[email protected]>, [email protected]
Message-ID:
<CAMLKXyka5m2im=_ar6erl+pbftybjjnlpfkzawb-uf6vnda...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"
exponentiation and logarithm.
So, I believe this C++ versus Haskell versus (your language of choice) is a
Penn & Teller misdirection.
Whereas, another level of indirection solves everything.
--
--
Regards,
KC
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
<http://www.haskell.org/pipermail/beginners/attachments/20120523/7f166315/attachment-0001.htm>
------------------------------
Message: 4
Date: Wed, 23 May 2012 22:13:33 -0400
From: Brandon Allbery <[email protected]>
Subject: Re: [Haskell-beginners] Most C++ compilers will not optimize
x^2.0 as x*x but instead will do an expensive ...
To: haskell-cafe <[email protected]>, [email protected]
Message-ID:
<cakfcl4u0ytkadtzdaawhywnbwy5qxama599tqhfoqrzjdpa...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"
On Wed, May 23, 2012 at 9:47 PM, KC <[email protected]> wrote:
> exponentiation and logarithm.
> So, I believe this C++ versus Haskell versus (your language of choice) is
> a Penn & Teller misdirection.
> Whereas, another level of indirection solves everything.
>
Is it me or is this style of message ? content broken between subject and
body, no reference information tying it to the presumed topic (or possibly
a /non sequitur/) ? better suited to Twitter than a mailing list?
--
brandon s allbery [email protected]
wandering unix systems administrator (available) (412) 475-9364 vm/sms
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
<http://www.haskell.org/pipermail/beginners/attachments/20120523/01212434/attachment-0001.htm>
------------------------------
Message: 5
Date: Thu, 24 May 2012 04:19:35 +0200
From: Bardur Arantsson <[email protected]>
Subject: Re: [Haskell-beginners] Most C++ compilers will not optimize
x^2.0 as x*x but instead will do an expensive ...
To: [email protected]
Cc: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=windows-1252
On 05/24/2012 04:13 AM, Brandon Allbery wrote:
> On Wed, May 23, 2012 at 9:47 PM, KC <[email protected]> wrote:
>
>> exponentiation and logarithm.
>> So, I believe this C++ versus Haskell versus (your language of choice) is
>> a Penn & Teller misdirection.
>> Whereas, another level of indirection solves everything.
>>
>
> Is it me or is this style of message ? content broken between subject and
> body, no reference information tying it to the presumed topic (or possibly
> a /non sequitur/) ? better suited to Twitter than a mailing list?
>
>
This has come up before -- this KC person probably has a broken mail
client which doesn't set appropriate References headers.
@KC: Which mail client are you using?
... and could you please 1) (ideally) use a mail client which doesn't
screw up threading, or 2) (less ideally) avoid messing with the subject
line so that at least everybody else's mail client has that to go on for
threading purposes?
Regards,
------------------------------
Message: 6
Date: Wed, 23 May 2012 22:31:32 -0400
From: Brandon Allbery <[email protected]>
Subject: Re: [Haskell-beginners] [Haskell-cafe] Most C++ compilers
will not optimize x^2.0 as x*x but instead will do an expensive ...
To: Bardur Arantsson <[email protected]>
Cc: [email protected], [email protected]
Message-ID:
<CAKFCL4VDa+ffc7EL3KXTtuRbzJn8iC-Zt5=7oso5p1voa2+...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"
On Wed, May 23, 2012 at 10:19 PM, Bardur Arantsson <[email protected]>wrote:
> This has come up before -- this KC person probably has a broken mail
> client which doesn't set appropriate References headers.
>
That, however, ignores the rest of it; the lack of references in this case
forms a pattern with the other things I noted, in that a conversation is
apparently being held in the form of single observations emitted at the
point of observation instead of being collected and presented *as* a
conversation.
--
brandon s allbery [email protected]
wandering unix systems administrator (available) (412) 475-9364 vm/sms
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
<http://www.haskell.org/pipermail/beginners/attachments/20120523/5356cf52/attachment-0001.htm>
------------------------------
Message: 7
Date: Thu, 24 May 2012 04:39:34 +0200
From: Bardur Arantsson <[email protected]>
Subject: Re: [Haskell-beginners] [Haskell-cafe] Most C++ compilers
will not optimize x^2.0 as x*x but instead will do an expensive ...
To: [email protected]
Cc: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1
On 05/24/2012 04:31 AM, Brandon Allbery wrote:
> On Wed, May 23, 2012 at 10:19 PM, Bardur Arantsson
> <[email protected]>wrote:
>
>> This has come up before -- this KC person probably has a broken mail
>> client which doesn't set appropriate References headers.
>>
>
> That, however, ignores the rest of it; the lack of references in this case
> forms a pattern with the other things I noted, in that a conversation is
> apparently being held in the form of single observations emitted at the
> point of observation instead of being collected and presented *as* a
> conversation.
>
Right. I was actually just about to respond to (only) KC in person, but
perhaps unwisely, decided to "hijack" your response to add a little
explanation for everyone.
You are of course right that not quoting context and just randomly
spewing out small bits of text is not really suitable for a mailing list.
------------------------------
_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners
End of Beginners Digest, Vol 47, Issue 17
*****************************************