[Haskell-cafe] snd and tuples of various sizes...

Tim Newsham newsham at lava.net
Fri Feb 2 02:01:18 EST 2007


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/


More information about the Haskell-Cafe mailing list