Beginners Digest, Vol 6, Issue 5

2008-12-15 Thread beginners-request
rg
Message-ID:
<29bf512f0812151248p163b3101pb9fe83c63685f...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Mon, Dec 15, 2008 at 12:17 PM, Jeff C. Britton  wrote:

> Hello,
>
> I have started reading "Yet Another Haskell Tutorial" by Hal Daum´e III
> which can be found here
> http://www.cs.utah.edu/~hal/docs/daume02yaht.pdf<http://www.cs.utah.edu/%7Ehal/docs/daume02yaht.pdf>
>
> One of the early examples in section 3.8 pg. 35
> is this
>
> askForWords = do
>  putStrLn "Please enter a word:"
>  word <- getLine
>  if word == ""
>then return []
>else do
>  rest <- askForWords
>  return (word : rest)
>
> I want to print the returned list and everything I try fails.
>
> I have tried the following:
>
> printList l =
>  if length l >= 1
>then do putStrLn (head l)
>printList (tail l)
>else putStrLn("")
>
> f = printList askForWords
>
> and I get
> Expression : printList askForWords
> *** Term   : askForWords
> *** Type   : IO [[Char]]
> *** Does not match : [[Char]]


I believe one of the following will work for you:

f = askForWords >>= printList
f = do
words <- askForWords
printList words


>
>
>
> *
> The exercise right below this asks for a very slight modification to read
> numbers instead.
>
> However, I am confused about how to convert strings to numbers.
> If I type in the hugs interactive console
> read "5" + 3 --> 8 -- ok perfect
>
> However
> read "5" gives
> ERROR - Unresolved overloading
> *** Type   : Read a => a
> *** Expression : read "5"
>
> Yet page 33 of the tutorial has the following code:
> doGuessing num = do
>  putStrLn "Enter your guess:"
>  guess <- getLine
>  let guessNum = read guess  -- ok in let stmt, but not at repl prompt?


The problem here is type inference. The statement read "5" has type "(Read
a) => a", which basically means anything that implements the class "Read."
When you do read "5" + 3, the read "5" gets the type of the 3. I assume that
in the latter case, you use the expression guessNum in a way later on that
the compiler can infer its type.

>
>
>
> Anyway I take the info that has been presented and create this function:
> askForNumbers = do
>hSetBuffering stdin LineBuffering
>putStrLn "Give me a number (or 0 to stop)"
>numStr <- getLine
>let num = read numStr
>if num == 0
>then return []
>else do
>rest <- askForNumbers
>return (num : rest)
>
> However, when I try to use it, like say
>
> map sqrt askForNumbers
>
> ERROR - Type error in application
> *** Expression : map sqrt askForNumbers
> *** Term   : askForNumbers
> *** Type   : IO [Integer]
> *** Does not match : [a]


Similar to above, try this:
do nums <- askForNumbers
map sqrt nums


>
>
> *
>
> Is there a way to write printList to handle Strings or numbers?
> Or should I write
> printList (map show askForNumbers)


Note: you should probably do this using mapM_, but for simplicity, I'll do
it using explicit recursion:

printList [] = putStrLn "" -- or return () if you don't want the extra blank
line
printList (x:xs) = do putStrLn (show x)
  printList xs

If you have any questions about how these worked, let me know!

Michael
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20081215/03bfa53c/attachment-0001.htm

--

Message: 4
Date: Tue, 16 Dec 2008 08:36:09 +1030
From: "Levi Stephen" 
Subject: Re: [Haskell-beginners] A type level programming question
To: "Justin Bailey" 
Cc: beginners@haskell.org
Message-ID:
<8341e4f40812151406p101192aal97c6a9becf4f3...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Tue, Dec 16, 2008 at 6:33 AM, Justin Bailey  wrote:
> On Sun, Dec 14, 2008 at 3:11 PM, Levi Stephen  wrote:
>> (!) :: (Pos s, Nat i, i :<: s) => FSVec s a -> i -> a
>>
>> I was wondering if it was possible to write a function of type:
>>
>> elementAt :: FSVec s a -> Int -> a
>>
>> that called the above function, throwing an error if the index was out
>> of bounds. e.g.,
>>
>
> Why would you want to write that function? From the signature on (!),
> it looks like any out of bounds errors should occur at compil

Beginners Digest, Vol 6, Issue 4

2008-12-15 Thread beginners-request
m for the presumably scary term monads/monadic)
operations.

it allows you to write in "classical" imperative/sequential style instead of
chaining operations manually (using the >> and >>= operators, which the do
notation translates into anyway). lookup some monad tutorials/docs.

you are right in that if there is only one operation, no transformation is
needed, so the do is unnecessary.
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20081215/cb2fd47b/attachment-0001.htm

--

Message: 6
Date: Mon, 15 Dec 2008 09:49:38 -0800
From: "Michael Snoyman" 
Subject: [Haskell-beginners] Existential data types
To: beginners@haskell.org
Message-ID:
<29bf512f0812150949w237cec4arb7e7dc92b8896...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi everyone,

I believe I have come to the conclusion that what I would like to do is
impossible, but I would like to have that confirmed. I would basically like
to be able to have a heterogeneous list without boxing everything in a data
type. Below is the sample code, with the code I would like to use commented
out. I'm I missing something, or does Haskell simply not support what I am
trying for?

{-# LANGUAGE ExistentialQuantification #-}

data Foo = Foo String
class IFoo a where
toFoo :: a -> Foo
instance IFoo Foo where
toFoo = id

data A = A String
instance IFoo A where
toFoo (A a) = Foo a

data B = B Int
instance IFoo B where
toFoo (B b) = Foo $ show b

data FooBox = forall t. IFoo t => FooBox t
instance IFoo FooBox where
toFoo (FooBox f) = toFoo f

myPrint :: IFoo t => [(String, t)] -> IO ()
myPrint = mapM_ myPrint'

myPrint' :: IFoo t => (String, t) -> IO ()
myPrint' (key, value) =
let (Foo foo) = toFoo value
 in putStrLn $ key ++ ": " ++ foo

{- What I'd like to do:
main = myPrint
[ ("one", Foo "1")
, ("two", A "2")
]
-}

main = myPrint
[ ("one", FooBox $ Foo "1")
, ("two", FooBox $ A "2")
]



Thanks
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20081215/05e6c5ee/attachment-0001.htm

--

Message: 7
Date: Mon, 15 Dec 2008 20:02:31 +0100
From: "Norbert Wojtowicz" 
Subject: [Haskell-beginners] gtk2hs timeoutSeq
To: beginners@haskell.org
Message-ID:

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

Hello,

I'm trying to use a sequence of timeoutAdd's in a gtk2hs app. By
sequence, I mean one (IO Bool) must return as False before the next
begins:

timeoutSeq [ (fn1, 100), (fn2, 200) ]

fn1 will keep running every 100, until it returns False. Then fn2 will
get a timeoutAdd 200, and so on...

First attempt (works fine, I think):

timeoutSeq :: [(IO Bool, Int)] -> IO ()
timeoutSeq [] = return ()
timeoutSeq ((fn,n):rest) = do
  timeoutAdd (aux fn rest) n
  return ()
where
  aux :: IO Bool -> [(IO Bool, Int)] -> IO Bool
  aux fn [] = fn
  aux fn lst = do
r <- fn
case r of
  True  -> return True
  False -> do
 timeoutSeq lst
 return False

Now, I'd like to write a timeoutDep (fn1, n1) (fn2, n2)  where fn1 and
fn2 are both running at their respective rates, and fn1 will run only
as long as fn2 is running. The use case for this is eg: Run fn1 often
and fn2 less often, but I only care fn1 to be running as long as fn2
is still valid.

timeoutDep (fn,n) (fn2,n2) = do
  hdl <- timeoutAdd fn n
  timeoutSeq [(aux fn2 hdl, n2), (return False, 100)]
where
  aux fn2 hdl = do
r <- fn2
case r of
  True  -> return True
  False -> do
 timeoutRemove hdl
 return False

This implementation sort of works, except it exits immiediately (and
as IO ()), so I can't for example do this:

  timeoutSeq [((timeoutDep (print "a" >> return True, 100)
  (print "b" >> return
True, 100)), 100)
 , (print "c" >> return False, 100)]

Ths silly example should keep printing 'a' and 'b' w/o ever printing
'c'.  Any ideas or suggestions?


--

Message: 8
Date: Mon, 15 Dec 2008 14:55:35 -0500
From: "Brandon S. Allbery KF8NH" 
Subject: Re: [Haskell-beginners] Existential data types
To: "Michael Snoyman" 
Cc: beginners@haskell.org
Message-ID: <82658da2-d2b7-4a26-9f97-933e2c4c6...@ece.cmu.edu>
Content-Type: text/plain; charset="us-ascii"

On 2008 Dec 15, at 12:49, Michael Snoyman wrote:
> I believ