module Proteome.Data.GrepOutputLine where import Path (Abs, File, Path) import Ribosome (MsgpackEncode) data GrepOutputLine = GrepOutputLine { GrepOutputLine -> Path Abs File path :: Path Abs File, GrepOutputLine -> Int line :: Int, GrepOutputLine -> Maybe Int col :: Maybe Int, GrepOutputLine -> Text content :: Text } deriving stock (GrepOutputLine -> GrepOutputLine -> Bool (GrepOutputLine -> GrepOutputLine -> Bool) -> (GrepOutputLine -> GrepOutputLine -> Bool) -> Eq GrepOutputLine forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: GrepOutputLine -> GrepOutputLine -> Bool $c/= :: GrepOutputLine -> GrepOutputLine -> Bool == :: GrepOutputLine -> GrepOutputLine -> Bool $c== :: GrepOutputLine -> GrepOutputLine -> Bool Eq, Int -> GrepOutputLine -> ShowS [GrepOutputLine] -> ShowS GrepOutputLine -> String (Int -> GrepOutputLine -> ShowS) -> (GrepOutputLine -> String) -> ([GrepOutputLine] -> ShowS) -> Show GrepOutputLine forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [GrepOutputLine] -> ShowS $cshowList :: [GrepOutputLine] -> ShowS show :: GrepOutputLine -> String $cshow :: GrepOutputLine -> String showsPrec :: Int -> GrepOutputLine -> ShowS $cshowsPrec :: Int -> GrepOutputLine -> ShowS Show, (forall x. GrepOutputLine -> Rep GrepOutputLine x) -> (forall x. Rep GrepOutputLine x -> GrepOutputLine) -> Generic GrepOutputLine forall x. Rep GrepOutputLine x -> GrepOutputLine forall x. GrepOutputLine -> Rep GrepOutputLine x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep GrepOutputLine x -> GrepOutputLine $cfrom :: forall x. GrepOutputLine -> Rep GrepOutputLine x Generic) deriving anyclass (GrepOutputLine -> Object (GrepOutputLine -> Object) -> MsgpackEncode GrepOutputLine forall a. (a -> Object) -> MsgpackEncode a toMsgpack :: GrepOutputLine -> Object $ctoMsgpack :: GrepOutputLine -> Object MsgpackEncode) sameLine :: GrepOutputLine -> GrepOutputLine -> Bool sameLine :: GrepOutputLine -> GrepOutputLine -> Bool sameLine (GrepOutputLine Path Abs File p1 Int l1 Maybe Int _ Text _) (GrepOutputLine Path Abs File p2 Int l2 Maybe Int _ Text _) = Path Abs File p1 Path Abs File -> Path Abs File -> Bool forall a. Eq a => a -> a -> Bool == Path Abs File p2 Bool -> Bool -> Bool && Int l1 Int -> Int -> Bool forall a. Eq a => a -> a -> Bool == Int l2