{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Language.Haskell.Syntax.ImpExp where
import Language.Haskell.Syntax.Extension
import Language.Haskell.Syntax.Module.Name
import Data.Eq (Eq)
import Data.Ord (Ord)
import Text.Show (Show)
import Data.Data (Data)
import Data.Bool (Bool)
import Data.Maybe (Maybe)
import Data.String (String)
import Data.Int (Int)
import GHC.Hs.Doc
type LImportDecl pass = XRec pass (ImportDecl pass)
data ImportDeclQualifiedStyle
= QualifiedPre
| QualifiedPost
| NotQualified
deriving (ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
$c/= :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
== :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
$c== :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
Eq, Typeable ImportDeclQualifiedStyle
ImportDeclQualifiedStyle -> DataType
ImportDeclQualifiedStyle -> Constr
(forall b. Data b => b -> b)
-> ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> u
forall u.
(forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportDeclQualifiedStyle
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportDeclQualifiedStyle
-> c ImportDeclQualifiedStyle
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportDeclQualifiedStyle)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportDeclQualifiedStyle)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
gmapT :: (forall b. Data b => b -> b)
-> ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle
$cgmapT :: (forall b. Data b => b -> b)
-> ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportDeclQualifiedStyle)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportDeclQualifiedStyle)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportDeclQualifiedStyle)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportDeclQualifiedStyle)
dataTypeOf :: ImportDeclQualifiedStyle -> DataType
$cdataTypeOf :: ImportDeclQualifiedStyle -> DataType
toConstr :: ImportDeclQualifiedStyle -> Constr
$ctoConstr :: ImportDeclQualifiedStyle -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportDeclQualifiedStyle
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportDeclQualifiedStyle
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportDeclQualifiedStyle
-> c ImportDeclQualifiedStyle
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportDeclQualifiedStyle
-> c ImportDeclQualifiedStyle
Data)
data IsBootInterface = NotBoot | IsBoot
deriving (IsBootInterface -> IsBootInterface -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IsBootInterface -> IsBootInterface -> Bool
$c/= :: IsBootInterface -> IsBootInterface -> Bool
== :: IsBootInterface -> IsBootInterface -> Bool
$c== :: IsBootInterface -> IsBootInterface -> Bool
Eq, Eq IsBootInterface
IsBootInterface -> IsBootInterface -> Bool
IsBootInterface -> IsBootInterface -> Ordering
IsBootInterface -> IsBootInterface -> IsBootInterface
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IsBootInterface -> IsBootInterface -> IsBootInterface
$cmin :: IsBootInterface -> IsBootInterface -> IsBootInterface
max :: IsBootInterface -> IsBootInterface -> IsBootInterface
$cmax :: IsBootInterface -> IsBootInterface -> IsBootInterface
>= :: IsBootInterface -> IsBootInterface -> Bool
$c>= :: IsBootInterface -> IsBootInterface -> Bool
> :: IsBootInterface -> IsBootInterface -> Bool
$c> :: IsBootInterface -> IsBootInterface -> Bool
<= :: IsBootInterface -> IsBootInterface -> Bool
$c<= :: IsBootInterface -> IsBootInterface -> Bool
< :: IsBootInterface -> IsBootInterface -> Bool
$c< :: IsBootInterface -> IsBootInterface -> Bool
compare :: IsBootInterface -> IsBootInterface -> Ordering
$ccompare :: IsBootInterface -> IsBootInterface -> Ordering
Ord, Int -> IsBootInterface -> ShowS
[IsBootInterface] -> ShowS
IsBootInterface -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IsBootInterface] -> ShowS
$cshowList :: [IsBootInterface] -> ShowS
show :: IsBootInterface -> String
$cshow :: IsBootInterface -> String
showsPrec :: Int -> IsBootInterface -> ShowS
$cshowsPrec :: Int -> IsBootInterface -> ShowS
Show, Typeable IsBootInterface
IsBootInterface -> DataType
IsBootInterface -> Constr
(forall b. Data b => b -> b) -> IsBootInterface -> IsBootInterface
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> IsBootInterface -> u
forall u. (forall d. Data d => d -> u) -> IsBootInterface -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsBootInterface
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsBootInterface -> c IsBootInterface
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IsBootInterface)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IsBootInterface)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> IsBootInterface -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> IsBootInterface -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> IsBootInterface -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IsBootInterface -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r
gmapT :: (forall b. Data b => b -> b) -> IsBootInterface -> IsBootInterface
$cgmapT :: (forall b. Data b => b -> b) -> IsBootInterface -> IsBootInterface
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IsBootInterface)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IsBootInterface)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IsBootInterface)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IsBootInterface)
dataTypeOf :: IsBootInterface -> DataType
$cdataTypeOf :: IsBootInterface -> DataType
toConstr :: IsBootInterface -> Constr
$ctoConstr :: IsBootInterface -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsBootInterface
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsBootInterface
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsBootInterface -> c IsBootInterface
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsBootInterface -> c IsBootInterface
Data)
data ImportDecl pass
= ImportDecl {
forall pass. ImportDecl pass -> XCImportDecl pass
ideclExt :: XCImportDecl pass,
forall pass. ImportDecl pass -> XRec pass ModuleName
ideclName :: XRec pass ModuleName,
forall pass. ImportDecl pass -> ImportDeclPkgQual pass
ideclPkgQual :: ImportDeclPkgQual pass,
forall pass. ImportDecl pass -> IsBootInterface
ideclSource :: IsBootInterface,
forall pass. ImportDecl pass -> Bool
ideclSafe :: Bool,
forall pass. ImportDecl pass -> ImportDeclQualifiedStyle
ideclQualified :: ImportDeclQualifiedStyle,
forall pass. ImportDecl pass -> Maybe (XRec pass ModuleName)
ideclAs :: Maybe (XRec pass ModuleName),
forall pass.
ImportDecl pass
-> Maybe (ImportListInterpretation, XRec pass [LIE pass])
ideclImportList :: Maybe (ImportListInterpretation, XRec pass [LIE pass])
}
| XImportDecl !(XXImportDecl pass)
data ImportListInterpretation = Exactly | EverythingBut
deriving (ImportListInterpretation -> ImportListInterpretation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportListInterpretation -> ImportListInterpretation -> Bool
$c/= :: ImportListInterpretation -> ImportListInterpretation -> Bool
== :: ImportListInterpretation -> ImportListInterpretation -> Bool
$c== :: ImportListInterpretation -> ImportListInterpretation -> Bool
Eq, Typeable ImportListInterpretation
ImportListInterpretation -> DataType
ImportListInterpretation -> Constr
(forall b. Data b => b -> b)
-> ImportListInterpretation -> ImportListInterpretation
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> ImportListInterpretation -> u
forall u.
(forall d. Data d => d -> u) -> ImportListInterpretation -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportListInterpretation
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportListInterpretation
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportListInterpretation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportListInterpretation
-> c ImportListInterpretation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportListInterpretation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportListInterpretation)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ImportListInterpretation -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ImportListInterpretation -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> ImportListInterpretation -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> ImportListInterpretation -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportListInterpretation
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportListInterpretation
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportListInterpretation
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportListInterpretation
-> r
gmapT :: (forall b. Data b => b -> b)
-> ImportListInterpretation -> ImportListInterpretation
$cgmapT :: (forall b. Data b => b -> b)
-> ImportListInterpretation -> ImportListInterpretation
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportListInterpretation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportListInterpretation)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportListInterpretation)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportListInterpretation)
dataTypeOf :: ImportListInterpretation -> DataType
$cdataTypeOf :: ImportListInterpretation -> DataType
toConstr :: ImportListInterpretation -> Constr
$ctoConstr :: ImportListInterpretation -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportListInterpretation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportListInterpretation
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportListInterpretation
-> c ImportListInterpretation
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportListInterpretation
-> c ImportListInterpretation
Data)
type LIE pass = XRec pass (IE pass)
data IE pass
= IEVar (XIEVar pass) (LIEWrappedName pass)
| IEThingAbs (XIEThingAbs pass) (LIEWrappedName pass)
| IEThingAll (XIEThingAll pass) (LIEWrappedName pass)
| IEThingWith (XIEThingWith pass)
(LIEWrappedName pass)
IEWildcard
[LIEWrappedName pass]
| IEModuleContents (XIEModuleContents pass) (XRec pass ModuleName)
| IEGroup (XIEGroup pass) Int (LHsDoc pass)
| IEDoc (XIEDoc pass) (LHsDoc pass)
| IEDocNamed (XIEDocNamed pass) String
| XIE !(XXIE pass)
data IEWildcard
= NoIEWildcard
| IEWildcard Int
deriving (IEWildcard -> IEWildcard -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IEWildcard -> IEWildcard -> Bool
$c/= :: IEWildcard -> IEWildcard -> Bool
== :: IEWildcard -> IEWildcard -> Bool
$c== :: IEWildcard -> IEWildcard -> Bool
Eq, Typeable IEWildcard
IEWildcard -> DataType
IEWildcard -> Constr
(forall b. Data b => b -> b) -> IEWildcard -> IEWildcard
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> IEWildcard -> u
forall u. (forall d. Data d => d -> u) -> IEWildcard -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IEWildcard
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IEWildcard -> c IEWildcard
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IEWildcard)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IEWildcard -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IEWildcard -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> IEWildcard -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IEWildcard -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
gmapT :: (forall b. Data b => b -> b) -> IEWildcard -> IEWildcard
$cgmapT :: (forall b. Data b => b -> b) -> IEWildcard -> IEWildcard
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IEWildcard)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IEWildcard)
dataTypeOf :: IEWildcard -> DataType
$cdataTypeOf :: IEWildcard -> DataType
toConstr :: IEWildcard -> Constr
$ctoConstr :: IEWildcard -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IEWildcard
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IEWildcard
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IEWildcard -> c IEWildcard
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IEWildcard -> c IEWildcard
Data)
data IEWrappedName p
= IEName (XIEName p) (LIdP p)
| IEPattern (XIEPattern p) (LIdP p)
| IEType (XIEType p) (LIdP p)
| XIEWrappedName !(XXIEWrappedName p)
type LIEWrappedName p = XRec p (IEWrappedName p)