Skip to content

Commit

Permalink
hlint hints
Browse files Browse the repository at this point in the history
  • Loading branch information
ix committed Jan 24, 2020
1 parent 727a3bc commit 19f6213
Show file tree
Hide file tree
Showing 5 changed files with 61 additions and 57 deletions.
2 changes: 1 addition & 1 deletion example/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,6 @@ main = rom >>= T.putStrLn
where rom = compileROM $ do
byte A 0xDE
byte B 0xDE
if' ((A == (0xDE :: Word8)) && (A == B)) $ do
if' ((A == (0xDE :: Word8)) && (A == B)) $
write (Address wram0) 0xDE
freeze
12 changes: 7 additions & 5 deletions src/Lazyboy/Control.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,8 @@ import Data.Word
import Lazyboy.Types
import Prelude hiding (not)

{-# ANN module "HLint: ignore Reduce duplication" #-}

-- | Get a label, and in the process increment the counter used to track labels.
-- this provides a safe interface to label retrieval and utilization.
getLabel :: Lazyboy Integer
Expand Down Expand Up @@ -149,10 +151,10 @@ not action = do
and :: Lazyboy Condition -> Lazyboy Condition -> Lazyboy Condition
and a b = do
a' <- a
cond a' $ do
cond a' $
tell [LDrn L 1]
b' <- b
cond b' $ do
cond b' $
tell [LDrn A 1]
tell [ANDr L]
return Zero
Expand All @@ -162,10 +164,10 @@ and a b = do
or :: Lazyboy Condition -> Lazyboy Condition -> Lazyboy Condition
or a b = do
a' <- a
cond a' $ do
cond a' $
tell [LDrn L 1]
b' <- b
cond b' $ do
cond b' $
tell [LDrn A 1]
tell [ORr L]
return Zero
Expand All @@ -176,7 +178,7 @@ while condition block = do
loop <- getLocalLabel
skip <- getLocalLabel
tell [LABEL loop]
if' (not condition) $ do
if' (not condition) $
tell [JP $ Name skip]
block
tell [JP $ Name loop]
Expand Down
2 changes: 1 addition & 1 deletion src/Lazyboy/IO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -120,7 +120,7 @@ memset dest len value = do

-- | Executes an action when vertical blank occurs.
onVblank :: Lazyboy () -> Lazyboy ()
onVblank block = do
onVblank block =
withLocalLabel $ \label -> do
tell [LDAnn $ Address ly, CPn 145]
tell [JPif NonZero $ Name label]
Expand Down
98 changes: 49 additions & 49 deletions src/Lazyboy/Target/ASM.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,15 +14,15 @@
{-# LANGUAGE OverloadedStrings #-}
module Lazyboy.Target.ASM where

import Control.Exception
import Data.List (intercalate)
import Data.Text (Text)
import Data.Word
import Lazyboy.Types
import Lazyboy.Templates (templatize, basic)
import Text.Printf
import Control.Exception
import Data.List (intercalate)
import Data.Text (Text)
import Data.Word
import Lazyboy.Templates (basic, templatize)
import Lazyboy.Types
import Text.Printf

import qualified Data.Text as T
import qualified Data.Text as T

-- | Lazyboy exception type.
data LazyboyException =
Expand Down Expand Up @@ -68,17 +68,17 @@ instance Show Instruction where
show (LDnnA v1) = printf "ld [%s], A" v1
show (LDAIO v1) = printf "ldh A, [$FF00+$%X]" v1
show (LDIOA v1) = printf "ldh [$FF00+$%X], A" v1
show (LDAIOC) = printf "ldh A, [$FF00+C]"
show (LDIOCA) = printf "ldh [$FF00+C], A"
show (LDHLAI) = printf "ld [HL+], A"
show (LDAHLI) = printf "ld A, [HL+]"
show LDAIOC = printf "ldh A, [$FF00+C]"
show LDIOCA = printf "ldh [$FF00+C], A"
show LDHLAI = printf "ld [HL+], A"
show LDAHLI = printf "ld A, [HL+]"

-- handle some special cases for ld rr,nn
show (LDrrnn AF _) = throw AttemptedAFPCLoad
show (LDrrnn PC _) = throw AttemptedAFPCLoad
show (LDrrnn r1 v1) = printf "ld %s, %s" r1 v1

show (LDSPHL) = printf "ld SP, HL"
show LDSPHL = printf "ld SP, HL"

-- stack manipulation
show (PUSH SP) = throw InvalidStackOperation
Expand All @@ -93,17 +93,17 @@ instance Show Instruction where
show (JP v1@(Address _)) = printf "jp %s" v1
show (JP v1@(Name (Global _))) = printf "jp %s" v1
show (JP v1@(Name (Local _))) = printf "jr %s" v1
show (JPHL) = printf "jp HL"
show JPHL = printf "jp HL"
show (JPif c v1@(Address _)) = printf "jp %s, %s" c v1
show (JPif c v1@(Name (Global _))) = printf "jp %s, %s" c v1
show (JPif c v1@(Name (Local _))) = printf "jr %s, %s" c v1

-- call and return
show (CALL v1) = printf "call %s" v1
show (CALLif c v1) = printf "call %s, %s" c v1
show (RET) = printf "ret"
show RET = printf "ret"
show (RETif c) = printf "ret %s" c
show (RETi) = printf "reti"
show RETi = printf "reti"

show (RST 0x00) = printf "RST $00"
show (RST 0x08) = printf "RST $08"
Expand All @@ -118,35 +118,35 @@ instance Show Instruction where
-- arithmetic and comparisons
show (ADDAr r1) = printf "add A, %s" r1
show (ADDAn v) = printf "add A, %d" v
show (ADDHL) = printf "add A, [HL]"
show ADDHL = printf "add A, [HL]"
show (ADCAr r1) = printf "adc A, %s" r1
show (ADCAn v) = printf "adc A, %d" v
show (ADCHL) = printf "adc A, [HL]"
show ADCHL = printf "adc A, [HL]"
show (SUBAr r1) = printf "sub A, %s" r1
show (SUBAn v) = printf "sub A, %d" v
show (SUBHL) = printf "sub A, [HL]"
show SUBHL = printf "sub A, [HL]"
show (SBCAr r1) = printf "sbc A, %s" r1
show (SBCAn v) = printf "sbc A, %d" v
show (SBCAHL) = printf "sbc A, [HL]"
show SBCAHL = printf "sbc A, [HL]"

show (ANDr r1) = printf "and A, %s" r1
show (ANDn v) = printf "and A, %d" v
show (ANDHL) = printf "and A, [HL]"
show ANDHL = printf "and A, [HL]"
show (XORr r1) = printf "xor A, %s" r1
show (XORn v) = printf "xor A, %d" v
show (XORHL) = printf "xor A, [HL]"
show XORHL = printf "xor A, [HL]"
show (ORr r1) = printf "or A, %s" r1
show (ORn v) = printf "or A, %d" v
show (ORHL) = printf "or A, [HL]"
show ORHL = printf "or A, [HL]"
show (CPr r1) = printf "cp A, %s" r1
show (CPn v) = printf "cp A, %d" v
show (CPHL) = printf "cp A, [HL]"
show CPHL = printf "cp A, [HL]"
show (INCr r1) = printf "inc %s" r1
show (INCHL) = printf "inc [HL]"
show INCHL = printf "inc [HL]"
show (DECr r1) = printf "dec %s" r1
show (DECHL) = printf "dec [HL]"
show (DAA) = printf "daa"
show (CPL) = printf "cpl"
show DECHL = printf "dec [HL]"
show DAA = printf "daa"
show CPL = printf "cpl"
show (ADDHLrr BC) = printf "add HL, BC"
show (ADDHLrr DE) = printf "add HL, DE"
show (ADDHLrr HL) = printf "add HL, HL"
Expand All @@ -164,35 +164,35 @@ instance Show Instruction where
show (DECrr r1) = throw $ IllegalModification r1

-- Rotate & shift
show (RLCA) = printf "rlca"
show (RLA) = printf "rla"
show (RRCA) = printf "rrca"
show (RRA) = printf "rra"
show RLCA = printf "rlca"
show RLA = printf "rla"
show RRCA = printf "rrca"
show RRA = printf "rra"
show (RLC r1) = printf "rlc %s" r1
show (RLCHL) = printf "rlc [HL]"
show RLCHL = printf "rlc [HL]"
show (RL r1) = printf "rl %s" r1
show (RLHL) = printf "rl [HL]"
show RLHL = printf "rl [HL]"
show (RRC r1) = printf "rrc %s" r1
show (RRCHL) = printf "rrc [HL]"
show RRCHL = printf "rrc [HL]"
show (RR r1) = printf "rr %s" r1
show (RRHL) = printf "rr [HL]"
show RRHL = printf "rr [HL]"
show (SLA r1) = printf "sla %s" r1
show (SLAHL) = printf "sla [HL]"
show SLAHL = printf "sla [HL]"
show (SWAP r1) = printf "swap %s" r1
show (SWAPHL) = printf "swap [HL]"
show SWAPHL = printf "swap [HL]"
show (SRA r1) = printf "sra %s" r1
show (SRAHL) = printf "sra [HL]"
show SRAHL = printf "sra [HL]"
show (SRL r1) = printf "srl %s" r1
show (SRLHL) = printf "srl [HL]"
show SRLHL = printf "srl [HL]"

-- CPU control
show (CCF) = printf "ccf"
show (SCF) = printf "scf"
show (NOP) = printf "nop"
show (HALT) = printf "halt"
show (STOP) = printf "stop"
show (DI) = printf "di"
show (EI) = printf "ei"
show CCF = printf "ccf"
show SCF = printf "scf"
show NOP = printf "nop"
show HALT = printf "halt"
show STOP = printf "stop"
show DI = printf "di"
show EI = printf "ei"

-- Bit manipulation
show (BITnr v r1)
Expand Down Expand Up @@ -239,8 +239,8 @@ instance PrintfArg Label where
formatArg (Global v) = formatString $ "L" ++ show v

instance PrintfArg Location where
formatArg (Address v) = formatString $ (printf "$%X" v :: String)
formatArg (Name label) = formatString $ (printf "%s" label :: String)
formatArg (Address v) = formatString (printf "$%X" v :: String)
formatArg (Name label) = formatString (printf "%s" label :: String)

-- | Compiles an action to an assembly source file.
-- This function makes use of a "bare" template, which
Expand Down
4 changes: 3 additions & 1 deletion test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,8 @@ import Lazyboy
import Lazyboy.Target.ASM
import Test.Hspec

{-# ANN module "HLint: ignore" #-}

disallow cmd = evaluate cmd `shouldThrow` anyException

main :: IO ()
Expand Down Expand Up @@ -387,4 +389,4 @@ main = hspec $ do
hram `shouldBe` 0xFF80
oam `shouldBe` 0xFE00
screenWidth `shouldBe` 160
screenHeight `shouldBe` 144
screenHeight `shouldBe` 144

0 comments on commit 19f6213

Please sign in to comment.