summaryrefslogtreecommitdiff
path: root/ghc/compiler/types/Kind.lhs
blob: cb29e48cceaf8b9a4761cd86d3e4e77e6783b194 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
%
% (c) The AQUA Project, Glasgow University, 1996
%
\section[Kind]{The @Kind@ datatype}

\begin{code}
#include "HsVersions.h"

module Kind (
	Kind(..),		-- Only visible to friends: TcKind

	mkArrowKind,
	mkTypeKind,
	mkUnboxedTypeKind,
	mkBoxedTypeKind,

	hasMoreBoxityInfo,
	resultKind, argKind,

	pprKind, pprParendKind,

	isUnboxedTypeKind, isTypeKind, isBoxedTypeKind,
	notArrowKind
    ) where

IMP_Ubiq(){-uitous-}

import Util		( panic, assertPanic )
--import Outputable	( Outputable(..) )
import Pretty
\end{code}

\begin{code}
data Kind
  = TypeKind		-- Any type (incl unboxed types)
  | BoxedTypeKind	-- Any boxed type
  | UnboxedTypeKind	-- Any unboxed type
  | ArrowKind Kind Kind
  deriving Eq

mkArrowKind 	  = ArrowKind
mkTypeKind  	  = TypeKind
mkUnboxedTypeKind = UnboxedTypeKind
mkBoxedTypeKind   = BoxedTypeKind

isTypeKind :: Kind -> Bool
isTypeKind TypeKind = True
isTypeKind other    = False

isBoxedTypeKind :: Kind -> Bool
isBoxedTypeKind BoxedTypeKind = True
isBoxedTypeKind other         = False

isUnboxedTypeKind :: Kind -> Bool
isUnboxedTypeKind UnboxedTypeKind = True
isUnboxedTypeKind other	 	  = False

hasMoreBoxityInfo :: Kind -> Kind -> Bool

BoxedTypeKind 	`hasMoreBoxityInfo` TypeKind	    = True
BoxedTypeKind   `hasMoreBoxityInfo` BoxedTypeKind   = True

UnboxedTypeKind `hasMoreBoxityInfo` TypeKind 	    = True
UnboxedTypeKind `hasMoreBoxityInfo` UnboxedTypeKind = True

TypeKind	`hasMoreBoxityInfo` TypeKind	    = True

kind1@(ArrowKind _ _) `hasMoreBoxityInfo` kind2@(ArrowKind _ _) = ASSERT( kind1 == kind2 )
								  True
	-- The two kinds can be arrow kinds; for example when unifying
	-- (m1 Int) and (m2 Int) we end up unifying m1 and m2, which should
	-- have the same kind.

kind1		`hasMoreBoxityInfo` kind2	    = False

notArrowKind (ArrowKind _ _) = False
notArrowKind other_kind	     = True

resultKind :: Kind -> Kind	-- Get result from arrow kind
resultKind (ArrowKind _ res_kind) = res_kind
resultKind other_kind 		  = panic "resultKind"

argKind :: Kind -> Kind		-- Get argument from arrow kind
argKind (ArrowKind arg_kind _) = arg_kind
argKind other_kind 	       = panic "argKind"
\end{code}

Printing
~~~~~~~~
\begin{code}
instance Outputable Kind where
  ppr sty kind = pprKind kind

pprKind TypeKind        = ppStr "**"	-- Can be boxed or unboxed
pprKind BoxedTypeKind   = ppStr "*"
pprKind UnboxedTypeKind = ppStr "*#"	-- Unboxed
pprKind (ArrowKind k1 k2) = ppSep [pprParendKind k1, ppStr "->", pprKind k2]

pprParendKind k@(ArrowKind _ _) = ppBesides [ppLparen, pprKind k, ppRparen]
pprParendKind k		 	= pprKind k
\end{code}