module CabalGild.Unstable.Type.Dependency where

import qualified CabalGild.Unstable.Type.VersionRange as VersionRange
import qualified Data.Ord as Ord
import qualified Distribution.Parsec as Parsec
import qualified Distribution.Pretty as Pretty
import qualified Distribution.Types.Dependency as Dependency

-- | This type exists to provide an 'Ord' instance for
-- 'Dependency.Dependency', which was added in @Cabal-syntax-3.10.1.0@.
newtype Dependency = Dependency
  { Dependency -> Dependency
unwrap :: Dependency.Dependency
  }
  deriving (Dependency -> Dependency -> Bool
(Dependency -> Dependency -> Bool)
-> (Dependency -> Dependency -> Bool) -> Eq Dependency
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Dependency -> Dependency -> Bool
== :: Dependency -> Dependency -> Bool
$c/= :: Dependency -> Dependency -> Bool
/= :: Dependency -> Dependency -> Bool
Eq, Int -> Dependency -> ShowS
[Dependency] -> ShowS
Dependency -> String
(Int -> Dependency -> ShowS)
-> (Dependency -> String)
-> ([Dependency] -> ShowS)
-> Show Dependency
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Dependency -> ShowS
showsPrec :: Int -> Dependency -> ShowS
$cshow :: Dependency -> String
show :: Dependency -> String
$cshowList :: [Dependency] -> ShowS
showList :: [Dependency] -> ShowS
Show)

instance Ord Dependency where
  compare :: Dependency -> Dependency -> Ordering
compare =
    (Dependency
 -> (PackageName, VersionRange Version, NonEmptySet LibraryName))
-> Dependency -> Dependency -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
Ord.comparing ((Dependency
  -> (PackageName, VersionRange Version, NonEmptySet LibraryName))
 -> Dependency -> Dependency -> Ordering)
-> (Dependency
    -> (PackageName, VersionRange Version, NonEmptySet LibraryName))
-> Dependency
-> Dependency
-> Ordering
forall a b. (a -> b) -> a -> b
$
      (\(Dependency.Dependency PackageName
pn VersionRange
vr NonEmptySet LibraryName
lns) -> (PackageName
pn, VersionRange -> VersionRange Version
VersionRange.fromVersionRange VersionRange
vr, NonEmptySet LibraryName
lns))
        (Dependency
 -> (PackageName, VersionRange Version, NonEmptySet LibraryName))
-> (Dependency -> Dependency)
-> Dependency
-> (PackageName, VersionRange Version, NonEmptySet LibraryName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dependency -> Dependency
unwrap

instance Parsec.Parsec Dependency where
  parsec :: forall (m :: * -> *). CabalParsing m => m Dependency
parsec = Dependency -> Dependency
Dependency (Dependency -> Dependency) -> m Dependency -> m Dependency
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m Dependency
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
forall (m :: * -> *). CabalParsing m => m Dependency
Parsec.parsec

instance Pretty.Pretty Dependency where
  pretty :: Dependency -> Doc
pretty = Dependency -> Doc
forall a. Pretty a => a -> Doc
Pretty.pretty (Dependency -> Doc)
-> (Dependency -> Dependency) -> Dependency -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dependency -> Dependency
unwrap