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 ...@@ -13,16 +13,22 @@ module HsBinds where
IMP_Ubiq() IMP_Ubiq()
-- friends: -- friends:
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ <= 201
IMPORT_DELOOPER(HsLoop) ( pprMatches, pprGRHSsAndBinds, IMPORT_DELOOPER(HsLoop) ( pprMatches, pprGRHSsAndBinds,
Match, GRHSsAndBinds, 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 HsPragmas ( GenPragmas, ClassOpPragmas )
import HsTypes ( HsType ) import HsTypes ( HsType )
import CoreSyn ( SYN_IE(CoreExpr) ) import CoreSyn ( SYN_IE(CoreExpr) )
--others: --others:
import Id ( SYN_IE(DictVar), SYN_IE(Id), GenId ) import Id ( SYN_IE(DictVar), SYN_IE(Id), GenId )
import Name ( getOccName, OccName, NamedThing(..) ) import Name ( OccName, NamedThing(..) )
import Outputable ( interpp'SP, ifnotPprForUser, pprQuote, import Outputable ( interpp'SP, ifnotPprForUser, pprQuote,
Outputable(..){-instance * (,)-} Outputable(..){-instance * (,)-}
) )
......
...@@ -11,7 +11,12 @@ module HsExpr where ...@@ -11,7 +11,12 @@ module HsExpr where
IMP_Ubiq(){-uitous-} IMP_Ubiq(){-uitous-}
-- friends: -- friends:
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ <= 201
IMPORT_DELOOPER(HsLoop) ( pprMatches, pprMatch, Match ) IMPORT_DELOOPER(HsLoop) ( pprMatches, pprMatch, Match )
#else
import {-# SOURCE #-} HsMatches ( pprMatches, pprMatch, Match )
#endif
import HsBinds ( HsBinds ) import HsBinds ( HsBinds )
import HsBasic ( HsLit ) import HsBasic ( HsLit )
import BasicTypes ( Fixity(..), FixityDirection(..) ) import BasicTypes ( Fixity(..), FixityDirection(..) )
...@@ -25,7 +30,6 @@ import PprType ( pprGenType, pprParendGenType, GenType{-instance-} ) ...@@ -25,7 +30,6 @@ import PprType ( pprGenType, pprParendGenType, GenType{-instance-} )
import Pretty import Pretty
import SrcLoc ( SrcLoc ) import SrcLoc ( SrcLoc )
import Usage ( GenUsage{-instance-} ) import Usage ( GenUsage{-instance-} )
--import Util ( panic{-ToDo:rm eventually-} )
#if __GLASGOW_HASKELL__ >= 202 #if __GLASGOW_HASKELL__ >= 202
import Name import Name
#endif #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