Skip to content

Commit

Permalink
Applied some hlint magic.
Browse files Browse the repository at this point in the history
  • Loading branch information
SOwOphie committed Jul 8, 2016
1 parent 986afa1 commit 03ae764
Show file tree
Hide file tree
Showing 12 changed files with 137 additions and 149 deletions.
66 changes: 34 additions & 32 deletions WSEdit.hs
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@ splitArgs args glob loc =

fext = case filter (isPrefixOf "-ff") sw of
[] | any (isInfixOf "-c") sw -> Just "wsconf"
[] | otherwise -> getExt <$> filename
| otherwise -> getExt <$> filename
l -> Just
$ drop 3
$ lastNote (fqn "splitArgs") l
Expand All @@ -107,18 +107,19 @@ start = do

-- Read the global and local config files. Use an empty string in case of
-- nonexistence.
h <- liftIO $ getHomeDirectory
h <- liftIO getHomeDirectory

b <- doesDirectoryExist $ h ++ "/.config/wsedit"

mods <- if b
then listDirectory (h ++ "/.config/wsedit")
>>= mapM ( fmap (lines . fromMaybe "")
. mayReadFile
. ((h ++ "/.config/wsedit/") ++ )
)
. filter (isSuffixOf ".wsconf")
>>= return . concat
then fmap concat
( mapM ( fmap (lines . fromMaybe "")
. mayReadFile
. ((h ++ "/.config/wsedit/") ++ )
)
. filter (isSuffixOf ".wsconf")
=<< listDirectory (h ++ "/.config/wsedit")
)
else return [""]


Expand Down Expand Up @@ -224,10 +225,7 @@ filterFileArgs (Just ext) s =
in
concatMap words
$ gl
++ ( filter (/= "")
$ map (fromMaybe "" . stripPrefix (ext ++ ":"))
loc
)
++ filter (/= "") (map (fromMaybe "" . stripPrefix (ext ++ ":")) loc)



Expand Down Expand Up @@ -311,20 +309,32 @@ mainLoop = do
-- if not found: insert the pressed key
-- if it's not alphanumeric: show an "event not bound" warning
catchEditor
( fromMaybe (case ev of
EvKey (KChar k) [] -> deleteSelection
>> insert k
>> listAutocomplete

EvResize _ _ -> return ()
_ -> setStatus $ "Event not bound: "
++ show ev
)
$ fmap fst
( maybe (case ev of
EvKey (KChar k) [] -> deleteSelection
>> insert k
>> listAutocomplete

EvResize _ _ -> return ()
_ -> setStatus $ "Event not bound: "
++ show ev
)
fst
$ lookup ev
$ catMaybes
$ keymap c
) $ \e -> do
) errHdl


when (dumpEvents c) $ do
s <- get
setStatus $ show ev ++ status s

b <- continue <$> get
when b mainLoop

where
errHdl :: SomeException -> WSEdit ()
errHdl e = do
b <- changed <$> get
if b
then do
Expand All @@ -336,11 +346,3 @@ mainLoop = do
++ " ./CRASH-RESCUE ."

else bail $ "An error occured: " ++ show e


when (dumpEvents c) $ do
s <- get
setStatus $ show ev ++ status s

b <- continue <$> get
when b mainLoop
34 changes: 17 additions & 17 deletions WSEdit/Buffer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -104,19 +104,19 @@ length b = prefLen b + sufLen b + 1

-- | Retrieve a sublist from the buffer. Indices are absolute and zero-based.
sub :: Int -> Int -> Buffer a -> [a]
sub from to b = ( L.reverse
$ L.drop (prefLen b - to - 1)
$ L.take (prefLen b - from)
$ prefix b
)
++ (if from <= currPos b && currPos b <= to
then [curr b]
else []
)
++ ( L.drop (from - prefLen b - 1)
$ L.take (to - prefLen b)
$ suffix b
)
sub from to b = L.reverse
( L.drop (prefLen b - to - 1)
$ L.take (prefLen b - from)
$ prefix b
)
++ (if from <= currPos b && currPos b <= to
then [curr b]
else []
)
++ L.drop (from - prefLen b - 1)
( L.take (to - prefLen b)
$ suffix b
)


-- | Retrieve the element left of the current position.
Expand Down Expand Up @@ -327,8 +327,8 @@ withLeftDef d f b | L.null $ prefix b = b { prefix = [f d]
withNLeft :: Int -> (a -> a) -> Buffer a -> Buffer a
withNLeft n f b =
let
l = (P.map f $ take n $ prefix b)
++ ( drop n $ prefix b)
l = P.map f (take n $ prefix b)
++ drop n ( prefix b)
in
b { prefix = l
, prefLen = P.length l
Expand Down Expand Up @@ -370,8 +370,8 @@ withRightDef d f b | L.null $ suffix b = b { suffix = [f d]
withNRight :: Int -> (a -> a) -> Buffer a -> Buffer a
withNRight n f b =
let
l = (P.map f $ take n $ suffix b)
++ ( drop n $ suffix b)
l = P.map f (take n $ suffix b)
++ drop n ( suffix b)
in
b { suffix = l
, sufLen = P.length l
Expand Down
7 changes: 3 additions & 4 deletions WSEdit/Control/Autocomplete.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,6 @@ import Control.Monad (forM_, unless, when)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.RWS.Strict (ask, get, modify, put)
import Data.Char (isSpace)
import Data.Maybe (fromMaybe)
import Data.List (intercalate, isSuffixOf, stripPrefix)
import System.Directory ( doesDirectoryExist, doesFileExist
, getCurrentDirectory, listDirectory
Expand Down Expand Up @@ -46,10 +45,10 @@ dictAdd f = do

let
depths = map snd
$ filter (\(x, _) -> fromMaybe (f == fname s) $ fmap (`isSuffixOf` f) x)
$ filter (\(x, _) -> maybe (f == fname s) (`isSuffixOf` f) x)
$ buildDict s

when (not $ null depths) $ do
unless (null depths) $ do
txt <- liftIO $ readFile f

d <- liftIO
Expand Down Expand Up @@ -133,7 +132,7 @@ listAutocomplete :: WSEdit ()
listAutocomplete = do
s <- get

unless ((null $ buildDict s) || (readOnly s))
unless (null (buildDict s) || readOnly s)
$ case getKeywordAtCursor (cursorPos s)
$ snd
$ B.curr
Expand Down
6 changes: 2 additions & 4 deletions WSEdit/Control/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ alterState a = modify (\s -> s { canComplete = False })

-- | Moves the viewport by the given amount of rows, columns.
moveViewport :: Int -> Int -> WSEdit ()
moveViewport r c = do
moveViewport r c =
getOffset
>>= setOffset
. withPair
Expand Down Expand Up @@ -107,14 +107,12 @@ moveCursor r c = alterState $ do

-- Targeted visual cursor offset
tPos <- case wantsPos s of
Just p -> return p
Nothing -> do
unless (n == 0)
$ modify (\s' -> s' { wantsPos = Just vPos })
return vPos

Just p -> do
return p

-- Resulting textual cursor offset (amount of characters)
newC <- visToTxtPos targetLn tPos
setCursor (tLnNo, newC)
Expand Down
5 changes: 1 addition & 4 deletions WSEdit/Control/Global.hs
Original file line number Diff line number Diff line change
Expand Up @@ -237,10 +237,7 @@ load = alterState $ do
{ edLines = B.toFirst l
, fname = p'
, cursorPos = 1
, readOnly = if w
then readOnly s
else True

, readOnly = not w || readOnly s
, replaceTabs = if detectTabs s
then '\t' `notElem` txt
else replaceTabs s
Expand Down
8 changes: 4 additions & 4 deletions WSEdit/Control/Selection.hs
Original file line number Diff line number Diff line change
Expand Up @@ -169,8 +169,8 @@ paste = alterBuffer $ do
-- | Indent the currently selected area using the current tab width and
-- replacement settings.
indentSelection :: WSEdit ()
indentSelection = alterBuffer $ do
getMark >>= \case
indentSelection = alterBuffer
$ getMark >>= \case
Nothing -> return ()
Just (sR, _) -> do
s <- get
Expand Down Expand Up @@ -201,8 +201,8 @@ indentSelection = alterBuffer $ do
-- | Unindent the currently selected area using the current tab width and
-- replacement settings.
unindentSelection :: WSEdit ()
unindentSelection = alterBuffer $ do
getMark >>= \case
unindentSelection = alterBuffer
$ getMark >>= \case
Nothing -> return ()
Just (sR, _) -> do
s <- get
Expand Down
2 changes: 1 addition & 1 deletion WSEdit/Control/Text.hs
Original file line number Diff line number Diff line change
Expand Up @@ -232,7 +232,7 @@ dumbNewLine = alterBuffer $ do
-- | Removes all trailing whitespace in the text buffer.
cleanse :: WSEdit ()
cleanse = alterBuffer $ do
modify (\s -> s { edLines = B.map (withSnd $ trim) $ edLines s })
modify (\s -> s { edLines = B.map (withSnd trim) $ edLines s })
moveCursor 0 0

where
Expand Down
11 changes: 4 additions & 7 deletions WSEdit/Data.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE FlexibleInstances
, LambdaCase
, StandaloneDeriving
, TypeSynonymInstances
#-}

Expand Down Expand Up @@ -79,7 +78,7 @@ fqn = ("WSEdit.Data." ++)

-- | Version number constant.
version :: String
version = "1.0.0.3 RC"
version = "1.0.0.4 RC"

-- | Upstream URL.
upstream :: String
Expand Down Expand Up @@ -238,12 +237,12 @@ clearMark = do

-- | Retrieve the position of the first selected element.
getFirstSelected :: WSEdit (Maybe (Int, Int))
getFirstSelected = (fmap fst) <$> getSelBounds
getFirstSelected = fmap fst <$> getSelBounds


-- | Retrieve the position of the last selected element.
getLastSelected :: WSEdit (Maybe (Int, Int))
getLastSelected = (fmap snd) <$> getSelBounds
getLastSelected = fmap snd <$> getSelBounds


-- | Faster combination of 'getFirstSelected' and 'getLastSelected'.
Expand Down Expand Up @@ -415,9 +414,7 @@ delSelection = getSelBounds >>= \case
-- | Retrieve the number of rows, colums displayed by vty, including all borders
-- , frames and similar woo.
getDisplayBounds :: WSEdit (Int, Int)
getDisplayBounds = ask
>>= displayBounds . outputIface . vtyObj
>>= return . swap
getDisplayBounds = fmap swap (displayBounds . outputIface . vtyObj =<< ask)



Expand Down
12 changes: 6 additions & 6 deletions WSEdit/Help.hs
Original file line number Diff line number Diff line change
Expand Up @@ -90,12 +90,12 @@ keymapHelp km =
)
in
"Dumping keymap (Meta = Alt on most systems):\n\n"
++ ( renderText 80
$ map (uncurry (++))
++ renderText 80
( map (uncurry (++))
$ concatMap (\case
Nothing -> [("",""), ("","")]
Just (e, s) ->
zip ( (padRight wdt ' ' (showEv e))
zip ( padRight wdt ' ' (showEv e)
: repeat (replicate wdt ' ')
) $ chunkWords (80 - wdt) s
)
Expand Down Expand Up @@ -134,7 +134,7 @@ keymapHelp km =

-- margin (87) |
confHelp :: String
confHelp = renderText 80 $
confHelp = renderText 80
[ "Persistent Configuration"
, ""
, "There are four distinct locations from which you can influence the behaviour of"
Expand Down Expand Up @@ -169,7 +169,7 @@ confHelp = renderText 80 $

-- margin (87) |
usageHelp :: String
usageHelp = renderText 80 $
usageHelp = renderText 80
[ "Usage: wsedit [-s] [<arguments>] [filename [line no. [column no.]]]"
, ""
, ""
Expand Down Expand Up @@ -358,7 +358,7 @@ usageHelp = renderText 80 $

-- margin (87) |
versionHelp :: String
versionHelp = renderText 80 $
versionHelp = renderText 80
[ "Wyvernscale Source Code Editor (wsedit) Version " ++ version
, ""
, "Licensed under the Wyvernscale Source Code License Version " ++ licenseVersion
Expand Down
Loading

0 comments on commit 03ae764

Please sign in to comment.