module Yi.Search (
setRegexE,
resetRegexE,
getRegexE,
SearchMatch,
SearchResult(..),
SearchOption(..),
doSearch,
searchInit,
continueSearch,
makeSimpleSearch,
searchReplaceRegionB,
searchReplaceSelectionB,
replaceString,
searchAndRepRegion,
searchAndRepRegion0,
searchAndRepUnit,
isearchInitE,
isearchIsEmpty,
isearchAddE,
isearchPrevE,
isearchNextE,
isearchWordE,
isearchHistory,
isearchDelE,
isearchCancelE,
isearchFinishE,
isearchCancelWithE,
isearchFinishWithE,
qrNext,
qrReplaceAll,
qrReplaceOne,
qrFinish,
) where
import Control.Applicative
import Control.Monad
import Control.Lens hiding (re, from, to)
import Data.Char
import Data.Maybe
import Data.Default
import Data.Typeable
import Data.Binary
import Yi.Regex
import Yi.Window
import Yi.Core
import Yi.History
import Yi.Utils
setRegexE :: SearchExp -> EditorM ()
setRegexE re = assign currentRegexA (Just re)
resetRegexE :: EditorM ()
resetRegexE = assign currentRegexA Nothing
getRegexE :: EditorM (Maybe SearchExp)
getRegexE = use currentRegexA
type SearchMatch = Region
data SearchResult = PatternFound
| PatternNotFound
| SearchWrapped
deriving Eq
doSearch :: Maybe String
-> [SearchOption]
-> Direction
-> EditorM SearchResult
doSearch (Just re) fs d = searchInit re d fs >>= withBuffer0 . continueSearch
doSearch Nothing _ d = do
mre <- getRegexE
case mre of
Nothing -> fail "No previous search pattern"
Just r -> withBuffer0 (continueSearch (r,d))
searchInit :: String -> Direction -> [SearchOption] -> EditorM (SearchExp, Direction)
searchInit re d fs = do
let Right c_re = makeSearchOptsM fs re
setRegexE c_re
assign searchDirectionA d
return (c_re,d)
continueSearch :: (SearchExp, Direction) -> BufferM SearchResult
continueSearch (c_re, dir) = do
mp <- savingPointB $ do
moveB Character dir
rs <- regexB dir c_re
moveB Document (reverseDir dir)
ls <- regexB dir c_re
return $ listToMaybe $ fmap Right rs ++ fmap Left ls
maybe (return ()) (moveTo . regionStart . either id id) mp
return $ f mp
where
f (Just (Right _)) = PatternFound
f (Just (Left _)) = SearchWrapped
f Nothing = PatternNotFound
searchReplaceRegionB ::
String
-> String
-> Region
-> BufferM Int
searchReplaceRegionB from to = searchAndRepRegion0 (makeSimpleSearch from) to True
searchReplaceSelectionB ::
String
-> String
-> BufferM Int
searchReplaceSelectionB from to = searchReplaceRegionB from to =<< getSelectRegionB
replaceString :: String -> String -> BufferM Int
replaceString a b = searchReplaceRegionB a b =<< regionOfB Document
searchAndRepRegion0 :: SearchExp -> String -> Bool -> Region -> BufferM Int
searchAndRepRegion0 c_re str globally region = do
mp <- (if globally then id else take 1) <$> regexRegionB c_re region
let mp' = mayReverse (reverseDir $ regionDirection region) mp
mapM_ (`replaceRegionB` str) mp'
return (length mp)
searchAndRepRegion :: String -> String -> Bool -> Region -> EditorM Bool
searchAndRepRegion [] _ _ _ = return False
searchAndRepRegion s str globally region = do
let c_re = makeSimpleSearch s
setRegexE c_re
assign searchDirectionA Forward
withBuffer0 $ (/= 0) <$> searchAndRepRegion0 c_re str globally region
searchAndRepUnit :: String -> String -> Bool -> TextUnit -> EditorM Bool
searchAndRepUnit re str g unit = searchAndRepRegion re str g =<< withBuffer0 (regionOfB unit)
newtype Isearch = Isearch [(String, Region, Direction)]
deriving (Typeable, Binary)
instance Default Isearch where
def = Isearch []
instance YiVariable Isearch
isearchInitE :: Direction -> EditorM ()
isearchInitE dir = do
historyStartGen iSearch
p <- withBuffer0 pointB
resetRegexE
setDynamic (Isearch [("",mkRegion p p,dir)])
printMsg "I-search: "
isearchIsEmpty :: EditorM Bool
isearchIsEmpty = do
Isearch s <- getDynamic
return $ not $ null $ fst3 $ head s
isearchAddE :: String -> EditorM ()
isearchAddE increment = isearchFunE (++ increment)
makeSimpleSearch :: String -> SearchExp
makeSimpleSearch s = se
where Right se = makeSearchOptsM [QuoteRegex] s
makeISearch :: String -> SearchExp
makeISearch s = case makeSearchOptsM opts s of
Left _ -> SearchExp s emptyRegex emptyRegex []
Right search -> search
where opts = QuoteRegex : if any isUpper s then [] else [IgnoreCase]
isearchFunE :: (String -> String) -> EditorM ()
isearchFunE fun = do
Isearch s <- getDynamic
let (previous,p0,direction) = head s
current = fun previous
srch = makeISearch current
printMsg $ "I-search: " ++ current
setRegexE srch
prevPoint <- withBuffer0 pointB
matches <- withBuffer0 $ do
moveTo $ regionStart p0
when (direction == Backward) $
moveN $ length current
regexB direction srch
let onSuccess p = do withBuffer0 $ moveTo (regionEnd p)
setDynamic $ Isearch ((current,p,direction):s)
case matches of
(p:_) -> onSuccess p
[] -> do matchesAfterWrap <- withBuffer0 $ do
case direction of
Forward -> moveTo 0
Backward -> do
bufferLength <- sizeB
moveTo bufferLength
regexB direction srch
case matchesAfterWrap of
(p:_) -> onSuccess p
[] -> do withBuffer0 $ moveTo prevPoint
setDynamic $ Isearch ((current,p0,direction):s)
printMsg $ "Failing I-search: " ++ current
isearchDelE :: EditorM ()
isearchDelE = do
Isearch s <- getDynamic
case s of
(_:(text,p,dir):rest) -> do
withBuffer0 $
moveTo $ regionEnd p
setDynamic $ Isearch ((text,p,dir):rest)
setRegexE $ makeISearch text
printMsg $ "I-search: " ++ text
_ -> return ()
isearchHistory :: Int -> EditorM ()
isearchHistory delta = do
Isearch ((current,_p0,_dir):_) <- getDynamic
h <- historyMoveGen iSearch delta (return current)
isearchFunE (const h)
isearchPrevE :: EditorM ()
isearchPrevE = isearchNext0 Backward
isearchNextE :: EditorM ()
isearchNextE = isearchNext0 Forward
isearchNext0 :: Direction -> EditorM ()
isearchNext0 newDir = do
Isearch ((current,_p0,_dir):_rest) <- getDynamic
if null current
then isearchHistory 1
else isearchNext newDir
isearchNext :: Direction -> EditorM ()
isearchNext direction = do
Isearch ((current,p0,_dir):rest) <- getDynamic
withBuffer0 $ moveTo (regionStart p0 + startOfs)
mp <- withBuffer0 $
regexB direction (makeISearch current)
case mp of
[] -> do
endPoint <- withBuffer0 $ do
moveTo (regionEnd p0)
sizeB
printMsg "isearch: end of document reached"
let wrappedOfs = case direction of
Forward -> mkRegion 0 0
Backward -> mkRegion endPoint endPoint
setDynamic $ Isearch ((current,wrappedOfs,direction):rest)
(p:_) -> do
withBuffer0 $
moveTo (regionEnd p)
printMsg $ "I-search: " ++ current
setDynamic $ Isearch ((current,p,direction):rest)
where startOfs = case direction of
Forward -> 1
Backward -> 1
isearchWordE :: EditorM ()
isearchWordE = do
text <- withBuffer0 (pointB >>= nelemsB 32)
let (prefix, rest) = break isAlpha text
word = takeWhile isAlpha rest
isearchAddE (prefix ++ word)
isearchFinishE :: EditorM ()
isearchFinishE = isearchEnd True
isearchCancelE :: EditorM ()
isearchCancelE = isearchEnd False
isearchFinishWithE :: EditorM a -> EditorM ()
isearchFinishWithE act = isearchEndWith act True
isearchCancelWithE :: EditorM a -> EditorM ()
isearchCancelWithE act = isearchEndWith act False
iSearch :: String
iSearch = "isearch"
isearchEndWith :: EditorM a -> Bool -> EditorM ()
isearchEndWith act accept = getDynamic >>= \case
Isearch [] -> return ()
Isearch s -> do
let (lastSearched,_,dir) = head s
let (_,p0,_) = last s
historyFinishGen iSearch (return lastSearched)
assign searchDirectionA dir
if accept
then do act
withBuffer0 $ setSelectionMarkPointB $ regionStart p0
printMsg "Quit"
else do resetRegexE
withBuffer0 $ moveTo $ regionStart p0
isearchEnd :: Bool -> EditorM ()
isearchEnd = isearchEndWith (return ())
qrNext :: Window -> BufferRef -> SearchExp -> EditorM ()
qrNext win b what = do
mp <- withGivenBufferAndWindow0 win b $ regexB Forward what
case mp of
[] -> do
printMsg "String to search not found"
qrFinish
(r:_) -> withGivenBufferAndWindow0 win b $ setSelectRegionB r
qrReplaceAll :: Window -> BufferRef -> SearchExp -> String -> EditorM ()
qrReplaceAll win b what replacement = do
n <- withGivenBufferAndWindow0 win b $ do
exchangePointAndMarkB
searchAndRepRegion0 what replacement True =<< regionOfPartB Document Forward
printMsg $ "Replaced " ++ show n ++ " occurrences"
qrFinish
qrFinish :: EditorM ()
qrFinish = do
assign currentRegexA Nothing
closeBufferAndWindowE
qrReplaceOne :: Window -> BufferRef -> SearchExp -> String -> EditorM ()
qrReplaceOne win b reg replacement =
do qrReplaceCurrent win b replacement
qrNext win b reg
qrReplaceCurrent :: Window -> BufferRef -> String -> EditorM ()
qrReplaceCurrent win b replacement =
withGivenBufferAndWindow0 win b $
flip replaceRegionB replacement =<< getRawestSelectRegionB