[project @ 1998-12-02 13:17:09 by simonm]
[ghc-hetmet.git] / ghc / interpreter / test / unused / syntax.hs
1 --!!! Testing Haskell 1.3 syntax
2
3 -- Haskell 1.3 syntax differs from Haskell 1.2 syntax in several ways:
4
5 -- * Qualified names in export lists
6 module TestSyntax where
7
8 -- * Qualified import/export
9
10 --   1) Syntax:
11
12 import qualified Prelude as P
13
14 import Prelude
15 import qualified Prelude
16
17 import Prelude ()
18 import Prelude (fst,snd)
19 import qualified Prelude(fst,snd)
20
21 -- bizarre syntax allowed in draft of Haskell 1.3 
22 import Prelude(,)
23 import Prelude(fst,snd,)
24 import Prelude(Ord(..),Eq((==),(/=)),)
25 import Prelude hiding (fst,snd,)
26
27 import Prelude hiding (fst,snd)
28 import qualified Prelude hiding (fst,snd)
29
30 import Prelude as P
31 import qualified Prelude as P
32
33 import Prelude as P(fst,snd)
34 import Prelude as P(,)
35 import qualified Prelude as P(fst,snd)
36
37 import Prelude as P hiding (fst,snd)
38 import qualified Prelude as P hiding (fst,snd)
39
40 -- 2) Use of qualified type names
41 -- 3) Use of qualified constructors
42 -- 4) Use of qualified variables
43
44 -- * No n+k patterns (yippee!)
45 --   (No tests yet)
46
47 -- Some things are unchanged.
48
49 -- * Unqualified imports and use of hiding/selective import.
50 --
51 --   Note: it's not clear how these various imports are supposed to
52 --         interact with one another.
53 --         John explains: 
54 --         1) "hiding" lists etc are just abbreviations for very long
55 --            lists.
56 --         2) Multiple imports are additive.
57 --         (This makes the meaning order-independent!)
58 --   Note: Hugs allows imports anywhere a topdecl is allowed.
59 --         This isn't legal Haskell - but it does no harm.
60
61 -- import Prelude(lex)
62 -- import Prelude
63 -- import Prelude hiding (lex)
64 -- lex = 1 :: Int -- error unless we've hidden lex.
65
66
67
68 -- * Qualified names
69
70 -- Function/operator names
71 myfilter  x = Prelude.filter x  -- argument added to avoid monomorphism restn
72 mycompose = (Prelude..)
73
74 -- Use of module synonyms
75 myfilter2 p = P.filter p
76
77 -- Method names
78 myplus :: Num a => a -> a -> a
79 myplus = (Prelude.+) 
80
81 -- Tycons
82 myminus = (Prelude.-) :: Prelude.Int -> Prelude.Int -> Prelude.Int
83
84 -- Type synonyms
85 foo :: P.ShowS
86 foo = foo
87
88 -- Class names in instances
89 instance P.Num P.Bool where
90   (+) = (P.||)
91   (*) = (P.&&)
92   negate = P.not
93
94 instance (P.Num a, P.Num b) => P.Num (a,b) where
95   x + y = (fst x + fst y, snd x + snd y)
96
97 -- Constructor names in expressions
98
99 -- this used to break tidyInfix in parser.y
100 -- Note that P.[] is _not_ legal!
101 testInfixQualifiedCon = 'a' P.: [] :: String
102
103 -- Constructor names in patterns
104 f (P.Just x)  = True
105 f (P.Nothing) = False
106
107 g (x P.: xs) = x
108
109 y P.: ys = ['a'..]
110
111 -- * Support for octal and hexadecimal numbers
112 --   Note: 0xff and 0xFF are legal but 0Xff and 0XFF are not.
113 --   ToDo: negative tests to make sure invalid numbers are excluded.
114
115 d = (  -1,  -0,  0,  1)    :: (Int,Int,Int,Int)
116 o = (-0o1,-0o0,0o0,0o1)    :: (Int,Int,Int,Int)
117 x = (-0x1,-0x0,0x0,0x1)    :: (Int,Int,Int,Int)
118 x' = (0xff,0xFf,0xfF,0xFF) :: (Int,Int,Int,Int)
119
120 -- * No renaming or interface files
121 --   We test that "interface", "renaming" and "to" are not reserved.
122
123 interface = 1  :: Int
124 renaming  = 42 :: Int
125 to        = 2  :: Int
126