{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.Types.ModuleRenaming (
ModuleRenaming(..),
interpModuleRenaming,
defaultRenaming,
isDefaultRenaming,
) where
import Distribution.CabalSpecVersion
import Distribution.Compat.Prelude hiding (empty)
import Prelude ()
import Distribution.ModuleName
import Distribution.Parsec
import Distribution.Pretty
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Distribution.Compat.CharParsing as P
import Text.PrettyPrint (hsep, parens, punctuate, text, (<+>), comma)
data ModuleRenaming
= ModuleRenaming [(ModuleName, ModuleName)]
| DefaultRenaming
| HidingRenaming [ModuleName]
deriving (Int -> ModuleRenaming -> ShowS
[ModuleRenaming] -> ShowS
ModuleRenaming -> String
(Int -> ModuleRenaming -> ShowS)
-> (ModuleRenaming -> String)
-> ([ModuleRenaming] -> ShowS)
-> Show ModuleRenaming
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModuleRenaming] -> ShowS
$cshowList :: [ModuleRenaming] -> ShowS
show :: ModuleRenaming -> String
$cshow :: ModuleRenaming -> String
showsPrec :: Int -> ModuleRenaming -> ShowS
$cshowsPrec :: Int -> ModuleRenaming -> ShowS
External instance of the constraint type Show ModuleName
External instance of the constraint type Show ModuleName
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
External instance of the constraint type Show ModuleName
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
External instance of the constraint type Show ModuleName
External instance of the constraint type Show ModuleName
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
Show, ReadPrec [ModuleRenaming]
ReadPrec ModuleRenaming
Int -> ReadS ModuleRenaming
ReadS [ModuleRenaming]
(Int -> ReadS ModuleRenaming)
-> ReadS [ModuleRenaming]
-> ReadPrec ModuleRenaming
-> ReadPrec [ModuleRenaming]
-> Read ModuleRenaming
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModuleRenaming]
$creadListPrec :: ReadPrec [ModuleRenaming]
readPrec :: ReadPrec ModuleRenaming
$creadPrec :: ReadPrec ModuleRenaming
readList :: ReadS [ModuleRenaming]
$creadList :: ReadS [ModuleRenaming]
readsPrec :: Int -> ReadS ModuleRenaming
$creadsPrec :: Int -> ReadS ModuleRenaming
External instance of the constraint type Read ModuleName
External instance of the constraint type Read ModuleName
External instance of the constraint type forall a b. (Read a, Read b) => Read (a, b)
External instance of the constraint type Read ModuleName
External instance of the constraint type forall a b. (Read a, Read b) => Read (a, b)
External instance of the constraint type Read ModuleName
External instance of the constraint type Read ModuleName
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read ModuleRenaming
Read, ModuleRenaming -> ModuleRenaming -> Bool
(ModuleRenaming -> ModuleRenaming -> Bool)
-> (ModuleRenaming -> ModuleRenaming -> Bool) -> Eq ModuleRenaming
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModuleRenaming -> ModuleRenaming -> Bool
$c/= :: ModuleRenaming -> ModuleRenaming -> Bool
== :: ModuleRenaming -> ModuleRenaming -> Bool
$c== :: ModuleRenaming -> ModuleRenaming -> Bool
External instance of the constraint type Eq ModuleName
External instance of the constraint type Eq ModuleName
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type Eq ModuleName
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type Eq ModuleName
External instance of the constraint type Eq ModuleName
External instance of the constraint type forall a. Eq a => Eq [a]
Eq, Eq ModuleRenaming
Eq ModuleRenaming
-> (ModuleRenaming -> ModuleRenaming -> Ordering)
-> (ModuleRenaming -> ModuleRenaming -> Bool)
-> (ModuleRenaming -> ModuleRenaming -> Bool)
-> (ModuleRenaming -> ModuleRenaming -> Bool)
-> (ModuleRenaming -> ModuleRenaming -> Bool)
-> (ModuleRenaming -> ModuleRenaming -> ModuleRenaming)
-> (ModuleRenaming -> ModuleRenaming -> ModuleRenaming)
-> Ord ModuleRenaming
ModuleRenaming -> ModuleRenaming -> Bool
ModuleRenaming -> ModuleRenaming -> Ordering
ModuleRenaming -> ModuleRenaming -> ModuleRenaming
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 :: ModuleRenaming -> ModuleRenaming -> ModuleRenaming
$cmin :: ModuleRenaming -> ModuleRenaming -> ModuleRenaming
max :: ModuleRenaming -> ModuleRenaming -> ModuleRenaming
$cmax :: ModuleRenaming -> ModuleRenaming -> ModuleRenaming
>= :: ModuleRenaming -> ModuleRenaming -> Bool
$c>= :: ModuleRenaming -> ModuleRenaming -> Bool
> :: ModuleRenaming -> ModuleRenaming -> Bool
$c> :: ModuleRenaming -> ModuleRenaming -> Bool
<= :: ModuleRenaming -> ModuleRenaming -> Bool
$c<= :: ModuleRenaming -> ModuleRenaming -> Bool
< :: ModuleRenaming -> ModuleRenaming -> Bool
$c< :: ModuleRenaming -> ModuleRenaming -> Bool
compare :: ModuleRenaming -> ModuleRenaming -> Ordering
$ccompare :: ModuleRenaming -> ModuleRenaming -> Ordering
External instance of the constraint type forall a b. (Ord a, Ord b) => Ord (a, b)
External instance of the constraint type forall a b. (Ord a, Ord b) => Ord (a, b)
External instance of the constraint type Ord ModuleName
External instance of the constraint type forall a b. (Ord a, Ord b) => Ord (a, b)
External instance of the constraint type Ord ModuleName
External instance of the constraint type forall a. Ord a => Ord [a]
Instance of class: Eq of the constraint type Eq ModuleRenaming
External instance of the constraint type Ord ModuleName
Instance of class: Ord of the constraint type Ord ModuleRenaming
Instance of class: Eq of the constraint type Eq ModuleRenaming
Ord, Typeable, Typeable ModuleRenaming
DataType
Constr
Typeable ModuleRenaming
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ModuleRenaming -> c ModuleRenaming)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ModuleRenaming)
-> (ModuleRenaming -> Constr)
-> (ModuleRenaming -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ModuleRenaming))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ModuleRenaming))
-> ((forall b. Data b => b -> b)
-> ModuleRenaming -> ModuleRenaming)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ModuleRenaming -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ModuleRenaming -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ModuleRenaming -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ModuleRenaming -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ModuleRenaming -> m ModuleRenaming)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ModuleRenaming -> m ModuleRenaming)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ModuleRenaming -> m ModuleRenaming)
-> Data ModuleRenaming
ModuleRenaming -> DataType
ModuleRenaming -> Constr
(forall b. Data b => b -> b) -> ModuleRenaming -> ModuleRenaming
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ModuleRenaming -> c ModuleRenaming
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ModuleRenaming
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) -> ModuleRenaming -> u
forall u. (forall d. Data d => d -> u) -> ModuleRenaming -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ModuleRenaming -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ModuleRenaming -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ModuleRenaming -> m ModuleRenaming
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ModuleRenaming -> m ModuleRenaming
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ModuleRenaming
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ModuleRenaming -> c ModuleRenaming
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ModuleRenaming)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ModuleRenaming)
$cHidingRenaming :: Constr
$cDefaultRenaming :: Constr
$cModuleRenaming :: Constr
$tModuleRenaming :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> ModuleRenaming -> m ModuleRenaming
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ModuleRenaming -> m ModuleRenaming
gmapMp :: (forall d. Data d => d -> m d)
-> ModuleRenaming -> m ModuleRenaming
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ModuleRenaming -> m ModuleRenaming
gmapM :: (forall d. Data d => d -> m d)
-> ModuleRenaming -> m ModuleRenaming
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ModuleRenaming -> m ModuleRenaming
gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleRenaming -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ModuleRenaming -> u
gmapQ :: (forall d. Data d => d -> u) -> ModuleRenaming -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ModuleRenaming -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ModuleRenaming -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ModuleRenaming -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ModuleRenaming -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ModuleRenaming -> r
gmapT :: (forall b. Data b => b -> b) -> ModuleRenaming -> ModuleRenaming
$cgmapT :: (forall b. Data b => b -> b) -> ModuleRenaming -> ModuleRenaming
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ModuleRenaming)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ModuleRenaming)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ModuleRenaming)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ModuleRenaming)
dataTypeOf :: ModuleRenaming -> DataType
$cdataTypeOf :: ModuleRenaming -> DataType
toConstr :: ModuleRenaming -> Constr
$ctoConstr :: ModuleRenaming -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ModuleRenaming
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ModuleRenaming
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ModuleRenaming -> c ModuleRenaming
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ModuleRenaming -> c ModuleRenaming
External instance of the constraint type Data ModuleName
External instance of the constraint type Data ModuleName
External instance of the constraint type Data ModuleName
External instance of the constraint type forall a b. (Data a, Data b) => Data (a, b)
External instance of the constraint type Data ModuleName
External instance of the constraint type forall a b. (Data a, Data b) => Data (a, b)
External instance of the constraint type Data ModuleName
External instance of the constraint type Data ModuleName
External instance of the constraint type Data ModuleName
External instance of the constraint type forall a b. (Data a, Data b) => Data (a, b)
External instance of the constraint type Data ModuleName
External instance of the constraint type Data ModuleName
External instance of the constraint type forall a. Data a => Data [a]
Data, (forall x. ModuleRenaming -> Rep ModuleRenaming x)
-> (forall x. Rep ModuleRenaming x -> ModuleRenaming)
-> Generic ModuleRenaming
forall x. Rep ModuleRenaming x -> ModuleRenaming
forall x. ModuleRenaming -> Rep ModuleRenaming x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ModuleRenaming x -> ModuleRenaming
$cfrom :: forall x. ModuleRenaming -> Rep ModuleRenaming x
Generic)
interpModuleRenaming :: ModuleRenaming -> ModuleName -> Maybe ModuleName
interpModuleRenaming :: ModuleRenaming -> ModuleName -> Maybe ModuleName
interpModuleRenaming ModuleRenaming
DefaultRenaming = ModuleName -> Maybe ModuleName
forall a. a -> Maybe a
Just
interpModuleRenaming (ModuleRenaming [(ModuleName, ModuleName)]
rns) =
let m :: Map ModuleName ModuleName
m = [(ModuleName, ModuleName)] -> Map ModuleName ModuleName
forall k a. Ord k => [(k, a)] -> Map k a
External instance of the constraint type Ord ModuleName
Map.fromList [(ModuleName, ModuleName)]
rns
in \ModuleName
k -> ModuleName -> Map ModuleName ModuleName -> Maybe ModuleName
forall k a. Ord k => k -> Map k a -> Maybe a
External instance of the constraint type Ord ModuleName
Map.lookup ModuleName
k Map ModuleName ModuleName
m
interpModuleRenaming (HidingRenaming [ModuleName]
hs) =
let s :: Set ModuleName
s = [ModuleName] -> Set ModuleName
forall a. Ord a => [a] -> Set a
External instance of the constraint type Ord ModuleName
Set.fromList [ModuleName]
hs
in \ModuleName
k -> if ModuleName
k ModuleName -> Set ModuleName -> Bool
forall a. Ord a => a -> Set a -> Bool
External instance of the constraint type Ord ModuleName
`Set.member` Set ModuleName
s then Maybe ModuleName
forall a. Maybe a
Nothing else ModuleName -> Maybe ModuleName
forall a. a -> Maybe a
Just ModuleName
k
defaultRenaming :: ModuleRenaming
defaultRenaming :: ModuleRenaming
defaultRenaming = ModuleRenaming
DefaultRenaming
isDefaultRenaming :: ModuleRenaming -> Bool
isDefaultRenaming :: ModuleRenaming -> Bool
isDefaultRenaming ModuleRenaming
DefaultRenaming = Bool
True
isDefaultRenaming ModuleRenaming
_ = Bool
False
instance Binary ModuleRenaming where
instance Structured ModuleRenaming where
instance NFData ModuleRenaming where rnf :: ModuleRenaming -> ()
rnf = ModuleRenaming -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type forall a b. (NFData a, NFData b) => NFData (a, b)
External instance of the constraint type NFData ModuleName
External instance of the constraint type NFData ModuleName
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData ModuleName
Instance of class: Generic of the constraint type Generic ModuleRenaming
genericRnf
instance Pretty ModuleRenaming where
pretty :: ModuleRenaming -> Doc
pretty ModuleRenaming
DefaultRenaming = Doc
forall a. Monoid a => a
External instance of the constraint type Monoid Doc
mempty
pretty (HidingRenaming [ModuleName]
hides)
= String -> Doc
text String
"hiding" Doc -> Doc -> Doc
<+> Doc -> Doc
parens ([Doc] -> Doc
hsep (Doc -> [Doc] -> [Doc]
punctuate Doc
comma ((ModuleName -> Doc) -> [ModuleName] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ModuleName -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty ModuleName
pretty [ModuleName]
hides)))
pretty (ModuleRenaming [(ModuleName, ModuleName)]
rns)
= Doc -> Doc
parens (Doc -> Doc) -> ([Doc] -> Doc) -> [Doc] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Doc] -> Doc
hsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ Doc -> [Doc] -> [Doc]
punctuate Doc
comma (((ModuleName, ModuleName) -> Doc)
-> [(ModuleName, ModuleName)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (ModuleName, ModuleName) -> Doc
forall {a}. (Eq a, Pretty a) => (a, a) -> Doc
External instance of the constraint type Pretty ModuleName
External instance of the constraint type Eq ModuleName
dispEntry [(ModuleName, ModuleName)]
rns)
where dispEntry :: (a, a) -> Doc
dispEntry (a
orig, a
new)
| a
orig a -> a -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq a
== a
new = a -> Doc
forall a. Pretty a => a -> Doc
Evidence bound by a type signature of the constraint type Pretty a
pretty a
orig
| Bool
otherwise = a -> Doc
forall a. Pretty a => a -> Doc
Evidence bound by a type signature of the constraint type Pretty a
pretty a
orig Doc -> Doc -> Doc
<+> String -> Doc
text String
"as" Doc -> Doc -> Doc
<+> a -> Doc
forall a. Pretty a => a -> Doc
Evidence bound by a type signature of the constraint type Pretty a
pretty a
new
instance Parsec ModuleRenaming where
parsec :: m ModuleRenaming
parsec = do
CabalSpecVersion
csv <- m CabalSpecVersion
forall (m :: * -> *). CabalParsing m => m CabalSpecVersion
Evidence bound by a type signature of the constraint type CabalParsing m
askCabalSpecVersion
if CabalSpecVersion
csv CabalSpecVersion -> CabalSpecVersion -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord CabalSpecVersion
>= CabalSpecVersion
CabalSpecV3_0
then (forall a. m a -> m a) -> m ModuleName -> m ModuleRenaming
forall (m :: * -> *).
CabalParsing m =>
(forall a. m a -> m a) -> m ModuleName -> m ModuleRenaming
Evidence bound by a type signature of the constraint type CabalParsing m
moduleRenamingParsec forall a. m a -> m a
forall {m :: * -> *} {a}. (Monad m, CharParsing m) => m a -> m a
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadPlus m
Evidence bound by a type signature of the constraint type CabalParsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadPlus m
Evidence bound by a type signature of the constraint type CabalParsing m
parensLax m ModuleName
forall (m :: * -> *) a. (CabalParsing m, Parsec a) => m a
External instance of the constraint type Parsec ModuleName
Evidence bound by a type signature of the constraint type CabalParsing m
lexemeParsec
else (forall a. m a -> m a) -> m ModuleName -> m ModuleRenaming
forall (m :: * -> *).
CabalParsing m =>
(forall a. m a -> m a) -> m ModuleName -> m ModuleRenaming
Evidence bound by a type signature of the constraint type CabalParsing m
moduleRenamingParsec forall a. m a -> m a
parensStrict m ModuleName
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
Evidence bound by a type signature of the constraint type CabalParsing m
External instance of the constraint type Parsec ModuleName
parsec
where
parensLax :: m a -> m a
parensLax m a
p = m () -> m () -> m a -> m a
forall (m :: * -> *) bra ket a.
Applicative m =>
m bra -> m ket -> m a -> m a
External instance of the constraint type forall (m :: * -> *). Monad m => Applicative m
Evidence bound by a type signature of the constraint type Monad m
P.between (Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
Evidence bound by a type signature of the constraint type CharParsing m
P.char Char
'(' m Char -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
Evidence bound by a type signature of the constraint type Monad m
>> m ()
forall (m :: * -> *). CharParsing m => m ()
Evidence bound by a type signature of the constraint type CharParsing m
P.spaces) (Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
Evidence bound by a type signature of the constraint type CharParsing m
P.char Char
')' m Char -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
Evidence bound by a type signature of the constraint type Monad m
>> m ()
forall (m :: * -> *). CharParsing m => m ()
Evidence bound by a type signature of the constraint type CharParsing m
P.spaces) m a
p
parensStrict :: m a -> m a
parensStrict m a
p = m (Maybe Any) -> m Char -> m a -> m a
forall (m :: * -> *) bra ket a.
Applicative m =>
m bra -> m ket -> m a -> m a
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.between (Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.char Char
'(' m Char -> m (Maybe Any) -> m (Maybe Any)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadPlus m
Evidence bound by a type signature of the constraint type CabalParsing m
>> m (Maybe Any)
forall {a}. m (Maybe a)
warnSpaces) (Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.char Char
')') m a
p
warnSpaces :: m (Maybe a)
warnSpaces = m a -> m (Maybe a)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.optional (m a -> m (Maybe a)) -> m a -> m (Maybe a)
forall a b. (a -> b) -> a -> b
$
m Char
forall (m :: * -> *). CharParsing m => m Char
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.space m Char -> m a -> m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
*> String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadFail m
Evidence bound by a type signature of the constraint type CabalParsing m
fail String
"space after parenthesis, use cabal-version: 3.0 or higher"
moduleRenamingParsec
:: CabalParsing m
=> (forall a. m a -> m a)
-> m ModuleName
-> m ModuleRenaming
moduleRenamingParsec :: (forall a. m a -> m a) -> m ModuleName -> m ModuleRenaming
moduleRenamingParsec forall a. m a -> m a
bp m ModuleName
mn =
[m ModuleRenaming] -> m ModuleRenaming
forall (m :: * -> *) a. Alternative m => [m a] -> m a
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.choice [ m ModuleRenaming
parseRename, m ModuleRenaming
parseHiding, ModuleRenaming -> m ModuleRenaming
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadPlus m
Evidence bound by a type signature of the constraint type CabalParsing m
return ModuleRenaming
DefaultRenaming ]
where
cma :: m ()
cma = Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.char Char
',' m Char -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadPlus m
Evidence bound by a type signature of the constraint type CabalParsing m
>> m ()
forall (m :: * -> *). CharParsing m => m ()
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.spaces
parseRename :: m ModuleRenaming
parseRename = do
[(ModuleName, ModuleName)]
rns <- m [(ModuleName, ModuleName)] -> m [(ModuleName, ModuleName)]
forall a. m a -> m a
bp m [(ModuleName, ModuleName)]
parseList
m ()
forall (m :: * -> *). CharParsing m => m ()
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.spaces
ModuleRenaming -> m ModuleRenaming
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadPlus m
Evidence bound by a type signature of the constraint type CabalParsing m
return ([(ModuleName, ModuleName)] -> ModuleRenaming
ModuleRenaming [(ModuleName, ModuleName)]
rns)
parseHiding :: m ModuleRenaming
parseHiding = do
String
_ <- String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.string String
"hiding"
m ()
forall (m :: * -> *). CharParsing m => m ()
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.spaces
[ModuleName]
hides <- m [ModuleName] -> m [ModuleName]
forall a. m a -> m a
bp (m ModuleName -> m () -> m [ModuleName]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.sepBy m ModuleName
mn m ()
cma)
ModuleRenaming -> m ModuleRenaming
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadPlus m
Evidence bound by a type signature of the constraint type CabalParsing m
return ([ModuleName] -> ModuleRenaming
HidingRenaming [ModuleName]
hides)
parseList :: m [(ModuleName, ModuleName)]
parseList =
m (ModuleName, ModuleName) -> m () -> m [(ModuleName, ModuleName)]
forall (m :: * -> *) a sep. Alternative m => m a -> m sep -> m [a]
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.sepBy m (ModuleName, ModuleName)
parseEntry m ()
cma
parseEntry :: m (ModuleName, ModuleName)
parseEntry = do
ModuleName
orig <- m ModuleName
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
Evidence bound by a type signature of the constraint type CabalParsing m
External instance of the constraint type Parsec ModuleName
parsec
m ()
forall (m :: * -> *). CharParsing m => m ()
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.spaces
(ModuleName, ModuleName)
-> m (ModuleName, ModuleName) -> m (ModuleName, ModuleName)
forall (m :: * -> *) a. Alternative m => a -> m a -> m a
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.option (ModuleName
orig, ModuleName
orig) (m (ModuleName, ModuleName) -> m (ModuleName, ModuleName))
-> m (ModuleName, ModuleName) -> m (ModuleName, ModuleName)
forall a b. (a -> b) -> a -> b
$ do
String
_ <- String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.string String
"as"
m ()
forall (m :: * -> *). CharParsing m => m ()
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.skipSpaces1
ModuleName
new <- m ModuleName
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
Evidence bound by a type signature of the constraint type CabalParsing m
External instance of the constraint type Parsec ModuleName
parsec
m ()
forall (m :: * -> *). CharParsing m => m ()
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.spaces
(ModuleName, ModuleName) -> m (ModuleName, ModuleName)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadPlus m
Evidence bound by a type signature of the constraint type CabalParsing m
return (ModuleName
orig, ModuleName
new)