Moved Eq Token instance to AST where it belongs
This commit is contained in:
parent
0e4f8a763f
commit
3f3ca2789b
|
@ -19,6 +19,7 @@ module ShellCheck.AST where
|
|||
|
||||
import Control.Monad
|
||||
import Control.Monad.Identity
|
||||
import qualified Text.Regex as Re
|
||||
|
||||
data Id = Id Int deriving (Show, Eq, Ord)
|
||||
|
||||
|
@ -28,6 +29,11 @@ data Token = T_AND_IF Id | T_OR_IF Id | T_DSEMI Id | T_Semi Id | T_DLESS Id | T_
|
|||
|
||||
data ConditionType = DoubleBracket | SingleBracket deriving (Show, Eq)
|
||||
|
||||
-- I apologize for nothing!
|
||||
lolHax s = Re.subRegex (Re.mkRegex "(Id [0-9]+)") (show s) "(Id 0)"
|
||||
instance Eq Token where
|
||||
(==) a b = (lolHax a) == (lolHax b)
|
||||
|
||||
|
||||
analyze :: Monad m => (Token -> m ()) -> (Token -> m ()) -> (Token -> Token) -> Token -> m Token
|
||||
analyze f g i t =
|
||||
|
|
|
@ -31,7 +31,6 @@ import Data.Maybe
|
|||
import Prelude hiding (readList)
|
||||
import System.IO
|
||||
import Text.Parsec.Error
|
||||
import qualified Text.Regex as Re
|
||||
import GHC.Exts (sortWith)
|
||||
|
||||
|
||||
|
@ -441,11 +440,6 @@ condSpacingMsg soft msg = do
|
|||
space <- spacing
|
||||
when (null space) $ (if soft then parseNoteAt else parseProblemAt) pos ErrorC msg
|
||||
|
||||
|
||||
lolHax s = Re.subRegex (Re.mkRegex "(Id [0-9]+)") (show s) "(Id 0)"
|
||||
instance Eq Token where
|
||||
(==) a b = (lolHax a) == (lolHax b)
|
||||
|
||||
readComment = do
|
||||
char '#'
|
||||
anyChar `reluctantlyTill` linefeed
|
||||
|
|
Loading…
Reference in New Issue