Re: composeList

2002-05-12 Thread David Feuer

See comments below.

On Sun, May 12, 2002, David Feuer wrote:
> On Sun, May 12, 2002, Emre Tezel wrote:
> > Hi all,
> > 
> > I recently bought Simon Thompson's Haskell book. I have been doing the 
> > exercises while I read on. There are couple questions that I can not 
> > solve. Any help would be greatly appreciated.
> > 
> > I got stuck on this question in Chapter 10.
> > 
> > Define a function composeList which composes a list of functions into a 
> > single function. What is the type of composeList?
> > 
> > I naively tried the following but the hugs compiler complained about the 
> > inferred type not being generic enough.
> > 
> > composeList :: [(a -> b)] -> (c -> b)
> > composeList [] = id
> > composeList (x:xs) = x . (composeList xs)



> You can do a lot better in Glasgow Haskell:
> 
> data Fun a b = forall c . Comp (c -> b) (Fun a c) | End (a -> b)
> 
> compose :: Fun a b -> a -> b   --GHC needs this type signature
>--to compile the program, but
>--I don't understand why.
>--Any tips?
> compose (End f) = f
> compose (Comp f l) = f . compose l

Well, I figured out why the type signature is necessary (polymorphic
recursion), but I don't understand the error message I got from GHC:

cc.hs:5:
Inferred type is less polymorphic than expected
Quantified type variable `c' escapes
When checking a pattern that binds
f :: c -> b
l :: Fun a c
In the definition of `compose':
compose (Comp f l) = f . (compose l)

What makes it think that `c' escapes?  This message had me staring at the code
the wrong way for quite a while before I decided to add a type signature and
see if that gave me any more useful information.

> 
> f::Int -> Float
> f x = fromIntegral x
> 
> g::String -> Int
> g = read
> 
> h::Int -> String
> h x = take x "123456789"
> 
> main = do
>putStrLn "hello!"
>print $ compose (End (\x -> "Foo!")) 3
>print $ compose (Comp f (Comp g (End h))) 4

-- 
Night.  An owl flies o'er rooftops.  The moon sheds its soft light upon
the trees.
David Feuer
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: composeList

2002-05-12 Thread David Feuer

On Sun, May 12, 2002, Emre Tezel wrote:
> Hi all,
> 
> I recently bought Simon Thompson's Haskell book. I have been doing the 
> exercises while I read on. There are couple questions that I can not 
> solve. Any help would be greatly appreciated.
> 
> I got stuck on this question in Chapter 10.
> 
> Define a function composeList which composes a list of functions into a 
> single function. What is the type of composeList?
> 
> I naively tried the following but the hugs compiler complained about the 
> inferred type not being generic enough.
> 
> composeList :: [(a -> b)] -> (c -> b)
> composeList [] = id
> composeList (x:xs) = x . (composeList xs)

The type signature is wrong.  It indicates that for any a,b,c, and d,
composeList takes a list of (a->b) and produces a (c->b).  So for
example, that would mean that if I gave it [(+3), (*4), (-5)] it would
be able to produce something of type (Maybe String -> Int).  This is of
course totally wrong.  You're going to have to restrict it some more .  The first
thing to note is that a=c: if you give it a list of functions that take
Floats, it's going to give back a function that takes a float.  So that
restricts it to [a -> b] -> (a -> b).  Now look at the function itself:

composeList (x:xs) = x . (composeList xs)

Now in order for f . g to make any sense, f must take values of the type
that g returns!  So if x has type p -> q, (composeList xs) must have
type r -> p.  But since x is in xs, xs must have type [p -> q], so
(composeList xs) has type p -> q.  So r -> p = p -> q.  This implies
immediately that p = q = r.  So the type of composeList is restricted
all the way down to [a -> a] -> (a -> a).  This can also be written
[a -> a] -> a -> a.  This may seem disappointing, but it is made
necessary by the type safety of Haskell, which requires that all the
elements of a list have the same type.

You can do a lot better in Glasgow Haskell:

data Fun a b = forall c . Comp (c -> b) (Fun a c) | End (a -> b)

compose :: Fun a b -> a -> b   --GHC needs this type signature
   --to compile the program, but
   --I don't understand why.
   --Any tips?
compose (End f) = f
compose (Comp f l) = f . compose l

f::Int -> Float
f x = fromIntegral x

g::String -> Int
g = read

h::Int -> String
h x = take x "123456789"

main = do
   putStrLn "hello!"
   print $ compose (End (\x -> "Foo!")) 3
   print $ compose (Comp f (Comp g (End h))) 4


-- 
Night.  An owl flies o'er rooftops.  The moon sheds its soft light upon
the trees.
David Feuer
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



composeList

2002-05-12 Thread Emre Tezel

Hi all,

I recently bought Simon Thompson's Haskell book. I have been doing the 
exercises while I read on. There are couple questions that I can not 
solve. Any help would be greatly appreciated.

I got stuck on this question in Chapter 10.

Define a function composeList which composes a list of functions into a 
single function. What is the type of composeList?

I naively tried the following but the hugs compiler complained about the 
inferred type not being generic enough.

composeList :: [(a -> b)] -> (c -> b)
composeList [] = id
composeList (x:xs) = x . (composeList xs)

or

composeList :: [(a -> b)] -> (c -> b)
composeList (x:xs) = x . (composeList xs)

ERROR "Chapter10.hs":6 - Inferred type is not general enough
*** Expression: composeList
*** Expected type : [a -> b] -> c -> b
*** Inferred type : [a -> a] -> b -> a

Anybody can solve this?

Emre

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: waiting for your reply

2002-05-12 Thread Bob Johnson
Title: welcome letter




Welcome to Johnson
Home Products & Services J.H
p&s

Online Shopping Over 1500
Quality
 Products & Many Great Online Features and
Services!

Dear Madam/Sir
@->->-
Let me first say Welcome and to introduce myself to you. My name
Bob Johnson, I operate J.H p&s online store from my home out
Muskegon Michigan.
 J.H p&s online store has been online since Nov 1st of
2001.
 Our warehouse is located in Utah, where most of the online items
are sent from.

 To begin an Relationship with Potential customers, and to earn
your Trust, I am offering you a Complimentary Gift. Sent you at my expense. Just for
registering with J.H p&s online store. There is no fees to register.
There no catch , simple register with my online store and I will send you one free gift out of the choices that are available.

 


Please click on to claim your complimentary gift.
 There are Seven Different Gifts to choose From.
 Plus once you become registered with J.H p&s online
Store.While Supplies last
 You will be enter in the monthly drawing contest every month
automatically.


 My promise and guarantee to you,
I will never give away or sell your
information to any one. Once I receive your information It is
printed out and put in a paper file, and then deleted from my
computer. Your first and last name and email address may be added
to our email list only for sending you special deals and updates
about J.H p&s online store.
 The winners of the Drawing contest, last name and the state they
live in will be display on J.H p&s feature website.
 I am Not one who usually uses the word promise unless I know 100%
I can keep the promise. An from the past few month I sure think
some is selling my information, because I have more email from
people and places I never ever heard of. and been scam of out
money myself.

 My principals and standards are set very high. One of my goals
are to earn an honest living. To be honest and up front with
others as they may cross my path through life.





 

 
 


Please click on to veiw our complete online Product catalog

Every Order You Place You will earn Buying Point, JH P.S Tokens.
 1  JH P.S has a cash value of $0.025
 10 JH P.S tokens has a Cash Value of $0.25
 100 JH P.S tokens has a Cash Value of $2.50
 1000 JH P.S tokens has a Cash Value of $25.00
 
 Every $25.00 You spend,  Earn's  1 Jh P.S Token, Your Token account will earn a Cash Value Balance of $0.025
 You Can use the tokens to purchase items from our online super store.
 Or have the Cash value of tokens earns,Taken off any order.
 All Register Members are Given 100 Token Applied to their Membership Account, After your very first order you place with
 our online store, The Free 100 JH P.S tokens in your account will be available for you to use on any new purchase. 
 

 
Please Click on to Check out our online special Features of
products, Winners of our monthly contest. Featuring
website.

 



 When You Place an Order with J.H p&s online store, I offer
you a free gift with any order you place with J.H p&s online
store.




Please click on to veiw our free offers when You Place an
Order.

 
Please click on to read
 about ordering,Through The mail, Fax orders, Paypal, and From
J.H p&s online Store.
 I accept all major credit cards, checks and money orders.
I offer a Toll Free Telephone number 1-866-236-1208 to place your
order.
 You can also Print out our online order form.
 



The Following is about our Great Online Features I been offering.
I also offer Live help You can Chat with me when I am Online with
any questions, comments, concerns or suggestion you may
have.



Please Click on to read your Daily Horoscope.


Please Click on to Learn how to Play our online
 Games and win weekly Prizes.
 
 
 

Please Click on to read 
more about out J.H p&s and Join our Email list. Also send us
your Feedback
 


Please click on to read 
our Policies on Products & Services



 The following are some of the services I am offering and seeking
new one to add 
 

Please click on to receive your 3 day free trial offer of
advertising.
After the 3 days are over you have the option to buy the service Plus for only $4.95
 per month, your text ad will be sent to 13,000 plus email.



Please Click on to ad your link to our FFa Site.



Please Click on to Purchase This Ebook for only $24.95.
Learn about Selling on ebay and making money online.



Please click on to Read.
 A topic we can all learn and grow From.

 

  
	To Be Removefrom my Email list

 
Under Bill s.1618 TITLE III passed by the 105th US Congress, this letter 
cannot be considered "Spam" as long as the sender includes contact 
information & a method of "removal".Click me on to click you off my email list Please Type "Remove Me " in the subject area of your email.

Wishing you a Great Week!

 





Re: preprocessing printf/regex strings (like ocaml)

2002-05-12 Thread Ralf Hinze


> I'm interested to know why a string translating preprocessor doesn't
> exist for haskell.  It seems to me that it would alleviate printf and
> regex like problems in an convenient, elegant and type-safe manner.
>
> An example of this I came across recently was the ocaml printf
> statement:
>
> # Printf.printf "roar";;
> roar- : unit = ()
>
> # Printf.printf "numbers %d %d" 11 23;;
> numbers 11 23- : unit = ()
>
> # Printf.printf "a number %d" "word";;
> This expression has type string but is here used with type int
>
>
> You can see logically how this might work in haskell, compile time
> evaluation would translate the string into the appropriate native
> expressions before the statements type is evaluated.

Incidentally, I've written a small functional pearl about implementing
printf in Haskell, see
http://www.informatik.uni-bonn.de/~ralf/publications.html#J11

Cheers, Ralf
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe