{-# 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
(ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool)
-> (ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool)
-> Eq ImportDeclQualifiedStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
== :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
$c/= :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
/= :: ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle -> Bool
Eq, Typeable ImportDeclQualifiedStyle
Typeable ImportDeclQualifiedStyle =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportDeclQualifiedStyle
-> c ImportDeclQualifiedStyle)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportDeclQualifiedStyle)
-> (ImportDeclQualifiedStyle -> Constr)
-> (ImportDeclQualifiedStyle -> DataType)
-> (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))
-> ((forall b. Data b => b -> b)
-> ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle)
-> (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 u.
(forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle)
-> Data ImportDeclQualifiedStyle
ImportDeclQualifiedStyle -> Constr
ImportDeclQualifiedStyle -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportDeclQualifiedStyle
-> c ImportDeclQualifiedStyle
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportDeclQualifiedStyle
-> c ImportDeclQualifiedStyle
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportDeclQualifiedStyle
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportDeclQualifiedStyle
$ctoConstr :: ImportDeclQualifiedStyle -> Constr
toConstr :: ImportDeclQualifiedStyle -> Constr
$cdataTypeOf :: ImportDeclQualifiedStyle -> DataType
dataTypeOf :: ImportDeclQualifiedStyle -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportDeclQualifiedStyle)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportDeclQualifiedStyle)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportDeclQualifiedStyle)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportDeclQualifiedStyle)
$cgmapT :: (forall b. Data b => b -> b)
-> ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle
gmapT :: (forall b. Data b => b -> b)
-> ImportDeclQualifiedStyle -> ImportDeclQualifiedStyle
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportDeclQualifiedStyle
-> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> [u]
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> u
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ImportDeclQualifiedStyle -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportDeclQualifiedStyle -> m ImportDeclQualifiedStyle
Data)
data IsBootInterface = NotBoot | IsBoot
deriving (IsBootInterface -> IsBootInterface -> Bool
(IsBootInterface -> IsBootInterface -> Bool)
-> (IsBootInterface -> IsBootInterface -> Bool)
-> Eq IsBootInterface
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IsBootInterface -> IsBootInterface -> Bool
== :: IsBootInterface -> IsBootInterface -> Bool
$c/= :: IsBootInterface -> IsBootInterface -> Bool
/= :: IsBootInterface -> IsBootInterface -> Bool
Eq, Eq IsBootInterface
Eq IsBootInterface =>
(IsBootInterface -> IsBootInterface -> Ordering)
-> (IsBootInterface -> IsBootInterface -> Bool)
-> (IsBootInterface -> IsBootInterface -> Bool)
-> (IsBootInterface -> IsBootInterface -> Bool)
-> (IsBootInterface -> IsBootInterface -> Bool)
-> (IsBootInterface -> IsBootInterface -> IsBootInterface)
-> (IsBootInterface -> IsBootInterface -> IsBootInterface)
-> Ord 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
$ccompare :: IsBootInterface -> IsBootInterface -> Ordering
compare :: IsBootInterface -> IsBootInterface -> Ordering
$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
>= :: IsBootInterface -> IsBootInterface -> Bool
$cmax :: IsBootInterface -> IsBootInterface -> IsBootInterface
max :: IsBootInterface -> IsBootInterface -> IsBootInterface
$cmin :: IsBootInterface -> IsBootInterface -> IsBootInterface
min :: IsBootInterface -> IsBootInterface -> IsBootInterface
Ord, Int -> IsBootInterface -> ShowS
[IsBootInterface] -> ShowS
IsBootInterface -> String
(Int -> IsBootInterface -> ShowS)
-> (IsBootInterface -> String)
-> ([IsBootInterface] -> ShowS)
-> Show IsBootInterface
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IsBootInterface -> ShowS
showsPrec :: Int -> IsBootInterface -> ShowS
$cshow :: IsBootInterface -> String
show :: IsBootInterface -> String
$cshowList :: [IsBootInterface] -> ShowS
showList :: [IsBootInterface] -> ShowS
Show, Typeable IsBootInterface
Typeable IsBootInterface =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsBootInterface -> c IsBootInterface)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsBootInterface)
-> (IsBootInterface -> Constr)
-> (IsBootInterface -> DataType)
-> (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))
-> ((forall b. Data b => b -> b)
-> IsBootInterface -> IsBootInterface)
-> (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 u.
(forall d. Data d => d -> u) -> IsBootInterface -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> IsBootInterface -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface)
-> Data IsBootInterface
IsBootInterface -> Constr
IsBootInterface -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsBootInterface -> c IsBootInterface
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IsBootInterface -> c IsBootInterface
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsBootInterface
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IsBootInterface
$ctoConstr :: IsBootInterface -> Constr
toConstr :: IsBootInterface -> Constr
$cdataTypeOf :: IsBootInterface -> DataType
dataTypeOf :: IsBootInterface -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IsBootInterface)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IsBootInterface)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IsBootInterface)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IsBootInterface)
$cgmapT :: (forall b. Data b => b -> b) -> IsBootInterface -> IsBootInterface
gmapT :: (forall b. Data b => b -> b) -> IsBootInterface -> IsBootInterface
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IsBootInterface -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> IsBootInterface -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> IsBootInterface -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> IsBootInterface -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m IsBootInterface
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IsBootInterface -> m 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
(ImportListInterpretation -> ImportListInterpretation -> Bool)
-> (ImportListInterpretation -> ImportListInterpretation -> Bool)
-> Eq ImportListInterpretation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImportListInterpretation -> ImportListInterpretation -> Bool
== :: ImportListInterpretation -> ImportListInterpretation -> Bool
$c/= :: ImportListInterpretation -> ImportListInterpretation -> Bool
/= :: ImportListInterpretation -> ImportListInterpretation -> Bool
Eq, Typeable ImportListInterpretation
Typeable ImportListInterpretation =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportListInterpretation
-> c ImportListInterpretation)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportListInterpretation)
-> (ImportListInterpretation -> Constr)
-> (ImportListInterpretation -> DataType)
-> (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))
-> ((forall b. Data b => b -> b)
-> ImportListInterpretation -> ImportListInterpretation)
-> (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 u.
(forall d. Data d => d -> u) -> ImportListInterpretation -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u) -> ImportListInterpretation -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation)
-> Data ImportListInterpretation
ImportListInterpretation -> Constr
ImportListInterpretation -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportListInterpretation
-> c ImportListInterpretation
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ImportListInterpretation
-> c ImportListInterpretation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportListInterpretation
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ImportListInterpretation
$ctoConstr :: ImportListInterpretation -> Constr
toConstr :: ImportListInterpretation -> Constr
$cdataTypeOf :: ImportListInterpretation -> DataType
dataTypeOf :: ImportListInterpretation -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportListInterpretation)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ImportListInterpretation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportListInterpretation)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ImportListInterpretation)
$cgmapT :: (forall b. Data b => b -> b)
-> ImportListInterpretation -> ImportListInterpretation
gmapT :: (forall b. Data b => b -> b)
-> ImportListInterpretation -> ImportListInterpretation
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportListInterpretation
-> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ImportListInterpretation
-> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> ImportListInterpretation -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> ImportListInterpretation -> [u]
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ImportListInterpretation -> u
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ImportListInterpretation -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m ImportListInterpretation
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ImportListInterpretation -> m 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
(IEWildcard -> IEWildcard -> Bool)
-> (IEWildcard -> IEWildcard -> Bool) -> Eq IEWildcard
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IEWildcard -> IEWildcard -> Bool
== :: IEWildcard -> IEWildcard -> Bool
$c/= :: IEWildcard -> IEWildcard -> Bool
/= :: IEWildcard -> IEWildcard -> Bool
Eq, Typeable IEWildcard
Typeable IEWildcard =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IEWildcard -> c IEWildcard)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IEWildcard)
-> (IEWildcard -> Constr)
-> (IEWildcard -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> IEWildcard -> IEWildcard)
-> (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 u. (forall d. Data d => d -> u) -> IEWildcard -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> IEWildcard -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard)
-> Data IEWildcard
IEWildcard -> Constr
IEWildcard -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IEWildcard -> c IEWildcard
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IEWildcard -> c IEWildcard
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IEWildcard
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IEWildcard
$ctoConstr :: IEWildcard -> Constr
toConstr :: IEWildcard -> Constr
$cdataTypeOf :: IEWildcard -> DataType
dataTypeOf :: IEWildcard -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IEWildcard)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IEWildcard)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard)
$cgmapT :: (forall b. Data b => b -> b) -> IEWildcard -> IEWildcard
gmapT :: (forall b. Data b => b -> b) -> IEWildcard -> IEWildcard
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IEWildcard -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IEWildcard -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> IEWildcard -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IEWildcard -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IEWildcard -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IEWildcard -> m 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)