module Proteome.Data.CurrentTag where import qualified Data.List.NonEmpty.Zipper as Zipper import Data.List.NonEmpty.Zipper (Zipper) import Path (Abs, File, Path) import Proteome.Tags.State (TagLoc) data CurrentTag = CurrentTag { CurrentTag -> Text name :: Text, CurrentTag -> Zipper (TagLoc (Path Abs File)) locations :: Zipper (TagLoc (Path Abs File)) } deriving stock (CurrentTag -> CurrentTag -> Bool (CurrentTag -> CurrentTag -> Bool) -> (CurrentTag -> CurrentTag -> Bool) -> Eq CurrentTag forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: CurrentTag -> CurrentTag -> Bool $c/= :: CurrentTag -> CurrentTag -> Bool == :: CurrentTag -> CurrentTag -> Bool $c== :: CurrentTag -> CurrentTag -> Bool Eq, Int -> CurrentTag -> ShowS [CurrentTag] -> ShowS CurrentTag -> String (Int -> CurrentTag -> ShowS) -> (CurrentTag -> String) -> ([CurrentTag] -> ShowS) -> Show CurrentTag forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [CurrentTag] -> ShowS $cshowList :: [CurrentTag] -> ShowS show :: CurrentTag -> String $cshow :: CurrentTag -> String showsPrec :: Int -> CurrentTag -> ShowS $cshowsPrec :: Int -> CurrentTag -> ShowS Show, (forall x. CurrentTag -> Rep CurrentTag x) -> (forall x. Rep CurrentTag x -> CurrentTag) -> Generic CurrentTag forall x. Rep CurrentTag x -> CurrentTag forall x. CurrentTag -> Rep CurrentTag x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep CurrentTag x -> CurrentTag $cfrom :: forall x. CurrentTag -> Rep CurrentTag x Generic) pattern CurrentLoc :: TagLoc (Path Abs File) -> CurrentTag pattern $mCurrentLoc :: forall {r}. CurrentTag -> (TagLoc (Path Abs File) -> r) -> (Void# -> r) -> r CurrentLoc loc <- (Zipper.current . locations -> loc) {-# complete CurrentLoc #-} cycleLoc :: Zipper (TagLoc (Path Abs File)) -> Zipper (TagLoc (Path Abs File)) cycleLoc :: Zipper (TagLoc (Path Abs File)) -> Zipper (TagLoc (Path Abs File)) cycleLoc Zipper (TagLoc (Path Abs File)) locs = Zipper (TagLoc (Path Abs File)) -> Maybe (Zipper (TagLoc (Path Abs File))) -> Zipper (TagLoc (Path Abs File)) forall a. a -> Maybe a -> a fromMaybe (Zipper (TagLoc (Path Abs File)) -> Zipper (TagLoc (Path Abs File)) forall a. Zipper a -> Zipper a Zipper.start Zipper (TagLoc (Path Abs File)) locs) (Zipper (TagLoc (Path Abs File)) -> Maybe (Zipper (TagLoc (Path Abs File))) forall a. Zipper a -> Maybe (Zipper a) Zipper.right Zipper (TagLoc (Path Abs File)) locs)