Skip to content
Snippets Groups Projects
Commit 0e61daaa authored by sof's avatar sof
Browse files

[project @ 1997-06-05 20:59:36 by sof]

import updates
parent 1f5257c1
No related merge requests found
......@@ -13,16 +13,22 @@ module HsBinds where
IMP_Ubiq()
-- friends:
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ <= 201
IMPORT_DELOOPER(HsLoop) ( pprMatches, pprGRHSsAndBinds,
Match, GRHSsAndBinds,
HsExpr, pprExpr )
pprExpr, HsExpr )
#else
import {-# SOURCE #-} HsMatches ( pprMatches, Match, pprGRHSsAndBinds, GRHSsAndBinds )
import {-# SOURCE #-} HsExpr ( pprExpr, HsExpr )
#endif
import HsPragmas ( GenPragmas, ClassOpPragmas )
import HsTypes ( HsType )
import CoreSyn ( SYN_IE(CoreExpr) )
--others:
import Id ( SYN_IE(DictVar), SYN_IE(Id), GenId )
import Name ( getOccName, OccName, NamedThing(..) )
import Name ( OccName, NamedThing(..) )
import Outputable ( interpp'SP, ifnotPprForUser, pprQuote,
Outputable(..){-instance * (,)-}
)
......
......@@ -11,7 +11,12 @@ module HsExpr where
IMP_Ubiq(){-uitous-}
-- friends:
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ <= 201
IMPORT_DELOOPER(HsLoop) ( pprMatches, pprMatch, Match )
#else
import {-# SOURCE #-} HsMatches ( pprMatches, pprMatch, Match )
#endif
import HsBinds ( HsBinds )
import HsBasic ( HsLit )
import BasicTypes ( Fixity(..), FixityDirection(..) )
......@@ -25,7 +30,6 @@ import PprType ( pprGenType, pprParendGenType, GenType{-instance-} )
import Pretty
import SrcLoc ( SrcLoc )
import Usage ( GenUsage{-instance-} )
--import Util ( panic{-ToDo:rm eventually-} )
#if __GLASGOW_HASKELL__ >= 202
import Name
#endif
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment