[project @ 1997-09-03 23:42:37 by sof]
[ghc-hetmet.git] / ghc / lib / ghc / PrelTup.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1996
3 %
4
5 \section[PrelTup]{Module @PrelTup@}
6
7 This modules defines the typle data types.
8
9 \begin{code}
10 {-# OPTIONS -fno-implicit-prelude #-}
11
12 module PrelTup where
13
14 import {-# SOURCE #-}   IOBase  ( error )
15 import PrelBase
16 \end{code}
17
18
19 %*********************************************************
20 %*                                                      *
21 \subsection{Other tuple types}
22 %*                                                      *
23 %*********************************************************
24
25 \begin{code}
26 data (,) a b = (,) a b   deriving (Eq, Ord, Bounded)
27 data (,,) a b c = (,,) a b c deriving (Eq, Ord, Bounded)
28 data (,,,) a b c d = (,,,) a b c d deriving (Eq, Ord, Bounded)
29 data (,,,,) a b c d e = (,,,,) a b c d e deriving (Eq, Ord, Bounded)
30 data (,,,,,) a b c d e f = (,,,,,) a b c d e f
31 data (,,,,,,) a b c d e f g = (,,,,,,) a b c d e f g
32 data (,,,,,,,) a b c d e f g h = (,,,,,,,) a b c d e f g h
33 data (,,,,,,,,) a b c d e f g h i = (,,,,,,,,) a b c d e f g h i
34 data (,,,,,,,,,) a b c d e f g h i j = (,,,,,,,,,) a b c d e f g h i j
35 data (,,,,,,,,,,) a b c d e f g h i j k = (,,,,,,,,,,) a b c d e f g h i j k
36 data (,,,,,,,,,,,) a b c d e f g h i j k l = (,,,,,,,,,,,) a b c d e f g h i j k l
37 data (,,,,,,,,,,,,) a b c d e f g h i j k l m = (,,,,,,,,,,,,) a b c d e f g h i j k l m
38 data (,,,,,,,,,,,,,) a b c d e f g h i j k l m n = (,,,,,,,,,,,,,) a b c d e f g h i j k l m n
39 data (,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o = (,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o
40 data (,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p = (,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p
41 data (,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q
42  = (,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q
43 data (,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r
44  = (,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r
45 data (,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s
46  = (,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s
47 data (,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t
48  = (,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t
49 data (,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u
50  = (,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u
51 data (,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v
52  = (,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v
53 data (,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w
54  = (,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w
55 data (,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x
56  = (,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x
57 data (,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y
58  = (,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y
59 data (,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z
60  = (,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z
61 data (,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_
62  = (,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_
63 data (,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_
64  = (,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_
65 data (,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_
66  = (,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_
67 data (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_
68  = (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_
69 data (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_
70  = (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_
71 data (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_ f_
72  = (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_ f_
73 data (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_ f_ g_
74  = (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_ f_ g_
75 data (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_ f_ g_ h_
76  = (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_ f_ g_ h_
77 data (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_ f_ g_ h_ i_
78  = (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_ f_ g_ h_ i_
79 data (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_ f_ g_ h_ i_ j_
80  = (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_ f_ g_ h_ i_ j_
81 data (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_ f_ g_ h_ i_ j_ k_
82  = (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_ f_ g_ h_ i_ j_ k_
83 \end{code}
84
85 @Show@ instances for just the first few.
86
87 \begin{code}
88 instance  (Show a, Show b) => Show (a,b)  where
89     showsPrec p (x,y) = showChar '(' . shows x . showString ", " .
90                                        shows y . showChar ')'
91     showList    = showList__ (showsPrec 0) 
92
93 instance (Show a, Show b, Show c) => Show (a, b, c) where
94     showsPrec p (x,y,z) = showChar '(' . showsPrec 0 x . showString ", " .
95                                          showsPrec 0 y . showString ", " .
96                                          showsPrec 0 z . showChar ')'
97     showList    = showList__ (showsPrec 0) 
98
99 instance (Show a, Show b, Show c, Show d) => Show (a, b, c, d) where
100     showsPrec p (w,x,y,z) = showChar '(' . showsPrec 0 w . showString ", " .
101                                            showsPrec 0 x . showString ", " .
102                                            showsPrec 0 y . showString ", " .
103                                            showsPrec 0 z . showChar ')'
104
105     showList    = showList__ (showsPrec 0) 
106
107 instance (Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) where
108     showsPrec p (v,w,x,y,z) = showChar '(' . showsPrec 0 v . showString ", " .
109                                              showsPrec 0 w . showString ", " .
110                                              showsPrec 0 x . showString ", " .
111                                              showsPrec 0 y . showString ", " .
112                                              showsPrec 0 z . showChar ')'
113     showList    = showList__ (showsPrec 0) 
114 \end{code}
115
116
117 %*********************************************************
118 %*                                                      *
119 \subsection{Standard functions over tuples}
120 *                                                       *
121 %*********************************************************
122
123 \begin{code}
124 fst                     :: (a,b) -> a
125 fst (x,y)               =  x
126
127 snd                     :: (a,b) -> b
128 snd (x,y)               =  y
129
130 -- curry converts an uncurried function to a curried function;
131 -- uncurry converts a curried function to a function on pairs.
132 curry                   :: ((a, b) -> c) -> a -> b -> c
133 curry f x y             =  f (x, y)
134
135 uncurry                 :: (a -> b -> c) -> ((a, b) -> c)
136 uncurry f p             =  f (fst p) (snd p)
137 \end{code}
138