Subversion

Galculator

?curdirlinks? -

Blame information for rev 1

Line No. Rev Author Line
1 1 paulosilva  
2 {-# LANGUAGE GADTs, TypeOperators, EmptyDataDecls, TypeSynonymInstances #-}
3 {-# OPTIONS_GHC -Wall #-}
4  
5 -------------------------------------------------------------------------------
6  
7 {- |
8 Module      :  Language.Type.Syntax
9 Description :  Polymorphic type representation of the types used by Galculator.
10 Copyright   :  (c) Paulo Silva
11 License     :  LGPL
12  
13 Maintainer  :  paufil@di.uminho.pt
14 Stability   :  experimental
15 Portability :  portable
16  
17 -}
18  
19 -------------------------------------------------------------------------------
20  
21 module Language.Type.Syntax (
22   Type(..),
23   (:<->:),
24   (:<-:),
25   PO,
26   Var,
27   GC,
28   One,
29   Name,
30   TypeBox
31  ) where
32  
33 import Data.Existential
34 import Data.Map
35 import Data.Set
36 import Language.Type.Equality
37 import Language.Type.Pretty
38  
39 -------------------------------------------------------------------------------
40  
41 type One = ()
42 type Name = String
43  
44 type b :<-: a = a -> b
45 data b :<->: a
46  
47 data GC b a
48 data PO a
49 data Var
50  
51 -------------------------------------------------------------------------------
52  
53 data Type a where
54   TVar   :: Name -> Type Var
55  
56   One    :: Type One
57   Bool   :: Type Bool
58   Char   :: Type Char
59   String :: Type String
60   Int    :: Type Int
61   Float  :: Type Float
62  
63   Prod   :: Type a -> Type b -> Type (a,b)
64   Either :: Type a -> Type b -> Type (Either a b)
65  
66   Maybe  :: Type a -> Type (Maybe a)
67   List   :: Type a -> Type [a]
68   Set    :: Type a -> Type (Set a)
69   Map    :: Type a -> Type b -> Type (Map a b)
70  
71   Fun    :: Type b -> Type a -> Type (b :<-: a)
72   Rel    :: Type b -> Type a -> Type (b :<->: a)
73   Ord    :: Type a -> Type (PO a)
74  
75   GC     :: Type b -> Type a -> Type (GC b a)
76  
77 -------------------------------------------------------------------------------
78  
79 instance Show (Type t) where
80   showsPrec _ = showType
81  
82 -------------------------------------------------------------------------------
83  
84 instance Eq (Type a) where
85   t1 == t2 = beq t1 t2
86  
87 -------------------------------------------------------------------------------
88  
89 type TypeBox = Covert Type
90  
91 -------------------------------------------------------------------------------
92  
93 instance Eq TypeBox where
94   (Hide t) == (Hide t') = beq t t'
95  
96 -------------------------------------------------------------------------------
97  
98 instance Show TypeBox where
99   show (Hide a) = show a
100  
101 -------------------------------------------------------------------------------
102  

Theme by Vikram Singh | Powered by WebSVN v2.3.3