{-# LANGUAGE CPP #-}
module Portage.Dependency.Print
(
dep2str
, dep2str_noindent
) where
import Portage.Version
import Portage.Use
import Portage.PackageId
import qualified Distribution.Pretty as DP (Pretty(..))
import qualified Text.PrettyPrint as Disp
import Text.PrettyPrint ( vcat, nest, render )
import Text.PrettyPrint as PP ((<>))
import Portage.Dependency.Types
dispSlot :: SlotDepend -> Disp.Doc
dispSlot :: SlotDepend -> Doc
dispSlot SlotDepend
AnySlot = Doc
Disp.empty
dispSlot SlotDepend
AnyBuildTimeSlot = String -> Doc
Disp.text String
":="
dispSlot (GivenSlot String
slot) = String -> Doc
Disp.text (Char
':' Char -> String -> String
forall a. a -> [a] -> [a]
: String
slot)
dispLBound :: PackageName -> LBound -> Disp.Doc
dispLBound :: PackageName -> LBound -> Doc
dispLBound PackageName
pn (StrictLB Version
v) = Char -> Doc
Disp.char Char
'>' Doc -> Doc -> Doc
PP.<> PackageName -> Doc
forall a. Pretty a => a -> Doc
DP.pretty PackageName
pn Doc -> Doc -> Doc
<-> Version -> Doc
forall a. Pretty a => a -> Doc
DP.pretty Version
v
dispLBound PackageName
pn (NonstrictLB Version
v) = String -> Doc
Disp.text String
">=" Doc -> Doc -> Doc
PP.<> PackageName -> Doc
forall a. Pretty a => a -> Doc
DP.pretty PackageName
pn Doc -> Doc -> Doc
<-> Version -> Doc
forall a. Pretty a => a -> Doc
DP.pretty Version
v
dispLBound PackageName
_pn LBound
ZeroB = String -> Doc
forall a. HasCallStack => String -> a
error String
"unhandled 'dispLBound ZeroB'"
dispUBound :: PackageName -> UBound -> Disp.Doc
dispUBound :: PackageName -> UBound -> Doc
dispUBound PackageName
pn (StrictUB Version
v) = Char -> Doc
Disp.char Char
'<' Doc -> Doc -> Doc
PP.<> PackageName -> Doc
forall a. Pretty a => a -> Doc
DP.pretty PackageName
pn Doc -> Doc -> Doc
<-> Version -> Doc
forall a. Pretty a => a -> Doc
DP.pretty Version
v
dispUBound PackageName
pn (NonstrictUB Version
v) = String -> Doc
Disp.text String
"<=" Doc -> Doc -> Doc
PP.<> PackageName -> Doc
forall a. Pretty a => a -> Doc
DP.pretty PackageName
pn Doc -> Doc -> Doc
<-> Version -> Doc
forall a. Pretty a => a -> Doc
DP.pretty Version
v
dispUBound PackageName
_pn UBound
InfinityB = String -> Doc
forall a. HasCallStack => String -> a
error String
"unhandled 'dispUBound Infinity'"
dispDAttr :: DAttr -> Disp.Doc
dispDAttr :: DAttr -> Doc
dispDAttr (DAttr SlotDepend
s [UseFlag]
u) = SlotDepend -> Doc
dispSlot SlotDepend
s Doc -> Doc -> Doc
PP.<> [UseFlag] -> Doc
dispUses [UseFlag]
u
dep2str :: Int -> Dependency -> String
dep2str :: Int -> Dependency -> String
dep2str Int
start_indent = Doc -> String
render (Doc -> String) -> (Dependency -> Doc) -> Dependency -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Doc -> Doc
nest Int
start_indent (Doc -> Doc) -> (Dependency -> Doc) -> Dependency -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dependency -> Doc
showDepend
dep2str_noindent :: Dependency -> String
dep2str_noindent :: Dependency -> String
dep2str_noindent = Doc -> String
render (Doc -> String) -> (Dependency -> Doc) -> Dependency -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dependency -> Doc
showDepend
(<->) :: Disp.Doc -> Disp.Doc -> Disp.Doc
Doc
a <-> :: Doc -> Doc -> Doc
<-> Doc
b = Doc
a Doc -> Doc -> Doc
PP.<> Char -> Doc
Disp.char Char
'-' Doc -> Doc -> Doc
PP.<> Doc
b
sp :: Disp.Doc
sp :: Doc
sp = Char -> Doc
Disp.char Char
' '
sparens :: Disp.Doc -> Disp.Doc
sparens :: Doc -> Doc
sparens Doc
doc = Doc -> Doc
Disp.parens (Doc
sp Doc -> Doc -> Doc
PP.<> Doc -> Doc
valign Doc
doc Doc -> Doc -> Doc
PP.<> Doc
sp)
valign :: Disp.Doc -> Disp.Doc
valign :: Doc -> Doc
valign Doc
d = Int -> Doc -> Doc
nest Int
0 Doc
d
showDepend :: Dependency -> Disp.Doc
showDepend :: Dependency -> Doc
showDepend (DependAtom (Atom PackageName
pn DRange
range DAttr
dattr))
= case DRange
range of
DRange LBound
ZeroB UBound
InfinityB -> PackageName -> Doc
forall a. Pretty a => a -> Doc
DP.pretty PackageName
pn Doc -> Doc -> Doc
PP.<> DAttr -> Doc
dispDAttr DAttr
dattr
DRange LBound
ZeroB UBound
ub -> PackageName -> UBound -> Doc
dispUBound PackageName
pn UBound
ub Doc -> Doc -> Doc
PP.<> DAttr -> Doc
dispDAttr DAttr
dattr
DRange LBound
lb UBound
InfinityB -> PackageName -> LBound -> Doc
dispLBound PackageName
pn LBound
lb Doc -> Doc -> Doc
PP.<> DAttr -> Doc
dispDAttr DAttr
dattr
DRange LBound
lb UBound
ub -> Dependency -> Doc
showDepend (Atom -> Dependency
DependAtom (PackageName -> DRange -> DAttr -> Atom
Atom PackageName
pn (LBound -> UBound -> DRange
DRange LBound
lb UBound
InfinityB) DAttr
dattr))
Doc -> Doc -> Doc
PP.<> Char -> Doc
Disp.char Char
' '
Doc -> Doc -> Doc
PP.<> Dependency -> Doc
showDepend (Atom -> Dependency
DependAtom (PackageName -> DRange -> DAttr -> Atom
Atom PackageName
pn (LBound -> UBound -> DRange
DRange LBound
ZeroB UBound
ub) DAttr
dattr))
DExact Version
v -> Char -> Doc
Disp.char Char
'~' Doc -> Doc -> Doc
PP.<> PackageName -> Doc
forall a. Pretty a => a -> Doc
DP.pretty PackageName
pn Doc -> Doc -> Doc
<-> Version -> Doc
forall a. Pretty a => a -> Doc
DP.pretty Version
v { versionRevision :: Int
versionRevision = Int
0 } Doc -> Doc -> Doc
PP.<> DAttr -> Doc
dispDAttr DAttr
dattr
showDepend (DependIfUse Use
u Dependency
td Dependency
fd) = Doc -> Doc
valign (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vcat [Doc
td_doc, Doc
fd_doc]
where td_doc :: Doc
td_doc
| Dependency -> Bool
is_empty_dependency Dependency
td = Doc
Disp.empty
| Bool
otherwise = Use -> Doc
forall a. Pretty a => a -> Doc
DP.pretty Use
u Doc -> Doc -> Doc
PP.<> Char -> Doc
Disp.char Char
'?' Doc -> Doc -> Doc
PP.<> Doc
sp Doc -> Doc -> Doc
PP.<> Doc -> Doc
sparens (Dependency -> Doc
showDepend Dependency
td)
fd_doc :: Doc
fd_doc
| Dependency -> Bool
is_empty_dependency Dependency
fd = Doc
Disp.empty
| Bool
otherwise = Char -> Doc
Disp.char Char
'!' Doc -> Doc -> Doc
PP.<> Use -> Doc
forall a. Pretty a => a -> Doc
DP.pretty Use
u Doc -> Doc -> Doc
PP.<> Char -> Doc
Disp.char Char
'?' Doc -> Doc -> Doc
PP.<> Doc
sp Doc -> Doc -> Doc
PP.<> Doc -> Doc
sparens (Dependency -> Doc
showDepend Dependency
fd)
showDepend (DependAnyOf [Dependency]
deps) = String -> Doc
Disp.text String
"||" Doc -> Doc -> Doc
PP.<> Doc
sp Doc -> Doc -> Doc
PP.<> Doc -> Doc
sparens ([Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (Dependency -> Doc) -> [Dependency] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Dependency -> Doc
showDependInAnyOf [Dependency]
deps)
showDepend (DependAllOf [Dependency]
deps) = Doc -> Doc
valign (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (Dependency -> Doc) -> [Dependency] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Dependency -> Doc
showDepend [Dependency]
deps
showDependInAnyOf :: Dependency -> Disp.Doc
showDependInAnyOf :: Dependency -> Doc
showDependInAnyOf d :: Dependency
d@(DependAllOf [Dependency]
_deps) = Doc -> Doc
sparens (Dependency -> Doc
showDepend Dependency
d)
showDependInAnyOf d :: Dependency
d@(DependAtom (Atom PackageName
_pn (DRange LBound
lb UBound
ub) DAttr
_dattr))
| LBound
lb LBound -> LBound -> Bool
forall a. Eq a => a -> a -> Bool
/= LBound
ZeroB Bool -> Bool -> Bool
&& UBound
ub UBound -> UBound -> Bool
forall a. Eq a => a -> a -> Bool
/= UBound
InfinityB
= Doc -> Doc
sparens (Dependency -> Doc
showDepend Dependency
d)
showDependInAnyOf Dependency
d = Dependency -> Doc
showDepend Dependency
d