defining functions in ghci

This messes me up: $ ghci GHCi, version 6.8.2: http://www.haskell.org/ghc/ :? for help double x =Loading package base ... linking ... done. Prelude> double x = x + x <interactive>:1:9: parse error on input `=' Why does that happen? -- Joe Van Dyk http://fixieconsulting.com

You can do several at a time like this: Prelude> let { x = 21 ; y = 7 } Unfortunately, the offside rule is hard to use from the prompt. -- Jason Dusek

On Mon, Jan 25, 2010 at 5:38 PM, Joe Van Dyk
This messes me up:
$ ghci GHCi, version 6.8.2: http://www.haskell.org/ghc/ :? for help double x =Loading package base ... linking ... done. Prelude> double x = x + x <interactive>:1:9: parse error on input `='
Why does that happen?
As others pointed out, you have to use "let" here; I don't know how much you've experimented with monads yet (e.g., IO), but the reason is that you're actually working in a monad in GHCi.

Hello, I have: data Nat = Z | S Nat deriving (Eq,Ord,Show) and should write a function that works for Nats like foldr for list where: instance Enum Nat where toEnum i | i < 0 = error "foo" | i == 0 = Z | otherwise = S (toEnum (i-1)) Can someone give me a hint how to do this? -- Nur noch bis 31.01.2010: DSL-Komplettpaket für 16,99 Euro/mtl.!* http://portal.gmx.net/de/go/dsl02

Hi One hint is that your data type for natural numbers is remarkably like the data type for lists... data List a = [] | a : List a The difference is that List has an element of type 'a' at the non-zero cases. Best wishes Stephen

yeahh, I know that it is similar, but don't know how to start implementing it. -------- Original-Nachricht --------
Datum: Tue, 26 Jan 2010 11:05:20 +0000 Von: Stephen Tetley
An: CC: Beginners@haskell.org Betreff: Re: [Haskell-beginners] foldr for Nats
Hi
One hint is that your data type for natural numbers is remarkably like the data type for lists...
data List a = [] | a : List a
The difference is that List has an element of type 'a' at the non-zero cases.
Best wishes
Stephen _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Jetzt kostenlos herunterladen: Internet Explorer 8 und Mozilla Firefox 3.5 - sicherer, schneller und einfacher! http://portal.gmx.net/de/go/atbrowser

Hello I'm suspecting this isn't homework as you've waited a week so would presumably have missed a deadline. As Daniel Fischer wrote, one view of folds is that they replace the constructors of a data type, code follows... data Nat = Z | S Nat deriving (Eq,Ord,Show) -- Look at the type of foldr... -- *GHCi> :t foldr -- foldr :: (a -> b -> b) -> b -> [a] -> b -- It has 2 'constructor replacements': -- (a -> b -> b) & b -- Replacing Z is easy, we can get some code to compile -- by avoiding the hard bit with a wildcard pattern "_"... foldrNat1 :: unknown -> b -> Nat -> b foldrNat1 _ b Z = b -- What to do about the constructor (S ..) takes a bit more -- thought or at least some experimenting. I'll do the later... -- One thing to try, is to simply translate foldr with as few -- changes as possible: -- foldr :: (a -> b -> b) -> b -> [a] -> b -- foldr _ z [] = z -- foldr f z (x:xs) = f x (foldr f z xs) -- Unfortunately this leads to a problem: foldrNat2 :: (Nat -> b -> b) -> b -> Nat -> b foldrNat2 f b Z = b -- Z case is the same as before foldrNat2 f b (S n) = f undefined (foldrNat2 f b n) -- Arggh! undefined -- undefined is useful for prototyping, but its a real -- problem for running code! -- Actually I had another problem as well... -- -- The difference between Nat and [a] is that List 'carries' some data -- therefore (Nat -> b -> b) on Nat is not equivalent to (a -> b -> b) -- on [a]. -- So rather than change the type signature first, get rid of the -- undefined and see what happens foldrNat3 f b Z = b foldrNat3 f b (S n) = f (foldrNat3 f b n) -- *GHCi> :t foldrNat3 -- > (t -> t) -> t -> Nat -> t -- GHCi likes to call type variables t, but the signature is equal to -- foldrNat3 :: (b -> b) -> b -> Nat -> b -- This looks promising - it typechecks! -- So try a test: fromNat :: Nat -> Int fromNat n = foldrNat3 (+1) 0 n demo1 = fromNat (S (S (S Z))) -- 3 ?? -- By experimenting we seem to have a good answer, -- other people might prefer a more rigorous proof though.

@Stephan thanks for the code so far. @Daniel it should look like foldrNat a b S(S(S(S(Z)))) gives a(a(a(a(b)))) The thing is the definition have to be -------- Original-Nachricht --------
Datum: Mon, 1 Feb 2010 21:56:14 +0000 Von: Stephen Tetley
An: kane96@gmx.de CC: Beginners@haskell.org Betreff: Re: [Haskell-beginners] foldr for Nats
Hello
I'm suspecting this isn't homework as you've waited a week so would presumably have missed a deadline.
As Daniel Fischer wrote, one view of folds is that they replace the constructors of a data type, code follows...
data Nat = Z | S Nat deriving (Eq,Ord,Show)
-- Look at the type of foldr...
-- *GHCi> :t foldr -- foldr :: (a -> b -> b) -> b -> [a] -> b
-- It has 2 'constructor replacements': -- (a -> b -> b) & b
-- Replacing Z is easy, we can get some code to compile -- by avoiding the hard bit with a wildcard pattern "_"...
foldrNat1 :: unknown -> b -> Nat -> b foldrNat1 _ b Z = b
-- What to do about the constructor (S ..) takes a bit more -- thought or at least some experimenting. I'll do the later...
-- One thing to try, is to simply translate foldr with as few -- changes as possible:
-- foldr :: (a -> b -> b) -> b -> [a] -> b -- foldr _ z [] = z -- foldr f z (x:xs) = f x (foldr f z xs)
-- Unfortunately this leads to a problem:
foldrNat2 :: (Nat -> b -> b) -> b -> Nat -> b foldrNat2 f b Z = b -- Z case is the same as before foldrNat2 f b (S n) = f undefined (foldrNat2 f b n) -- Arggh! undefined
-- undefined is useful for prototyping, but its a real -- problem for running code!
-- Actually I had another problem as well... -- -- The difference between Nat and [a] is that List 'carries' some data -- therefore (Nat -> b -> b) on Nat is not equivalent to (a -> b -> b) -- on [a].
-- So rather than change the type signature first, get rid of the -- undefined and see what happens
foldrNat3 f b Z = b foldrNat3 f b (S n) = f (foldrNat3 f b n)
-- *GHCi> :t foldrNat3 -- > (t -> t) -> t -> Nat -> t
-- GHCi likes to call type variables t, but the signature is equal to
-- foldrNat3 :: (b -> b) -> b -> Nat -> b
-- This looks promising - it typechecks! -- So try a test:
fromNat :: Nat -> Int fromNat n = foldrNat3 (+1) 0 n
demo1 = fromNat (S (S (S Z))) -- 3 ??
-- By experimenting we seem to have a good answer, -- other people might prefer a more rigorous proof though.
-- NEU: Mit GMX DSL über 1000,- ¿ sparen! http://portal.gmx.net/de/go/dsl02

nobody here, who can tell me how it can work? -------- Original-Nachricht --------
Datum: Thu, 04 Feb 2010 21:58:45 +0100 Von: kane96@gmx.de An: Stephen Tetley
, Daniel Fischer CC: Beginners@haskell.org Betreff: Re: [Haskell-beginners] foldr for Nats
@Stephan thanks for the code so far. @Daniel it should look like foldrNat a b S(S(S(S(Z)))) gives a(a(a(a(b))))
The thing is the definition have to be -------- Original-Nachricht --------
Datum: Mon, 1 Feb 2010 21:56:14 +0000 Von: Stephen Tetley
An: kane96@gmx.de CC: Beginners@haskell.org Betreff: Re: [Haskell-beginners] foldr for Nats Hello
I'm suspecting this isn't homework as you've waited a week so would presumably have missed a deadline.
As Daniel Fischer wrote, one view of folds is that they replace the constructors of a data type, code follows...
data Nat = Z | S Nat deriving (Eq,Ord,Show)
-- Look at the type of foldr...
-- *GHCi> :t foldr -- foldr :: (a -> b -> b) -> b -> [a] -> b
-- It has 2 'constructor replacements': -- (a -> b -> b) & b
-- Replacing Z is easy, we can get some code to compile -- by avoiding the hard bit with a wildcard pattern "_"...
foldrNat1 :: unknown -> b -> Nat -> b foldrNat1 _ b Z = b
-- What to do about the constructor (S ..) takes a bit more -- thought or at least some experimenting. I'll do the later...
-- One thing to try, is to simply translate foldr with as few -- changes as possible:
-- foldr :: (a -> b -> b) -> b -> [a] -> b -- foldr _ z [] = z -- foldr f z (x:xs) = f x (foldr f z xs)
-- Unfortunately this leads to a problem:
foldrNat2 :: (Nat -> b -> b) -> b -> Nat -> b foldrNat2 f b Z = b -- Z case is the same as before foldrNat2 f b (S n) = f undefined (foldrNat2 f b n) -- Arggh! undefined
-- undefined is useful for prototyping, but its a real -- problem for running code!
-- Actually I had another problem as well... -- -- The difference between Nat and [a] is that List 'carries' some data -- therefore (Nat -> b -> b) on Nat is not equivalent to (a -> b -> b) -- on [a].
-- So rather than change the type signature first, get rid of the -- undefined and see what happens
foldrNat3 f b Z = b foldrNat3 f b (S n) = f (foldrNat3 f b n)
-- *GHCi> :t foldrNat3 -- > (t -> t) -> t -> Nat -> t
-- GHCi likes to call type variables t, but the signature is equal to
-- foldrNat3 :: (b -> b) -> b -> Nat -> b
-- This looks promising - it typechecks! -- So try a test:
fromNat :: Nat -> Int fromNat n = foldrNat3 (+1) 0 n
demo1 = fromNat (S (S (S Z))) -- 3 ??
-- By experimenting we seem to have a good answer, -- other people might prefer a more rigorous proof though.
-- NEU: Mit GMX DSL über 1000,- ¿ sparen! http://portal.gmx.net/de/go/dsl02 _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- GRATIS für alle GMX-Mitglieder: Die maxdome Movie-FLAT! Jetzt freischalten unter http://portal.gmx.net/de/go/maxdome01

Am Dienstag 26 Januar 2010 11:52:45 schrieb kane96@gmx.de:
Hello, I have: data Nat = Z | S Nat deriving (Eq,Ord,Show) and should write a function that works for Nats like foldr for list where: instance Enum Nat where toEnum i | i < 0 = error "foo"
| i == 0 = Z | otherwise = S (toEnum (i-1))
Can someone give me a hint how to do this?
I don't understand what "works for Nats like foldr for lists" means. A very nice explanation of how foldr works is foldr f z (a1 : (a2 : (a3 : (... : (an : []) ...)))) ~> (a1 `f` (a2 `f` (a3 `f` (... `f` (an `f` z) ...)))) So we replace the constructor [] with the base value z, and the constructor (:) with the function f. Maybe it's meant to be similar, foldNat f z should replace the constructor Z with the base value and the constructor S with the function.
participants (7)
-
Amy de Buitléir
-
Daniel Fischer
-
Jason Dusek
-
Joe Van Dyk
-
kane96@gmx.de
-
Stephen Tetley
-
Tom Tobin