Skip to content

Commit

Permalink
Use catMaybe
Browse files Browse the repository at this point in the history
  • Loading branch information
raxod502 committed May 12, 2020
1 parent da37fa3 commit c0bda83
Show file tree
Hide file tree
Showing 3 changed files with 3 additions and 8 deletions.
4 changes: 2 additions & 2 deletions src/Lexer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,11 @@ module Lexer
where

import Control.Applicative
import Data.Maybe
import Text.Regex.TDFA
import Text.Regex.TDFA.String ( )

import Tokens
import Util

-- Chars that cannot appear in a symbol, for use inside character
-- class. We have to put the brackets first for regex syntax reasons.
Expand Down Expand Up @@ -76,7 +76,7 @@ getToken s =
Just (text, token) -> (drop (length text) s, token)

tokenize :: String -> [Token]
tokenize str = collectMaybes $ getTokens str
tokenize str = catMaybes $ getTokens str
where
getTokens [] = []
getTokens s = let (s', t) = getToken s in t : getTokens s'
2 changes: 1 addition & 1 deletion src/Linker.hs
Original file line number Diff line number Diff line change
Expand Up @@ -282,7 +282,7 @@ link (codeB, dataB, codeSymbols, dataSymbols) =
, dataLen = fromIntegral $ B.length dataB
}
shdrData = sectionHeader info (length allSymbols)
shStringList = collectMaybes (map snd shdrData)
shStringList = mapMaybe snd shdrData
shstrtabData = strtab shStringList
symstrtabData = strtab allSymbols
in if all (\phe -> B.length phe == phelen) phdr
Expand Down
5 changes: 0 additions & 5 deletions src/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,11 +11,6 @@ class Pretty a where
fixedPoint :: Eq a => a -> (a -> a) -> a
fixedPoint x f = let fx = f x in if x == fx then x else fixedPoint fx f

collectMaybes :: [Maybe a] -> [a]
collectMaybes [] = []
collectMaybes (Nothing : ms) = collectMaybes ms
collectMaybes (Just a : ms) = a : collectMaybes ms

leftover :: Integral n => n -> n -> n
leftover f x = (f - x) `mod` f

Expand Down

0 comments on commit c0bda83

Please sign in to comment.