module Z80.Primitives where
--- not really into lenses so we're using these for now
+-- One day this will all be lenses.
+
+import Data.Word
+import Data.Bits
+
+import Z80.CPU
+
+-- 16-bit setters
setAF, setBC, setDE, setHL :: CPU -> Word16 -> CPU
-setAF cpu w = cpu { af = w }
-setBC cpu w = cpu { bc = w }
-setDE cpu w = cpu { de = w }
-setHL cpu w = cpu { hl = w }
+setAF cpu w = cpu { getAF = w }
+setBC cpu w = cpu { getBC = w }
+setDE cpu w = cpu { getDE = w }
+setHL cpu w = cpu { getHL = w }
setAF', setBC', setDE', setHL' :: CPU -> Word16 -> CPU
-setAF' cpu w = cpu { af' = w }
-setBC' cpu w = cpu { bc' = w }
-setDE' cpu w = cpu { de' = w }
-setHL' cpu w = cpu { hl' = w }
+setAF' cpu w = cpu { getAF' = w }
+setBC' cpu w = cpu { getBC' = w }
+setDE' cpu w = cpu { getDE' = w }
+setHL' cpu w = cpu { getHL' = w }
setIX, setIY, setSP, setPC :: CPU -> Word16 -> CPU
-setIX cpu w = cpu { ix = w }
-setIY cpu w = cpu { iy = w }
-setSP cpu w = cpu { sp = w }
-setPC cpu w = cpu { pc = w }
+setIX cpu w = cpu { getIX = w }
+setIY cpu w = cpu { getIY = w }
+setSP cpu w = cpu { getSP = w }
+setPC cpu w = cpu { getPC = w }
+
+-- 8-bit getters
+getA, getF, getB, getC, getD, getE, getH, getL :: CPU -> Word8
+getA cpu = fromIntegral $ getAF cpu `shiftR` 8
+getF cpu = fromIntegral $ getAF cpu
+getB cpu = fromIntegral $ getBC cpu `shiftR` 8
+getC cpu = fromIntegral $ getBC cpu
+getD cpu = fromIntegral $ getDE cpu `shiftR` 8
+getE cpu = fromIntegral $ getDE cpu
+getH cpu = fromIntegral $ getHL cpu `shiftR` 8
+getL cpu = fromIntegral $ getHL cpu
+getA', getF', getB', getC', getD', getE', getH', getL' :: CPU -> Word8
+getA' cpu = fromIntegral $ getAF' cpu `shiftR` 8
+getF' cpu = fromIntegral $ getAF' cpu
+getB' cpu = fromIntegral $ getBC' cpu `shiftR` 8
+getC' cpu = fromIntegral $ getBC' cpu
+getD' cpu = fromIntegral $ getDE' cpu `shiftR` 8
+getE' cpu = fromIntegral $ getDE' cpu
+getH' cpu = fromIntegral $ getHL' cpu `shiftR` 9
+getL' cpu = fromIntegral $ getHL' cpu
+
+-- 8-bit setters
setI, setR :: CPU -> Word8 -> CPU
-setI cpu b = cpu { i = b }
-setR cpu b = cpu { r = b }
+setI cpu b = cpu { getI = b }
+setR cpu b = cpu { getR = b }
+
+setA, setF, setB, setC, setD, setE, setH, setL :: CPU -> Word8 -> CPU
+setA cpu b = cpu
+ { getAF = (getAF cpu .&. 0x00ff) .|. (fromIntegral b `shiftL` 8) }
+setF cpu b = cpu { getAF = (getAF cpu .&. 0xff00) .|. fromIntegral b }
+setB cpu b = cpu
+ { getBC = (getBC cpu .&. 0x00ff) .|. (fromIntegral b `shiftL` 8) }
+setC cpu b = cpu { getBC = (getBC cpu .&. 0xff00) .|. fromIntegral b }
+setD cpu b = cpu
+ { getDE = (getDE cpu .&. 0x00ff) .|. (fromIntegral b `shiftL` 8) }
+setE cpu b = cpu { getDE = (getDE cpu .&. 0xff00) .|. fromIntegral b }
+setH cpu b = cpu
+ { getHL = (getHL cpu .&. 0x00ff) .|. (fromIntegral b `shiftL` 8) }
+setL cpu b = cpu { getHL = (getHL cpu .&. 0xff00) .|. fromIntegral b }
+
+setA', setF', setB', setC', setD', setE', setH', setL' :: CPU -> Word8 -> CPU
+setA' cpu b = cpu
+ { getAF' = (getAF' cpu .&. 0x00ff) .|. (fromIntegral b `shiftL` 8) }
+setF' cpu b = cpu { getAF' = (getAF' cpu .&. 0xff00) .|. fromIntegral b }
+setB' cpu b = cpu
+ { getBC' = (getBC' cpu .&. 0x00ff) .|. (fromIntegral b `shiftL` 8) }
+setC' cpu b = cpu { getBC' = (getBC' cpu .&. 0xff00) .|. fromIntegral b }
+setD' cpu b = cpu
+ { getDE' = (getDE' cpu .&. 0x00ff) .|. (fromIntegral b `shiftL` 8) }
+setE' cpu b = cpu { getDE' = (getDE' cpu .&. 0xff00) .|. fromIntegral b }
+setH' cpu b = cpu
+ { getHL' = (getHL' cpu .&. 0x00ff) .|. (fromIntegral b `shiftL` 8) }
+setL' cpu b = cpu { getHL' = (getHL' cpu .&. 0xff00) .|. fromIntegral b }
+-- 16-bit modifiers
+modifyAF, modifyBC, modifyDE, modifyHL :: CPU -> (Word16 -> Word16) -> CPU
+modifyAF cpu f = cpu `setAF` f (getAF cpu)
+modifyBC cpu f = cpu `setBC` f (getBC cpu)
+modifyDE cpu f = cpu `setDE` f (getDE cpu)
+modifyHL cpu f = cpu `setHL` f (getHL cpu)
+
+modifyAF', modifyBC', modifyDE', modifyHL' :: CPU -> (Word16 -> Word16) -> CPU
+modifyAF' cpu f = cpu `setAF'` f (getAF' cpu)
+modifyBC' cpu f = cpu `setBC'` f (getBC' cpu)
+modifyDE' cpu f = cpu `setDE'` f (getDE' cpu)
+modifyHL' cpu f = cpu `setHL'` f (getHL' cpu)
+
+modifyIX, modifyIY, modifySP, modifyPC :: CPU -> (Word16 -> Word16) -> CPU
+modifyIX cpu f = cpu `setIX` f (getIX cpu)
+modifyIY cpu f = cpu `setIY` f (getIY cpu)
+modifySP cpu f = cpu `setSP` f (getSP cpu)
+modifyPC cpu f = cpu `setPC` f (getPC cpu)
+
+-- 8-bit modifiers
+modifyI, modifyR :: CPU -> (Word8 -> Word8) -> CPU
+modifyI cpu f = cpu `setI` f (getI cpu)
+modifyR cpu f = cpu `setR` f (getR cpu)
+
+modifyA, modifyF, modifyB, modifyC :: CPU -> (Word8 -> Word8) -> CPU
+modifyD, modifyE, modifyH, modifyL :: CPU -> (Word8 -> Word8) -> CPU
+modifyA cpu f = cpu `setA` f (getA cpu)
+modifyF cpu f = cpu `setF` f (getF cpu)
+modifyB cpu f = cpu `setB` f (getB cpu)
+modifyC cpu f = cpu `setC` f (getC cpu)
+modifyD cpu f = cpu `setD` f (getD cpu)
+modifyE cpu f = cpu `setE` f (getE cpu)
+modifyH cpu f = cpu `setH` f (getH cpu)
+modifyL cpu f = cpu `setL` f (getL cpu)
+
+modifyA', modifyF', modifyB', modifyC' :: CPU -> (Word8 -> Word8) -> CPU
+modifyD', modifyE', modifyH', modifyL' :: CPU -> (Word8 -> Word8) -> CPU
+modifyA' cpu f = cpu `setA'` f (getA' cpu)
+modifyF' cpu f = cpu `setF'` f (getF' cpu)
+modifyB' cpu f = cpu `setB'` f (getB' cpu)
+modifyC' cpu f = cpu `setC'` f (getC' cpu)
+modifyD' cpu f = cpu `setD'` f (getD' cpu)
+modifyE' cpu f = cpu `setE'` f (getE' cpu)
+modifyH' cpu f = cpu `setH'` f (getH' cpu)
+modifyL' cpu f = cpu `setL'` f (getL' cpu)
+
+-- prefixed
setPrefixed :: CPU -> Prefixed -> CPU
-setPrefixed cpu p = cpu { prefixed = p }
+setPrefixed cpu p = cpu { getPrefixed = p }
+
+modifyPrefixed :: CPU -> (Prefixed -> Prefixed) -> CPU
+modifyPrefixed cpu f = cpu `setPrefixed` f (getPrefixed cpu)