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
9fc856c1
Commit
9fc856c1
authored
May 26, 1997
by
sof
Browse files
[project @ 1997-05-26 04:38:15 by sof]
Imports updated
parent
1bda1b2e
Changes
1
Hide whitespace changes
Inline
Side-by-side
ghc/compiler/hsSyn/HsLoop.lhi
View file @
9fc856c1
...
...
@@ -2,44 +2,32 @@
interface HsLoop where
import Hs
Expr ( HsExpr, Stmt
)
import Hs
Binds ( HsBinds, MonoBinds, Sig, nullBinds, nullMonoBinds
)
import Hs
Matches( Match, GRHSsAndBinds, pprMatch, pprMatches, pprGRHSsAndBinds
)
import Hs
Expr ( HsExpr, pprExpr
)
import HsDecls ( ConDecl )
import Name ( NamedThing )
import Outputable ( Outputable )
-- HsExpr outputs
data HsExpr tyvar uvar id pat
data Stmt tyvar uvar id pat
instance (NamedThing id, Outputable id, Outputable pat,
Eq tyvar, Outputable tyvar, Eq uvar, Outputable uvar)
=> Outputable (HsExpr tyvar uvar id pat)
instance (NamedThing id, Outputable id, Outputable pat,
Eq tyvar, Outputable tyvar, Eq uvar, Outputable uvar)
=> Outputable (Stmt tyvar uvar id pat)
import Outputable ( Outputable, PprStyle )
import Pretty ( Doc )
-- HsMatches outputs
data Match tyvar uvar id pat
data GRHSsAndBinds tyvar uvar id pat
-- HsBinds outputs
data Sig id
instance (NamedThing name, Outputable name) => Outputable (Sig name)
pprGRHSsAndBinds :: (NamedThing id, Outputable id, Outputable pat,
Eq tyvar, Outputable tyvar, Eq uvar, Outputable uvar) =>
PprStyle -> Bool -> GRHSsAndBinds tyvar uvar id pat -> Doc
data HsBinds tyvar uvar id pat
pprMatches :: (NamedThing id, Outputable id, Outputable pat,
Eq tyvar, Outputable tyvar, Eq uvar, Outputable uvar) =>
PprStyle -> (Bool, Doc) -> [Match tyvar uvar id pat] -> Doc
instance (Outputable pat,
NamedThing id, Outputable id,
Eq tyvar, Outputable tyvar, Eq uvar, Outputable uvar) =>
Outputable (HsBinds
tyvar uvar id pat
)
pprMatch :: (
NamedThing id, Outputable id,
Outputable pat,
Eq tyvar, Outputable tyvar, Eq uvar, Outputable uvar) =>
PprStyle -> Bool -> Match
tyvar uvar id pat
-> Doc
data MonoBinds tyvar uvar id pat
instance (NamedThing id, Outputable id, Outputable pat,
Eq tyvar, Outputable tyvar, Eq uvar, Outputable uvar) =>
Outputable (MonoBinds tyvar uvar id pat)
nullBinds :: HsBinds tyvar uvar id pat -> Bool
nullMonoBinds :: MonoBinds tyvar uvar id pat -> Bool
-- HsExpr outputs
data HsExpr tyvar uvar id pat
pprExpr :: (NamedThing c, Outputable c, Outputable d, Eq a, Outputable a, Eq b, Outputable b)
=> PprStyle -> HsExpr a b c d -> Doc
-- HsDecls outputs
data ConDecl name
\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