{-# LANGUAGE DeriveDataTypeable #-}
{-# 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
$c== :: ExposedModule -> ExposedModule -> Bool
== :: ExposedModule -> ExposedModule -> Bool
$c/= :: ExposedModule -> ExposedModule -> Bool
/= :: 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
$cfrom :: forall x. ExposedModule -> Rep ExposedModule x
from :: forall x. ExposedModule -> Rep ExposedModule x
$cto :: forall x. Rep ExposedModule x -> ExposedModule
to :: forall x. Rep ExposedModule x -> ExposedModule
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
$creadsPrec :: Int -> ReadS ExposedModule
readsPrec :: Int -> ReadS ExposedModule
$creadList :: ReadS [ExposedModule]
readList :: ReadS [ExposedModule]
$creadPrec :: ReadPrec ExposedModule
readPrec :: ReadPrec ExposedModule
$creadListPrec :: ReadPrec [ExposedModule]
readListPrec :: ReadPrec [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
$cshowsPrec :: Int -> ExposedModule -> ShowS
showsPrec :: Int -> ExposedModule -> ShowS
$cshow :: ExposedModule -> String
show :: ExposedModule -> String
$cshowList :: [ExposedModule] -> ShowS
showList :: [ExposedModule] -> ShowS
Show, Typeable)

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 :: forall (m :: * -> *). CabalParsing m => m ExposedModule
parsec = do
    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
forall (m :: * -> *). CabalParsing m => m ModuleName
parsec
    P.spaces

    reexport <- P.optional $ do
      _ <- P.string "from"
      P.skipSpaces1
      parsec

    return (ExposedModule m reexport)

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