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. (Brent Yorgey)
3. Help!, was Re: Trouble with "import qualified" (Dudley Brooks)
4. Re: Help!, was Re: Trouble with "import qualified"
(Michael Orlitzky)
5. Re: Help!, was Re: Trouble with "import qualified" (Keshav Kini)
6. Re: Help!, was Re: Trouble with "import qualified" (Tim Perry)
7. Re: Help!, was Re: Trouble with "import qualified"
(Michael Orlitzky)
8. Re: Help!, was Re: Trouble with "import qualified" (Brent Yorgey)
----------------------------------------------------------------------
Message: 1
Date: Thu, 24 May 2012 15:09:24 +0400
From: Dmitriy Matrosov <[email protected]>
Subject: Re: [Haskell-beginners] Traverse tree with computing current
level using Foldable instance.
To: Chadda? Fouch? <[email protected]>
Cc: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=UTF-8; format=flowed
On 05/23/12 20:48, Chadda? Fouch? wrote:
> 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 ?)
Hi, Chadda?. Thanks for the clarification!
Now i think i get it. Here is three my solutions. First one is (as you
suggest)
without monads:
> import Data.Monoid
> import Control.Monad.State
>
> data Tape a = Tape a [Tape a]
>
> foldTape :: (a -> [b] -> b) -> Tape a -> b
> foldTape f (Tape name ts)
> = f name (map (foldTape f) ts)
>
> foldTapeD :: (Monoid m) => (Int -> a -> m) -> Tape a -> m
> foldTapeD f t = (foldTape (go f) t) 0
> where
> go :: (Monoid m) => (Int -> a -> m) -> a -> [(Int -> m)] -> (Int
-> m)
> go f name xs = \cs ->
> foldr (mappend . ($ (cs + 1))) (f cs name) xs
second one with monadic go function:
> foldTapeD1 :: (Monoid m) => (Int -> a -> m) -> Tape a -> m
> foldTapeD1 f t = fst $ runState (foldTape (go f) t) 0
> where
> go :: (Monoid m) => (Int -> a -> m) -> a -> [State Int m] ->
State Int m
> go f name xs = do
> cs <- get
> put (cs + 1)
> foldr (go' (cs + 1)) (return (f cs name)) xs
> go' :: (Monoid m) => Int -> State Int m -> State Int m -> State Int m
> go' cs mx mz = do
> x <- mx
> put cs
> z <- mz
> put cs
> return (x `mappend` z)
and the last one with monadic go function and monadic user-defined folding
function:
> foldTapeD2 :: (Monoid m) => (a -> State Int m) -> Tape a -> m
> foldTapeD2 f t = fst $ runState (foldTape (go f) t) 0
> where
> go :: (Monoid m) =>
> (a -> State Int m) -> a -> [State Int m] -> State Int m
> go f name xs = do
> cs <- get
> z <- f name
> put (cs + 1)
> foldr (go' (cs + 1)) (return z) xs
> go' :: (Monoid m) => Int -> State Int m -> State Int m -> State Int m
> go' cs mx mz = do
> x <- mx
> put cs
> z <- mz
> put cs
> return (x `mappend` z)
and here is test functions:
> testTape :: Tape String
> testTape = Tape "A" [ Tape "B" [ Tape "C" []
> , Tape "F" [Tape "G"
> [Tape
"H" []]]
> , Tape "E" []
> ]
> , Tape "D" [ Tape "I" []]
> ]
> testFoldTapeD :: ((Int -> a -> [a]) -> Tape a -> [a]) ->
> Int -> Tape a -> [a]
> testFoldTapeD ftD i t = ftD (\cs x -> if cs == i then [x] else []) t
> testFoldTapeD1 :: ((a -> State Int [a]) -> Tape a -> [a]) ->
> Int -> Tape a -> [a]
> testFoldTapeD1 ftD i t
> = ftD (\x -> get >>= \cs -> if cs == i then return [x] else
return []) t
Is my answer correct? :)
And at the end it seems, that first (non-monadic) version is much
simpler and
clearer, than all other. So.. should i use monads here?
Earlier i think, that it's better to use them, but now i doubt.
--
Dmitriy Matrosov
------------------------------
Message: 2
Date: Thu, 24 May 2012 08:54:23 -0400
From: Brent Yorgey <[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=us-ascii
On Thu, May 24, 2012 at 03:09:24PM +0400, Dmitriy Matrosov wrote:
>
> and the last one with monadic go function and monadic user-defined folding
> function:
>
> > foldTapeD2 :: (Monoid m) => (a -> State Int m) -> Tape a -> m
> > foldTapeD2 f t = fst $ runState (foldTape (go f) t) 0
> > where
> > go :: (Monoid m) =>
> > (a -> State Int m) -> a -> [State Int m] -> State Int m
> > go f name xs = do
> > cs <- get
> > z <- f name
> > put (cs + 1)
> > foldr (go' (cs + 1)) (return z) xs
> > go' :: (Monoid m) => Int -> State Int m -> State Int m -> State Int m
> > go' cs mx mz = do
> > x <- mx
> > put cs
> > z <- mz
> > put cs
> > return (x `mappend` z)
By the way, for this sort of pattern where you change the state for
some subcomputation and then restore it after the subcomputation
returns, it can be much nicer to use the Reader monad with the 'local'
function instead of the State monad. That might actually go a long
way towards making the monadic version nicer to read. =)
-Brent
------------------------------
Message: 3
Date: Thu, 24 May 2012 09:34:22 -0700
From: Dudley Brooks <[email protected]>
Subject: [Haskell-beginners] Help!, was Re: Trouble with "import
qualified"
Cc: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed
Hi. I've had this up for over a week, and haven't received any
response. Any help would be greatly appreciated.
On 5/16/12 10:04 PM, Dudley Brooks wrote:
> Almost complete beginner.
>
> I just downloaded Haskell 32-bit for Mac from Haskell.org and am going
> through Learn You a Haskell. I tried to follow the instructions on
>
> http://learnyouahaskell.com/modules#loading-modules
>
> in particular
>
> import qualified Data.Map as Map
>
> which, following the instructions, I put in a .hs file which I attempted
> to load into GHCi with :l. I got
>
> parse error on input `import'
>
> I have no idea what the problem might be or what to do about it. Other
> imports have been successful, but after getting the above message I
> tried to "import qualified" other modules, always with the same error.
------------------------------
Message: 4
Date: Thu, 24 May 2012 12:49:59 -0400
From: Michael Orlitzky <[email protected]>
Subject: Re: [Haskell-beginners] Help!, was Re: Trouble with "import
qualified"
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1
On 05/24/12 12:34, Dudley Brooks wrote:
> Hi. I've had this up for over a week, and haven't received any
> response. Any help would be greatly appreciated.
>
> On 5/16/12 10:04 PM, Dudley Brooks wrote:
>
>> Almost complete beginner.
>>
>> I just downloaded Haskell 32-bit for Mac from Haskell.org and am going
>> through Learn You a Haskell. I tried to follow the instructions on
>>
>> http://learnyouahaskell.com/modules#loading-modules
>>
>> in particular
>>
>> import qualified Data.Map as Map
>>
>> which, following the instructions, I put in a .hs file which I attempted
>> to load into GHCi with :l. I got
>>
>> parse error on input `import'
>>
>> I have no idea what the problem might be or what to do about it. Other
>> imports have been successful, but after getting the above message I
>> tried to "import qualified" other modules, always with the same error.
>
Try starting from a fresh file? I just tried the simplest thing I could
think of to reproduce this, but it worked:
jumba ~ $ echo "import qualified Data.Map as Map" >> test.hs
jumba ~ $ echo "main = print \"Hello, World\"" >> test.hs
jumba ~ $ runhaskell test.hs
"Hello, World"
jumba ~ $ ghci
GHCi, version 7.4.1: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Prelude> :l test.hs
[1 of 1] Compiling Main ( test.hs, interpreted )
Ok, modules loaded: Main.
*Main> main
Loading package array-0.4.0.0 ... linking ... done.
Loading package deepseq-1.3.0.0 ... linking ... done.
Loading package containers-0.4.2.1 ... linking ... done.
"Hello, World"
*Main>
------------------------------
Message: 5
Date: Thu, 24 May 2012 09:58:53 -0700
From: Keshav Kini <[email protected]>
Subject: Re: [Haskell-beginners] Help!, was Re: Trouble with "import
qualified"
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii
Michael Orlitzky <[email protected]> writes:
> jumba ~ $ ghci
> GHCi, version 7.4.1: http://www.haskell.org/ghc/ :? for help
I doubt this really matters when it comes to import statements, but note
that the Haskell platform's latest release is using GHC/GHCi version
7.0.4.
(hi mjo :) )
-Keshav
------------------------------
Message: 6
Date: Thu, 24 May 2012 10:23:45 -0700
From: Tim Perry <[email protected]>
Subject: Re: [Haskell-beginners] Help!, was Re: Trouble with "import
qualified"
To: [email protected]
Message-ID:
<CAFVgASW4e-7960bmeBs=ddu1OoVKsyU_XW=sx04oljjxjar...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"
It sounds mostly likely that there were spaces or tabs in the wrong place.
Good luck....
On Thu, May 24, 2012 at 9:58 AM, Keshav Kini <[email protected]> wrote:
> Michael Orlitzky <[email protected]> writes:
> > jumba ~ $ ghci
> > GHCi, version 7.4.1: http://www.haskell.org/ghc/ :? for help
>
> I doubt this really matters when it comes to import statements, but note
> that the Haskell platform's latest release is using GHC/GHCi version
> 7.0.4.
>
> (hi mjo :) )
>
> -Keshav
>
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
<http://www.haskell.org/pipermail/beginners/attachments/20120524/be280b58/attachment-0001.htm>
------------------------------
Message: 7
Date: Thu, 24 May 2012 13:35:49 -0400
From: Michael Orlitzky <[email protected]>
Subject: Re: [Haskell-beginners] Help!, was Re: Trouble with "import
qualified"
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1
On 05/24/12 12:58, Keshav Kini wrote:
> Michael Orlitzky <[email protected]> writes:
>> jumba ~ $ ghci
>> GHCi, version 7.4.1: http://www.haskell.org/ghc/ :? for help
>
> I doubt this really matters when it comes to import statements, but note
> that the Haskell platform's latest release is using GHC/GHCi version
> 7.0.4.
>
> (hi mjo :) )
>
> -Keshav
For a second I was sure I sent this to the wrong list =)
If the OP doesn't see any misplaced whitespace at the beginning of the
file, I'd also check that there's isn't any unicode junk there.
------------------------------
Message: 8
Date: Thu, 24 May 2012 13:43:11 -0400
From: Brent Yorgey <[email protected]>
Subject: Re: [Haskell-beginners] Help!, was Re: Trouble with "import
qualified"
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii
On Thu, May 24, 2012 at 09:34:22AM -0700, Dudley Brooks wrote:
> Hi. I've had this up for over a week, and haven't received any
> response. Any help would be greatly appreciated.
When you say "had this up", what do you mean? I don't see any other
messages from you to the haskell-beginners list.
>
> >
> >in particular
> >
> > import qualified Data.Map as Map
> >
> >which, following the instructions, I put in a .hs file which I attempted
> >to load into GHCi with :l. I got
> >
> > parse error on input `import'
It's impossible to tell what's wrong only from this description. If
you upload an *exact* copy of your file somewhere (e.g. hpaste.org)
I'm sure someone could take a look. Some general things to watch out
for:
* the real error could be in the previous line to the one being
reported
* all the imports have to come at the very beginning of a module
* don't put any spaces or tabs before "import"
-Brent
------------------------------
_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners
End of Beginners Digest, Vol 47, Issue 19
*****************************************