{-# LANGUAGE NoImplicitPrelude #-}
module Stack.Types.ExtraDirs
( ExtraDirs (..)
) where
import Generics.Deriving.Monoid ( mappenddefault, memptydefault )
import Stack.Prelude
data =
{ ExtraDirs -> [Path Abs Dir]
edBins :: ![Path Abs Dir]
, ExtraDirs -> [Path Abs Dir]
edInclude :: ![Path Abs Dir]
, ExtraDirs -> [Path Abs Dir]
edLib :: ![Path Abs Dir]
}
deriving (Int -> ExtraDirs -> ShowS
[ExtraDirs] -> ShowS
ExtraDirs -> String
(Int -> ExtraDirs -> ShowS)
-> (ExtraDirs -> String)
-> ([ExtraDirs] -> ShowS)
-> Show ExtraDirs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExtraDirs -> ShowS
showsPrec :: Int -> ExtraDirs -> ShowS
$cshow :: ExtraDirs -> String
show :: ExtraDirs -> String
$cshowList :: [ExtraDirs] -> ShowS
showList :: [ExtraDirs] -> ShowS
Show, (forall x. ExtraDirs -> Rep ExtraDirs x)
-> (forall x. Rep ExtraDirs x -> ExtraDirs) -> Generic ExtraDirs
forall x. Rep ExtraDirs x -> ExtraDirs
forall x. ExtraDirs -> Rep ExtraDirs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExtraDirs -> Rep ExtraDirs x
from :: forall x. ExtraDirs -> Rep ExtraDirs x
$cto :: forall x. Rep ExtraDirs x -> ExtraDirs
to :: forall x. Rep ExtraDirs x -> ExtraDirs
Generic)
instance Semigroup ExtraDirs where
<> :: ExtraDirs -> ExtraDirs -> ExtraDirs
(<>) = ExtraDirs -> ExtraDirs -> ExtraDirs
forall a. (Generic a, Monoid' (Rep a)) => a -> a -> a
mappenddefault
instance Monoid ExtraDirs where
mempty :: ExtraDirs
mempty = ExtraDirs
forall a. (Generic a, Monoid' (Rep a)) => a
memptydefault
mappend :: ExtraDirs -> ExtraDirs -> ExtraDirs
mappend = ExtraDirs -> ExtraDirs -> ExtraDirs
forall a. Semigroup a => a -> a -> a
(<>)