{-# LANGUAGE DeriveGeneric #-}
module Distribution.Types.ExposedModule where

import Distribution.Compat.Prelude
import Prelude ()

import Distribution.Backpack
import Distribution.ModuleName
import Distribution.Parsec
import Distribution.Pretty

import qualified Distribution.Compat.CharParsing as P
import qualified Text.PrettyPrint                as Disp

data ExposedModule
   = ExposedModule {
       ExposedModule -> ModuleName
exposedName      :: ModuleName,
       ExposedModule -> Maybe OpenModule
exposedReexport  :: Maybe OpenModule
     }
  deriving (ExposedModule -> ExposedModule -> Bool
(ExposedModule -> ExposedModule -> Bool)
-> (ExposedModule -> ExposedModule -> Bool) -> Eq ExposedModule
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExposedModule -> ExposedModule -> Bool
$c/= :: ExposedModule -> ExposedModule -> Bool
== :: ExposedModule -> ExposedModule -> Bool
$c== :: ExposedModule -> ExposedModule -> Bool
Eq, (forall x. ExposedModule -> Rep ExposedModule x)
-> (forall x. Rep ExposedModule x -> ExposedModule)
-> Generic ExposedModule
forall x. Rep ExposedModule x -> ExposedModule
forall x. ExposedModule -> Rep ExposedModule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExposedModule x -> ExposedModule
$cfrom :: forall x. ExposedModule -> Rep ExposedModule x
Generic, ReadPrec [ExposedModule]
ReadPrec ExposedModule
Int -> ReadS ExposedModule
ReadS [ExposedModule]
(Int -> ReadS ExposedModule)
-> ReadS [ExposedModule]
-> ReadPrec ExposedModule
-> ReadPrec [ExposedModule]
-> Read ExposedModule
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExposedModule]
$creadListPrec :: ReadPrec [ExposedModule]
readPrec :: ReadPrec ExposedModule
$creadPrec :: ReadPrec ExposedModule
readList :: ReadS [ExposedModule]
$creadList :: ReadS [ExposedModule]
readsPrec :: Int -> ReadS ExposedModule
$creadsPrec :: Int -> ReadS ExposedModule
Read, Int -> ExposedModule -> ShowS
[ExposedModule] -> ShowS
ExposedModule -> String
(Int -> ExposedModule -> ShowS)
-> (ExposedModule -> String)
-> ([ExposedModule] -> ShowS)
-> Show ExposedModule
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExposedModule] -> ShowS
$cshowList :: [ExposedModule] -> ShowS
show :: ExposedModule -> String
$cshow :: ExposedModule -> String
showsPrec :: Int -> ExposedModule -> ShowS
$cshowsPrec :: Int -> ExposedModule -> ShowS
Show)

instance Pretty ExposedModule where
    pretty :: ExposedModule -> Doc
pretty (ExposedModule ModuleName
m Maybe OpenModule
reexport) =
        [Doc] -> Doc
Disp.hsep [ ModuleName -> Doc
forall a. Pretty a => a -> Doc
pretty ModuleName
m
                  , case Maybe OpenModule
reexport of
                     Just OpenModule
m' -> [Doc] -> Doc
Disp.hsep [String -> Doc
Disp.text String
"from", OpenModule -> Doc
forall a. Pretty a => a -> Doc
pretty OpenModule
m']
                     Maybe OpenModule
Nothing -> Doc
Disp.empty
                  ]

instance Parsec ExposedModule where
    parsec :: m ExposedModule
parsec = do
        ModuleName
m <- m ModuleName -> m ModuleName
forall (m :: * -> *) a. CabalParsing m => m a -> m a
parsecMaybeQuoted m ModuleName
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
        m ()
forall (m :: * -> *). CharParsing m => m ()
P.spaces

        Maybe OpenModule
reexport <- m OpenModule -> m (Maybe OpenModule)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
P.optional (m OpenModule -> m (Maybe OpenModule))
-> m OpenModule -> m (Maybe OpenModule)
forall a b. (a -> b) -> a -> b
$ do
            String
_ <- String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
P.string String
"from"
            m ()
forall (m :: * -> *). CharParsing m => m ()
P.skipSpaces1
            m OpenModule
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec

        ExposedModule -> m ExposedModule
forall (m :: * -> *) a. Monad m => a -> m a
return (ModuleName -> Maybe OpenModule -> ExposedModule
ExposedModule ModuleName
m Maybe OpenModule
reexport)

instance Binary ExposedModule

instance NFData ExposedModule where rnf :: ExposedModule -> ()
rnf = ExposedModule -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf