Skip to content

Commit

Permalink
Apply some hlint suggestions
Browse files Browse the repository at this point in the history
  • Loading branch information
rezbyte authored and dbousamra committed Mar 15, 2023
1 parent c2e720c commit f4dfd0f
Show file tree
Hide file tree
Showing 6 changed files with 7 additions and 8 deletions.
4 changes: 2 additions & 2 deletions app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module Main where

import Control.Monad
import qualified Data.ByteString as BS
import Data.Maybe (catMaybes)
import Data.Maybe (mapMaybe)
import Data.Set as Set hiding (foldl)
import qualified Data.Text as T
import Emulator (reset, stepFrame)
Expand Down Expand Up @@ -65,7 +65,7 @@ render renderer = do
pure texture

eventsToIntents :: [SDL.Event] -> Set Intent
eventsToIntents events = Set.fromList $ catMaybes $ eventToIntent . SDL.eventPayload <$> events
eventsToIntents events = Set.fromList $ mapMaybe (eventToIntent . SDL.eventPayload) events
where
eventToIntent :: SDL.EventPayload -> Maybe Intent
eventToIntent SDL.QuitEvent = Just Exit
Expand Down
2 changes: 1 addition & 1 deletion src/Emulator/Mapper/Mapper2.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ read (Mapper2 Cartridge {..} _ prgBank1 prgBank2) addr
write :: Mapper2 -> Word16 -> Word8 -> IO ()
write (Mapper2 Cartridge {..} prgBanks prgBank1 _) addr v
| addr' < 0x2000 = VUM.write chrRom addr' v
| addr' >= 0x8000 = modifyIORef prgBank1 (const $ toInt v `rem` prgBanks)
| addr' >= 0x8000 = writeIORef prgBank1 (toInt v `rem` prgBanks)
| addr' >= 0x6000 = VUM.write sram (addr' - 0x6000) v
| otherwise = error $ "Erroneous cart write detected!" ++ prettifyWord16 addr
where addr' = fromIntegral addr
2 changes: 1 addition & 1 deletion src/Emulator/Mapper/Mapper3.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ write (Mapper3 Cartridge {..} chrBank _ _) addr v
| addr' < 0x2000 = do
chrBankV <- readIORef chrBank
VUM.write chrRom ((chrBankV * 0x2000) + addr') v
| addr' >= 0x8000 = modifyIORef chrBank (const $ toInt v .&. 3)
| addr' >= 0x8000 = writeIORef chrBank (toInt v .&. 3)
| addr' >= 0x6000 = VUM.write sram (addr' - 0x6000) v
| otherwise = error $ "Erroneous cart write detected!" ++ prettifyWord16 addr
where addr' = fromIntegral addr
2 changes: 1 addition & 1 deletion src/Emulator/Mapper/Mapper7.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ write (Mapper7 Cartridge {..} prgBank) addr v
let m = case v .&. 0x10 of
0x00 -> MirrorSingle0
0x10 -> MirrorSingle1
modifyIORef mirror (const m)
writeIORef mirror m
| addr' >= 0x6000 = VUM.write sram (addr' - 0x6000) v
| otherwise = error $ "Erroneous cart write detected!" ++ prettifyWord16 addr
where addr' = fromIntegral addr
Expand Down
3 changes: 1 addition & 2 deletions src/Emulator/Opcode.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@ module Emulator.Opcode (
, decodeOpcode
) where

import Data.List (intersperse)
import Data.Word
import Emulator.Util

Expand Down Expand Up @@ -55,7 +54,7 @@ data Opcode = Opcode {

instance Show Opcode where
show (Opcode raw mn mode len cyc pageCrossCy) =
concat . intersperse " "
unwords
$ "Opcode:" : prettifyWord8 raw
: show mn : show mode
: map show [len, cyc, pageCrossCy]
Expand Down
2 changes: 1 addition & 1 deletion test/Nestest/Parsing.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ parseTrace = do
_ <- space
cyc <- string "CYC:" >> cyclesP
_ <- space
_ <- string "SL:" >> (many $ noneOf "\n")
_ <- string "SL:" >> many (noneOf "\n")
let opcode = decodeOpcode a0r
pure $ Trace pcv spv av xv yv pv opcode a0r a1r a2r cyc

Expand Down

0 comments on commit f4dfd0f

Please sign in to comment.