-- | Operations involving Offset and Range through Engine interface module Offset where import Text.Regex.Posix import Data.List (find) import Data.Maybe (fromJust) import Control.Monad.State import Editor import Engine -- | move the cursor in the engine jumpE :: Ctx m w => Offset -- ^ the new position for the cursor -> Editor m w w -- ^ the modified engine under the Editor jumpE Current = through Just jumpE LastLine = through Engine.last jumpE (Next n) = through $ nextn n jumpE (Prev n) = through $ prevn n jumpE (Absolute n) = through $ jump n jumpE (ReNext s) = putlastre s >> (through . finder fwdcycle) s jumpE LastReNext = gets lastre >>= through . finder fwdcycle jumpE (RePrev s) = putlastre s >> (through . finder bwdcycle) s jumpE LastRePrev = gets lastre >>= through . finder bwdcycle finder f s = find ((=~ s) . fromJust . line) . f -- | From a range to the tuple (nelements,starting range element) rangeResolve :: Ctx m w => Range -- ^ the range to focus -> Editor m w (Int, w) -- ^ the tuple (nelements,engine placed -- at first offset of range) rangeResolve (Range o1 o2) = do w1 <- jumpE o1 w2 <- jumpE o2 return (distance (pos w1) (pos w2) , w1) -- | a complete backend + Editor action on an Offset doOffset :: Ctx m w => Offset -- ^ Offset for the action -> (a -> Editor m w b) -- ^ the final action -> ( w -> Maybe a) -- ^ the backend ation -> Editor m w b -- ^ .. doOffset o ef mf = jumpE o >>= backend . mf >>= ef -- | a backend action ending in a save state for the file editOffset :: Ctx m w => Offset -- ^ Offset for the backend action -> ( w -> Maybe w) -- ^ the backend ation -> Editor m w () -- ^ modified monad editOffset o = doOffset o hputfile -- | a complete backend + Editor action on a Range doRange :: Ctx m w => Range -- ^ the addressed range -> (a -> Editor m w b) -- ^ the closing Editor action -> (Int -> w -> Maybe a) -- ^ the backend action -> Editor m w b -- ^ ... doRange r ef mf = rangeResolve r >>= backend . uncurry mf >>= ef editRange :: Ctx m w => Range -- ^ the addressed range -> (Int -> w -> Maybe w) -- ^ the backend action -> Editor m w () -- ^ modified monad editRange r = doRange r hputfile