snd and tuples of various sizes...

This seems to make using tuples of various sizes easier (and can also be applied to non-tuples). I think it more closely matches how I describe something in spoken language (when I say "second" its obvious what that means for any tuple size): {-# OPTIONS_GHC -fglasgow-exts #-} module Main where class Second a b | a -> b where snd :: a -> b instance Second (a,b) b where snd (a,b) = b instance Second (a,b,c) b where snd (a,b,c) = b instance Second (a,b,c,d) b where snd (a,b,c,d) = b instance Second (a,b,c,d,e) b where snd (a,b,c,d,e) = b instance Second (a,b,c,d,e,f) b where snd (a,b,c,d,e,f) = b instance Second [a] a where snd [] = error "don't got none" snd (x:y:xs) = y main = do print $ snd (1,2) print $ snd (8,9,3) print $ snd (9,8,9,3) print $ snd (4,9,8,9,3) print $ snd [3,4] Tim Newsham http://www.thenewsh.com/~newsham/

On Thu, 2007-02-01 at 21:01 -1000, Tim Newsham wrote:
instance Second [a] a where snd [] = error "don't got none" snd (x:y:xs) = y
Would'nt that instance mean this: snd [] produces error snd [x] gives [] I'd implement it something like this (if this works?): instance Second [a] (Maybe a) where snd [] = Nothing snd [x] = Nothing snd (x:y:xs) = Just y

Mattias Bengtsson wrote:
On Thu, 2007-02-01 at 21:01 -1000, Tim Newsham wrote:
instance Second [a] a where snd [] = error "don't got none" snd (x:y:xs) = y
Would'nt that instance mean this: snd [] produces error snd [x] gives []
I'd implement it something like this (if this works?):
instance Second [a] (Maybe a) where snd [] = Nothing snd [x] = Nothing snd (x:y:xs) = Just y
And while we're re-implementing the Prelude with MPTC: class Currying a b | a -> b where curryC :: a -> b uncurryC :: b -> a instance Currying ((a, b) -> c) (a -> b -> c) where curryC = curry uncurryC = uncurry instance Currying ((a, b, c) -> d) (a -> b -> c -> d) where curryC f a b c = f (a, b, c) uncurryC f (a, b, c) = f a b c instance Currying ((a, b, c, d) -> e) (a -> b -> c -> d -> e) where curryC f a b c d = f (a, b, c, d) uncurryC f (a, b, c, d) = f a b c d instance Currying ((a, b, c, d, e) -> f) (a -> b -> c -> d -> e -> f) where curryC f a b c d e = f (a, b, c, d, e) uncurryC f (a, b, c, d, e) = f a b c d e ... Andreas -- some cannot be created more equal than others

"Mattias" == Mattias Bengtsson
writes:
Mattias> On Thu, 2007-02-01 at 21:01 -1000, Tim Newsham wrote:
instance Second [a] a where snd [] = error "don't got none" snd (x:y:xs) = y
Mattias> Would'nt that instance mean this: snd [] produces error Mattias> snd [x] gives [] No. It is non-exhaustive pattern. In fact this is needed:
instance Second [a] a where snd (_:y:_) = y snd _ = error "don't got none"
Mattias> I'd implement it something like this (if this works?): Mattias> instance Second [a] (Maybe a) where snd [] = Nothing snd Mattias> [x] = Nothing snd (x:y:xs) = Just y Well, we also can define:
class SafeSecond a b | a -> b where ssnd :: (Monad m) => a -> m b
instance SafeSecond [a] a where ssnd (_:y:_) = return y ssnd _ = fail "don't got none"
main = do print $ (ssnd [1, 2, 3] :: Maybe Int) print $ (ssnd [1] :: Maybe Int)
-- WBR, Max Vasin.
participants (4)
-
Andreas Farre
-
Mattias Bengtsson
-
Max Vasin
-
Tim Newsham