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.  Printf and bool (Aditya Mahajan)
   2. Re:  Printf and bool (Brent Yorgey)
   3.  Re: Printf and bool (Aditya Mahajan)
   4.  System.IO.withFile (Rafael Gustavo da Cunha Pereira Pinto)
   5. Re:  System.IO.withFile (Antoine Latter)
   6. Re:  System.IO.withFile (Rafael Gustavo da Cunha Pereira Pinto)
   7.  Type Operator (Kellen J. McClain)
   8. Re:  Type Operator (Daniel Fischer)
   9.  This is problem 2, chapter 4 RWH (Michael Litchard)
  10. Re:  This is problem 2, chapter 4 RWH (Daniel Fischer)


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

Message: 1
Date: Mon, 19 Jan 2009 10:04:21 -0500
From: Aditya Mahajan <adi.maha...@gmail.com>
Subject: [Haskell-beginners] Printf and bool
To: beginners@haskell.org
Message-ID: <alpine.lnx.2.00.0901190955430.4...@ybpnyubfg.ybpnyqbznva>
Content-Type: TEXT/PLAIN; format=flowed; charset=US-ASCII

Hi,

I like the printf function from Text.Printf to display results on the 
terminal. I noticed that there is no format specifier for Bool. Can 
someone suggest how to create an instance of PrintfArg for Bool?

Aditya



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

Message: 2
Date: Mon, 19 Jan 2009 13:22:00 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Printf and bool
To: beginners@haskell.org
Message-ID: <20090119182200.ga15...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Mon, Jan 19, 2009 at 10:04:21AM -0500, Aditya Mahajan wrote:
> Hi,
>
> I like the printf function from Text.Printf to display results on the 
> terminal. I noticed that there is no format specifier for Bool. Can someone 
> suggest how to create an instance of PrintfArg for Bool?

Why not just use something like

  printf "%s" (show b)

where b :: Bool ?

-Brent


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

Message: 3
Date: Mon, 19 Jan 2009 14:42:15 -0500
From: Aditya Mahajan <adi.maha...@gmail.com>
Subject: [Haskell-beginners] Re: Printf and bool
To: beginners@haskell.org
Message-ID: <alpine.lnx.2.00.0901191441220.4...@ybpnyubfg.ybpnyqbznva>
Content-Type: TEXT/PLAIN; charset=US-ASCII; format=flowed

On Mon, 19 Jan 2009, Brent Yorgey wrote:

> On Mon, Jan 19, 2009 at 10:04:21AM -0500, Aditya Mahajan wrote:
>> Hi,
>>
>> I like the printf function from Text.Printf to display results on the
>> terminal. I noticed that there is no format specifier for Bool. Can someone
>> suggest how to create an instance of PrintfArg for Bool?
>
> Why not just use something like
>
>  printf "%s" (show b)
>
> where b :: Bool ?

Because it breaks type safety.

Aditya



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

Message: 4
Date: Mon, 19 Jan 2009 23:30:30 -0200
From: "Rafael Gustavo da Cunha Pereira Pinto"
        <rafaelgcpp.li...@gmail.com>
Subject: [Haskell-beginners] System.IO.withFile
To: beginners@haskell.org
Message-ID:
        <351ff25e0901191730h2078eb6emc7787160c8dda...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi folks,



I am trying to use the withFile function of System.IO, but it always return
an empty string when testing.

Could someone explain why:

main= do
              h<-openFile "test.cir" ReadMode
              c<-hGetContents h
              print c

> runhaskell test1.hs
> "* Teste\n\nR1  1 0 10\nC1  1 0 10uF\nI1  1 0 1mA\n\n.DC \n.PRINT\n"

works and


main= (withFile "test.cir" ReadMode hGetContents) >>= print

> runhaskell test1.hs
> ""

don't?


Thanks!
-- 
Rafael Gustavo da Cunha Pereira Pinto
Electronic Engineer, MSc.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090119/86c36b61/attachment-0001.htm

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

Message: 5
Date: Mon, 19 Jan 2009 21:44:56 -0600
From: "Antoine Latter" <aslat...@gmail.com>
Subject: Re: [Haskell-beginners] System.IO.withFile
To: "Rafael Gustavo da Cunha Pereira Pinto"
        <rafaelgcpp.li...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <694519c50901191944g11d677d6w5b96d8b2213c8...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Mon, Jan 19, 2009 at 7:30 PM, Rafael Gustavo da Cunha Pereira Pinto
<rafaelgcpp.li...@gmail.com> wrote:
> Could someone explain why:
>
> main= do
>               h<-openFile "test.cir" ReadMode
>               c<-hGetContents h
>               print c
>
>> runhaskell test1.hs
>> "* Teste\n\nR1  1 0 10\nC1  1 0 10uF\nI1  1 0 1mA\n\n.DC \n.PRINT\n"
>
> works and
>
>
> main= (withFile "test.cir" ReadMode hGetContents) >>= print
>
>> runhaskell test1.hs
>> ""
>
> don't?

'hGetContents' is a lazy-IO function, which means doesn't really start
reading from the handle until another function tries to consume its
output.

The problem is that 'print' - the consumer - is outside of the
'withFile' argument, and 'withFile' guarantees that the file is closed
when it finishes execution.

So by the time 'hGetContents' tries to do its thing, the file handle is closed.

This snippet:

> main = withFile "test.cir" ReadMode $ \h -> hGetContents h >>= print

puts the call to 'print' inside the argument to 'withFile', so it
should work as expected.

-Antoine


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

Message: 6
Date: Tue, 20 Jan 2009 10:20:41 -0200
From: "Rafael Gustavo da Cunha Pereira Pinto"
        <rafaelgcpp.li...@gmail.com>
Subject: Re: [Haskell-beginners] System.IO.withFile
To: "Antoine Latter" <aslat...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <351ff25e0901200420r2c3eeb60nbdf32e4086c53...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Thanks Antoine!

I was suspecting it should be the lazyness of hGetContents yesterday, before
going to sleep.

You just confirmed that for me!

On Tue, Jan 20, 2009 at 01:44, Antoine Latter <aslat...@gmail.com> wrote:

> On Mon, Jan 19, 2009 at 7:30 PM, Rafael Gustavo da Cunha Pereira Pinto
> <rafaelgcpp.li...@gmail.com> wrote:
> > Could someone explain why:
> >
> > main= do
> >               h<-openFile "test.cir" ReadMode
> >               c<-hGetContents h
> >               print c
> >
> >> runhaskell test1.hs
> >> "* Teste\n\nR1  1 0 10\nC1  1 0 10uF\nI1  1 0 1mA\n\n.DC \n.PRINT\n"
> >
> > works and
> >
> >
> > main= (withFile "test.cir" ReadMode hGetContents) >>= print
> >
> >> runhaskell test1.hs
> >> ""
> >
> > don't?
>
> 'hGetContents' is a lazy-IO function, which means doesn't really start
> reading from the handle until another function tries to consume its
> output.
>
> The problem is that 'print' - the consumer - is outside of the
> 'withFile' argument, and 'withFile' guarantees that the file is closed
> when it finishes execution.
>
> So by the time 'hGetContents' tries to do its thing, the file handle is
> closed.
>
> This snippet:
>
> > main = withFile "test.cir" ReadMode $ \h -> hGetContents h >>= print
>
> puts the call to 'print' inside the argument to 'withFile', so it
> should work as expected.
>
> -Antoine
>



-- 
Rafael Gustavo da Cunha Pereira Pinto
Electronic Engineer, MSc.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090120/67de0e2e/attachment-0001.htm

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

Message: 7
Date: Wed, 21 Jan 2009 17:30:12 -0500
From: "Kellen J. McClain" <kjmccl...@comcast.net>
Subject: [Haskell-beginners] Type Operator
To: beginners@haskell.org
Message-ID: <1232577012.4387.12.ca...@kgateway>
Content-Type: text/plain

I have a quick question.

Recall that:
class Monad m where
        (>>=) :: m a -> (a -> m b) -> m b
        ...

and suppose I have a data type Sample:

data Sample a b = ...

how could I define Sample to be an instance of Monad such that:

(>>=) :: Sample a c -> (a -> Sample b c) -> Sample b c

?

I would like to use a (\a -> ...)-like operator, but for types. 
So, something like this:

instance Monad (\a -> Sample a c) where
        (>>=) :: Sample a c -> (a -> Sample b c) -> Sample b c
        a >>= f = ...

but that obviously doesn't work. Alternatively I would 
like to use a type declaration and partially apply it:

type SampleFlip b a = Sample a b
instance Monad (SampleFlip c) where
        (>>=) :: SampleFlip c a -> (a -> SampleFlip c b) -> SampleFlip c b

which translates to:

        (>>=) :: Sample a c -> (a -> Sample b c) -> Sample b c

But this doesn't work either, and ghc extensions don't add this functionality.  
Can I do this in Haskell?



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

Message: 8
Date: Wed, 21 Jan 2009 23:51:26 +0100
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Type Operator
To: "Kellen J. McClain" <kjmccl...@comcast.net>,        beginners@haskell.org
Message-ID: <200901212351.26389.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-15"

Am Mittwoch, 21. Januar 2009 23:30 schrieb Kellen J. McClain:
> I have a quick question.
>
> Recall that:
> class Monad m where
>       (>>=) :: m a -> (a -> m b) -> m b
>       ...
>
> and suppose I have a data type Sample:
>
> data Sample a b = ...
>
> how could I define Sample to be an instance of Monad such that:
>
> (>>=) :: Sample a c -> (a -> Sample b c) -> Sample b c
>
> ?
>
> I would like to use a (\a -> ...)-like operator, but for types.
> So, something like this:
>
> instance Monad (\a -> Sample a c) where
>       (>>=) :: Sample a c -> (a -> Sample b c) -> Sample b c
>       a >>= f = ...
>
> but that obviously doesn't work. Alternatively I would
> like to use a type declaration and partially apply it:
>
> type SampleFlip b a = Sample a b
> instance Monad (SampleFlip c) where
>       (>>=) :: SampleFlip c a -> (a -> SampleFlip c b) -> SampleFlip c b
>
> which translates to:
>
>       (>>=) :: Sample a c -> (a -> Sample b c) -> Sample b c
>
> But this doesn't work either, and ghc extensions don't add this
> functionality. Can I do this in Haskell?
>
I think you can't.
If it's possible, the best option would be to change the order of type 
parameters of Sample. If that's not possible, you can define

newtype FSample b a = FS (Sample a b)

and make that an instance of Monad.

Somebody remind me, why does Haskell not have type-lambdas?


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

Message: 9
Date: Wed, 21 Jan 2009 17:33:40 -0800
From: Michael Litchard <mich...@schmong.org>
Subject: [Haskell-beginners] This is problem 2, chapter 4 RWH
To: beginners@haskell.org
Message-ID:
        <3dc350d00901211733v6f7e8842l4ca9581aefc75...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

splitWith' :: (a -> Bool) -> [a] -> [[a]]
splitWith' p x = case takeUntil p x of
        [] -> []
        x' -> subset : splitWith' p x''
              where (subset, x'') = break p x'
   where takeUntil :: (a -> Bool) -> [a] -> [a]
         takeUntil p' = takeWhile q
              where q x = not (p' x)

It doesn't give me the right behavior though.
It should work like this:
splitWith' odd [2,2,1,4,4,3,6,6,5]
[[2,2],[4,4],[6,6]]
but it works like this instead
[[2,2]]

I'm pretty sure I modeled splitWith' on words, which is what the
exercise indirectly suggests.
Can someone help me step through this code to figure out what's wrong.
It looks right to me.


Michael Litchard


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

Message: 10
Date: Thu, 22 Jan 2009 03:02:42 +0100
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] This is problem 2, chapter 4 RWH
To: Michael Litchard <mich...@schmong.org>, beginners@haskell.org
Message-ID: <200901220302.42525.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Donnerstag, 22. Januar 2009 02:33 schrieb Michael Litchard:
> splitWith' :: (a -> Bool) -> [a] -> [[a]]
> splitWith' p x = case takeUntil p x of
>         [] -> []
>         x' -> subset : splitWith' p x''
>               where (subset, x'') = break p x'
>    where takeUntil :: (a -> Bool) -> [a] -> [a]
>          takeUntil p' = takeWhile q
>               where q x = not (p' x)
>
> It doesn't give me the right behavior though.
> It should work like this:
> splitWith' odd [2,2,1,4,4,3,6,6,5]
> [[2,2],[4,4],[6,6]]
> but it works like this instead
> [[2,2]]
>
> I'm pretty sure I modeled splitWith' on words, which is what the
> exercise indirectly suggests.
> Can someone help me step through this code to figure out what's wrong.
> It looks right to me.

takeUntil odd [2,2,1,4,4,3,6,6,5]
gives [2,2], so the second branch is taken, next break odd [2,2] is 
calculated. Since this list doesn't contain any odd numbers,
break odd [2,2] == ([2,2],[]), so subset = [2,2], x'' = [] and
subset : splitWith' p x'' reduces to [2,2] : splitWith odd [], which of course 
is [2,2] : [] = [[2,2]].
Your code never touches anything behind the first odd number. To rectify that, 
instead of takeUntil, you need a function which returns two parts, the 
initial segment of the list until the first odd number and the part following 
the first odd number (if there is any). Then your result would be 
(first part) : splitWith' p (second part). You already use the relevant 
function, albeit in the wrong place.

>
>
> Michael Litchard

HTH,
Daniel


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

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


End of Beginners Digest, Vol 7, Issue 14
****************************************

Reply via email to