{-# LANGUAGE NoImplicitPrelude #-}
module Stack.Types.Dependency
( DepValue (..)
, DepType (..)
) where
import Distribution.Types.VersionRange ( VersionRange )
import Stack.Prelude
import Stack.Types.Version ( intersectVersionRanges )
data DepValue = DepValue
{ DepValue -> VersionRange
dvVersionRange :: !VersionRange
, DepValue -> DepType
dvType :: !DepType
}
deriving (Int -> DepValue -> ShowS
[DepValue] -> ShowS
DepValue -> String
(Int -> DepValue -> ShowS)
-> (DepValue -> String) -> ([DepValue] -> ShowS) -> Show DepValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DepValue -> ShowS
showsPrec :: Int -> DepValue -> ShowS
$cshow :: DepValue -> String
show :: DepValue -> String
$cshowList :: [DepValue] -> ShowS
showList :: [DepValue] -> ShowS
Show, Typeable)
instance Semigroup DepValue where
DepValue VersionRange
a DepType
x <> :: DepValue -> DepValue -> DepValue
<> DepValue VersionRange
b DepType
y = VersionRange -> DepType -> DepValue
DepValue (VersionRange -> VersionRange -> VersionRange
intersectVersionRanges VersionRange
a VersionRange
b) (DepType
x DepType -> DepType -> DepType
forall a. Semigroup a => a -> a -> a
<> DepType
y)
data DepType
= AsLibrary
| AsBuildTool
deriving (DepType -> DepType -> Bool
(DepType -> DepType -> Bool)
-> (DepType -> DepType -> Bool) -> Eq DepType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DepType -> DepType -> Bool
== :: DepType -> DepType -> Bool
$c/= :: DepType -> DepType -> Bool
/= :: DepType -> DepType -> Bool
Eq, Int -> DepType -> ShowS
[DepType] -> ShowS
DepType -> String
(Int -> DepType -> ShowS)
-> (DepType -> String) -> ([DepType] -> ShowS) -> Show DepType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DepType -> ShowS
showsPrec :: Int -> DepType -> ShowS
$cshow :: DepType -> String
show :: DepType -> String
$cshowList :: [DepType] -> ShowS
showList :: [DepType] -> ShowS
Show)
instance Semigroup DepType where
DepType
AsLibrary <> :: DepType -> DepType -> DepType
<> DepType
_ = DepType
AsLibrary
DepType
AsBuildTool <> DepType
x = DepType
x