Beginners Digest, Vol 8, Issue 16

2009-02-19 Thread beginners-request
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. Re:  Sequential IO processing (Andrew Wagner)
   2. Re:  Sequential IO processing (Sergey V. Mikhanov)
   3.  Re: Sequential IO processing (Heinrich Apfelmus)
   4. Re:  Re: Sequential IO processing (Sergey V. Mikhanov)
   5. Re:  Re: Sequential IO processing (Felipe Lessa)
   6.  Counting Fruits (Adolfo Builes)
   7. Re:  Counting Fruits (Alexander Dunlap)


--

Message: 1
Date: Thu, 19 Feb 2009 10:19:35 -0500
From: Andrew Wagner 
Subject: Re: [Haskell-beginners] Sequential IO processing
To: "Sergey V. Mikhanov" 
Cc: beginners@haskell.org
Message-ID:

Content-Type: text/plain; charset="iso-8859-1"

You did really well here. There's just one small detail that you missed,
which is causing the problem:

>
> sequenceIO [] = return []
> sequenceIO (x : xs) = do result <- x
> return result : sequenceIO xs
>

The problem is indeed here. The type of 'sequenceIO xs' is IO [a], but the
type of result is 'a'. You can't cons an 'a' onto an 'IO [a]'. Thus, what
you need is something like this:

sequenceIO [] = return []
sequenceIO (x : xs) = do result <- x xs'
<- sequenceIO xs -- to take the list out of the IO Monad
 return result : xs'
On Thu, Feb 19, 2009 at 9:56 AM, Sergey V. Mikhanov wrote:

>   Hi community,
>
> I am making my first steps in Haskell, reading Haskell wikibook and
> now stuck with one of the excercises, namely this one:
>
> Implement a function sequenceIO :: [IO a] -> IO [a]. Given a list of
> actions, this function runs each of the actions in order and returns
> all their results as a list.
>
> This is what I came with:
>
> ioOne :: Num a => IO a
>
> ioOne = do print guid
>   return guid
>where
>   guid = 2
>
> ioTwo :: Num a => IO a
>
> ioTwo = do print guid
>   return guid
>where
>   guid = 3
>
> sequenceIO :: Num a => [IO a] -> IO [a]
>
> sequenceIO [] = return []
> sequenceIO (x : xs) = do result <- x
> return result : sequenceIO xs
>
> First two functions are there because of the invocation that I've
> planned: sequenceIO [getGuid, getNextGuid].
>
> However, this could not be compiled (GHC):
>
> Couldn't match expected type `[m a]' against inferred type `IO [a]'
> In the second argument of `(:)', namely `sequenceIO xs'
> In the expression: return result : sequenceIO xs
> In the expression:
>do result <- x
>return result : sequenceIO xs
>
> Fine, I thought, something wrong with the type of the 'sequenceIO xs'
> (becasue I am sure the type of 'result' is fine). So I wrote another
> program to check what happens to the result of IO action evaluation
> (namely, which type is assigned):
>
> bar :: Num a => IO a
>
> bar = do print guid
> return guid
>  where
> guid = 2
>
> foo = do result <- bar
> result
>
> This could not be compiled either:
>
> No instance for (Num (IO b))
>arising from a use of `bar' at auxil.hs:8:19-21
> Possible fix: add an instance declaration for (Num (IO b))
> In a stmt of a 'do' expression: result <- bar
> In the expression:
>do result <- bar
>result
> In the definition of `foo':
>foo = do result <- bar
>result
>
> I am a newbie, so I am interpreting this like "Haskell could not
> construct Num from the result of invocation of bar, which is of type
> IO a". But why do I need this at all? When doing console I/O with
> 'result <- getLine', I do not need to reconstruct String from the
> result.
>
> What am I doing wrong? Where is the failure in reasoning?
>
> Thanks,
> Sergey
> ___
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachment

Beginners Digest, Vol 8, Issue 15

2009-02-19 Thread beginners-request
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. Re:  Palindromic solution?? (Dave Bayer)
   2. Re:  Palindromic solution?? (Thomas Davie)
   3. Re:  Indentation of local functions (Miguel Pignatelli)
   4. Re:  Indentation of local functions (ChengWei)
   5.  Re: Indentation of local functions (Christian Maeder)
   6.  Sequential IO processing (Sergey V. Mikhanov)


--

Message: 1
Date: Mon, 16 Feb 2009 13:30:46 -0500
From: Dave Bayer 
Subject: Re: [Haskell-beginners] Palindromic solution??
To: Thomas Davie 
Cc: beginners@haskell.org
Message-ID: <45a0058e-f1c3-4d11-bbac-7a2e3d8dc...@math.columbia.edu>
Content-Type: text/plain; charset=US-ASCII; format=flowed

Here's a solution harder on the machine, easier on the brain:

isPalindrome :: Eq a => [a] -> Bool
isPalindrome xs = and $ zipWith (==) xs $ reverse xs

On Feb 16, 2009, at 1:04 PM, Thomas Davie wrote:

> isPalindrome xs = take l xs == (take l $ reverse xs)
>  where l = length xs `div` 2



--

Message: 2
Date: Mon, 16 Feb 2009 19:38:50 +0100
From: Thomas Davie 
Subject: Re: [Haskell-beginners] Palindromic solution??
To: Dave Bayer 
Cc: beginners@haskell.org
Message-ID: 
Content-Type: text/plain; charset=US-ASCII; format=flowed


On 16 Feb 2009, at 19:30, Dave Bayer wrote:

> Here's a solution harder on the machine, easier on the brain:
>
> isPalindrome :: Eq a => [a] -> Bool
> isPalindrome xs = and $ zipWith (==) xs $ reverse xs

Lets just tidy that up a little...
isPalindrome = (and . zipWith (==)) <*> reverse

But I don't see how either is easier on the brain than xs == reverse xs.

Bob


--

Message: 3
Date: Tue, 17 Feb 2009 00:24:23 +0100
From: Miguel Pignatelli 
Subject: Re: [Haskell-beginners] Indentation of local functions
To: Daniel Fischer 
Cc: beginners@haskell.org
Message-ID: <991970a6-4bfd-43cb-ab03-6060f2e59...@uv.es>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed; delsp=yes

Nice!
Thanks a lot for the explanation. (and to the others that have replied!)

M;


El 16/02/2009, a las 17:05, Daniel Fischer escribió:

> Am Montag, 16. Februar 2009 16:32 schrieb Miguel Pignatelli:
>> Hi all,
>>
>> This is my first post in this forum, I'm pretty new to Haskell
>> (although I have some previous experience in functional programming
>> with OCaml).
>>
>> I'm trying to write the typical function that determines if a list is
>> a palindrome.
>> The typical answer would be something like:
>>
>> isPalindrome xs = xs == (reverse xs)
>>
>> But I find this pretty inefficient (duplication of the list and  
>> double
>> of needed comparisons).
>> So I tried my own version using just indexes:
>>
>> isPalindrome xs =
>>  isPalindrome' 0 (length xs)
>>  where isPalindrome' i j =
>> if i == j   -- line 43
>> then True
>> else
>>  if (xs !! i) == (xs !! (j-1))
>>  then isPalindrome' (i+1) (j-1)
>>  else False
>>
>> But, when trying to load this in ghci it throws the following error:
>>
>> xxx.hs:43:12: parse error (possibly incorrect indentation)
>> Failed, modules loaded: none.
>> (Line 43 is marked in the code)
>>
>> I seems that the definition of isPalindrome' must be in one line. So,
>> this works as expected:
>>
>> isPalindrome xs =
>>  isPalindrome' 0 (length xs)
>>where isPalindrome' i j = if i == j then True else if (xs !! i)
>> == (xs !! (j-1)) then isPalindrome' (i+1) (j-1) else False
>>
>> Is there any way to make the local definition of isPalindrome' more
>> readable?
>>
>
> Yes, it would be horrible to look at Haskell code if there weren't.
> The problem is that originally, the code for isPalindrome' was  
> indented less
> than the function name. Specifically, the first relevant token (i.e.  
> not
> whitespace or comments) after the keywords do, let, where, case ... of
> opens up a new scope, which lasts until something is indented less  
> or equally
> far.
> To not suffer from e-mailing programmes behaviour regarding leading  
> spaces on
> a line, I replace those with '°', then a more readable formatting of  
> your
> code would be
>
> isPalindrome xs = isPalindrome' 0 (length xs)
> °°°where
> °°isPalindrome' i j
> °| j <= i = True
> °| xs !! i /= xs !! (j-1) = False
> °| otherwise = isPalindrome (i+1) (j-1)
>
> I have replaced your nested ifs by guards (increases readability,  
> IMO) and
> corrected the stopping condition so that