{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} module Zuul.SourceContext (SourceContext (..)) where import Data.Aeson (FromJSON (..), ToJSON (..), Value (String)) import Data.Aeson.Types (prependFailure, typeMismatch) import Data.Text (Text) import GHC.Generics (Generic) import Zuul.Aeson (zuulParseJSON, zuulToJSON) data SourceContext = SourceContext { SourceContext -> Text scBranch :: Text, SourceContext -> Text scPath :: Text, SourceContext -> Text scProject :: Text } deriving (Int -> SourceContext -> ShowS [SourceContext] -> ShowS SourceContext -> String (Int -> SourceContext -> ShowS) -> (SourceContext -> String) -> ([SourceContext] -> ShowS) -> Show SourceContext forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [SourceContext] -> ShowS $cshowList :: [SourceContext] -> ShowS show :: SourceContext -> String $cshow :: SourceContext -> String showsPrec :: Int -> SourceContext -> ShowS $cshowsPrec :: Int -> SourceContext -> ShowS Show, SourceContext -> SourceContext -> Bool (SourceContext -> SourceContext -> Bool) -> (SourceContext -> SourceContext -> Bool) -> Eq SourceContext forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: SourceContext -> SourceContext -> Bool $c/= :: SourceContext -> SourceContext -> Bool == :: SourceContext -> SourceContext -> Bool $c== :: SourceContext -> SourceContext -> Bool Eq, Eq SourceContext Eq SourceContext -> (SourceContext -> SourceContext -> Ordering) -> (SourceContext -> SourceContext -> Bool) -> (SourceContext -> SourceContext -> Bool) -> (SourceContext -> SourceContext -> Bool) -> (SourceContext -> SourceContext -> Bool) -> (SourceContext -> SourceContext -> SourceContext) -> (SourceContext -> SourceContext -> SourceContext) -> Ord SourceContext SourceContext -> SourceContext -> Bool SourceContext -> SourceContext -> Ordering SourceContext -> SourceContext -> SourceContext 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 :: SourceContext -> SourceContext -> SourceContext $cmin :: SourceContext -> SourceContext -> SourceContext max :: SourceContext -> SourceContext -> SourceContext $cmax :: SourceContext -> SourceContext -> SourceContext >= :: SourceContext -> SourceContext -> Bool $c>= :: SourceContext -> SourceContext -> Bool > :: SourceContext -> SourceContext -> Bool $c> :: SourceContext -> SourceContext -> Bool <= :: SourceContext -> SourceContext -> Bool $c<= :: SourceContext -> SourceContext -> Bool < :: SourceContext -> SourceContext -> Bool $c< :: SourceContext -> SourceContext -> Bool compare :: SourceContext -> SourceContext -> Ordering $ccompare :: SourceContext -> SourceContext -> Ordering $cp1Ord :: Eq SourceContext Ord, (forall x. SourceContext -> Rep SourceContext x) -> (forall x. Rep SourceContext x -> SourceContext) -> Generic SourceContext forall x. Rep SourceContext x -> SourceContext forall x. SourceContext -> Rep SourceContext x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep SourceContext x -> SourceContext $cfrom :: forall x. SourceContext -> Rep SourceContext x Generic) instance ToJSON SourceContext where toJSON :: SourceContext -> Value toJSON = Text -> SourceContext -> Value forall a. (Generic a, GToJSON' Value Zero (Rep a)) => Text -> a -> Value zuulToJSON Text "sc" instance FromJSON SourceContext where parseJSON :: Value -> Parser SourceContext parseJSON = Text -> Value -> Parser SourceContext forall a. (Generic a, GFromJSON Zero (Rep a)) => Text -> Value -> Parser a zuulParseJSON Text "sc"