Skip to content
GitLab
Menu
Projects
Groups
Snippets
Loading...
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
d06c6312
Commit
d06c6312
authored
May 26, 1997
by
sof
Browse files
[project @ 1997-05-26 04:44:02 by sof]
Moved Fixity(..) and Version(..) to basicTypes/BasicTypes
parent
06af002a
Changes
1
Hide whitespace changes
Inline
Side-by-side
ghc/compiler/hsSyn/HsBasic.lhs
View file @
d06c6312
...
...
@@ -9,22 +9,11 @@
module HsBasic where
IMP_Ubiq(){-uitous-}
IMPORT_1_3(Ratio(Rational))
import Pretty
#if __GLASGOW_HASKELL__ >= 202
import Outputable
#endif
\end{code}
%************************************************************************
%* *
\subsection[Version]{Module and identifier version numbers}
%* *
%************************************************************************
\begin{code}
type Version = Int
\end{code}
%************************************************************************
...
...
@@ -80,26 +69,4 @@ instance Outputable HsLit where
ppr sty (HsLitLit s) = hcat [text "``", ptext s, text "''"]
\end{code}
%************************************************************************
%* *
\subsection[Fixity]{Fixity info}
%* *
%************************************************************************
\begin{code}
data Fixity = Fixity Int FixityDirection
data FixityDirection = InfixL | InfixR | InfixN
deriving(Eq)
instance Outputable Fixity where
ppr sty (Fixity prec dir) = hcat [ppr sty dir, space, int prec]
instance Outputable FixityDirection where
ppr sty InfixL = ptext SLIT("infixl")
ppr sty InfixR = ptext SLIT("infixr")
ppr sty InfixN = ptext SLIT("infix")
instance Eq Fixity where -- Used to determine if two fixities conflict
(Fixity p1 dir1) == (Fixity p2 dir2) = p1==p2 && dir1 == dir2
\end{code}
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment