{-# LINE 1 "System/CWiid.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LINE 2 "System/CWiid.hsc" #-}

-- |
-- Module      :  System.CWiid
-- Copyright   :  Kiwamu Okabe, Ivan Perez and the cwiid team
-- License     :  GPL-2
--
-- Maintainer  :  ivan.perez@keera.co.uk
-- Stability   :  experimental
-- Portability :  unknown
--
-- Bindings for the cwiid library, a working userspace driver
-- along with various applications implementing event drivers,
-- multiple Wiimote connectivity, gesture recognition, and other
-- Wiimote-based functionality.
--
-- The current implementation is rather incomplete. In particular:
--
-- * Some Haskell functions (those related to rpt mode, rumble, leds)
-- had hard-coded values in them. Therefore, they implemented only a
-- very partial interface to their C counterparts. The new versions
-- should be tested and, if any other function is like this,
-- then exported properly.
--
-- * Not all functions/wiimote fields are accessible. In particular,
-- acceleromoter and IR is in testing stage. Nunchuck, calibration,
-- wiimote plus are not handled at all (but will be in the future).
--
-- All in all, the code works quite well and is currently being used
-- to implement several real games.

module System.CWiid
       (
        -- * Initialization
        cwiidOpen,
        CWiidWiimote,
        -- * State
        CWiidState(..),
        -- * Reception mode
        cwiidSetRptMode,
        -- * Leds
        CWiidLedFlag,
        cwiidLed1,
        cwiidLed2,
        cwiidLed3,
        cwiidLed4,
        -- ** Led operations
        cwiidSetLed,
        combineCwiidLedFlag,
        -- * Rumble
        cwiidSetRumble,
        -- * Buttons
        cwiidGetBtnState, cwiidIsBtnPushed,
        cwiidBtn2, cwiidBtn1, cwiidBtnB, cwiidBtnA, cwiidBtnMinus,
        cwiidBtnHome, cwiidBtnLeft, cwiidBtnRight, cwiidBtnDown, cwiidBtnUp,
        cwiidBtnPlus, combineCwiidBtnFlag, diffCwiidBtnFlag,
        CWiidBtnFlag(..),
        -- * Accelerometers
        cwiidGetAcc,
        CWiidAcc(..),
        -- * Infra-red
        CWiidIRSrc(..),
        cwiidGetIR
        ) where

-- import Foreign.C.Error
import Data.Bits
import Foreign.C.Types
import Foreign.Marshal
import Foreign.Ptr
import Foreign.Storable


{-# LINE 74 "System/CWiid.hsc" #-}

-----------------------------------------------------------------------------
-- Data type
---

-- typedef struct {
--         uint8_t b[6];
-- } __attribute__((packed)) bdaddr_t;
-- #define BDADDR_ANY   (&(bdaddr_t) {{0, 0, 0, 0, 0, 0}})
data CWiidBdaddr = CWiidBdaddr Int Int Int Int Int Int
instance Storable CWiidBdaddr where
  sizeOf = const (6)
{-# LINE 86 "System/CWiid.hsc" #-}
  alignment = sizeOf
  poke bdat (CWiidBdaddr b0 b1 b2 b3 b4 b5) = do
    ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) bdat b0
{-# LINE 89 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 1)) bdat b1
{-# LINE 90 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 2)) bdat b2
{-# LINE 91 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 3)) bdat b3
{-# LINE 92 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 4)) bdat b4
{-# LINE 93 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 5)) bdat b5
{-# LINE 94 "System/CWiid.hsc" #-}
  peek bdat = do
    b0 <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) bdat
{-# LINE 96 "System/CWiid.hsc" #-}
    b1 <- ((\hsc_ptr -> peekByteOff hsc_ptr 1)) bdat
{-# LINE 97 "System/CWiid.hsc" #-}
    b2 <- ((\hsc_ptr -> peekByteOff hsc_ptr 2)) bdat
{-# LINE 98 "System/CWiid.hsc" #-}
    b3 <- ((\hsc_ptr -> peekByteOff hsc_ptr 3)) bdat
{-# LINE 99 "System/CWiid.hsc" #-}
    b4 <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) bdat
{-# LINE 100 "System/CWiid.hsc" #-}
    b5 <- ((\hsc_ptr -> peekByteOff hsc_ptr 5)) bdat
{-# LINE 101 "System/CWiid.hsc" #-}
    return $ CWiidBdaddr b0 b1 b2 b3 b4 b5

-- typedef struct wiimote cwiid_wiimote_t;
--
-- | A connection to an existing wiimote. Use 'cwiidOpen' to
-- connect to a wiimote and obtain one of these.
newtype CWiidWiimote = CWiidWiimote { unCWiidWiimote :: Ptr () }

-- | Try to establish a connection to any existing Wiimote using
-- any existing bluetooth interface.
-- 
-- The function returns 'Nothing' if there is no bluetooth interface
-- or if no wiimote can be located. If the connection succeeds,
-- a 'CWiidWiimote' is returned (inside a 'Just'), which can be used to 
-- poll the wiimote using other functions.
-- 
-- There is a default timeout of 5 seconds.
-- 
-- * TODO: export cwiid_open_time and cwiid_close as well.

-- wiimote = cwiid_open(&bdaddr, 0)))
cwiidOpen :: IO (Maybe CWiidWiimote)
cwiidOpen =
  alloca $ \bdAddr -> do
    poke bdAddr $ CWiidBdaddr 0 0 0 0 0 0
    handle <- c_cwiid_open bdAddr 0 -- エラー処理必要
    if handle == nullPtr
      then return Nothing
      else return $ Just $ CWiidWiimote handle

{--
struct cwiid_state {
        uint8_t rpt_mode;
        uint8_t led;
        uint8_t rumble;
        uint8_t battery;
        uint16_t buttons;
        uint8_t acc[3];
        struct cwiid_ir_src ir_src[CWIID_IR_SRC_COUNT];
        enum cwiid_ext_type ext_type;
        union ext_state ext;
        enum cwiid_error error;
};
--}

-- | The state of the wiimote. Use 'cwiidSetRptMode' to enable/disable
-- sensors.
-- 
-- * FIXME: incomplete state
-- * FIXME: export get_state
data CWiidState = CWiidState
  { rptMode :: Int, led :: Int, rumble :: Int, 
    battery :: Int, buttons :: Int, acc :: [Int]
  , irSrc   :: [CWiidIRSrc]
  }
  deriving Show

instance Storable CWiidState where
  sizeOf = const (60)
{-# LINE 160 "System/CWiid.hsc" #-}
  alignment = sizeOf
  poke cwst (CWiidState rp l ru ba bu [ac0,ac1,ac2] irs) = do
    ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) cwst rp
{-# LINE 163 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 1)) cwst l
{-# LINE 164 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 2)) cwst ru
{-# LINE 165 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 3)) cwst ba
{-# LINE 166 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 4)) cwst bu
{-# LINE 167 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 6)) cwst (fromIntegral ac0 :: CUChar)
{-# LINE 168 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 7)) cwst (fromIntegral ac1 :: CUChar)
{-# LINE 169 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) cwst (fromIntegral ac2 :: CUChar)
{-# LINE 170 "System/CWiid.hsc" #-}
    pokeArray (((\hsc_ptr -> hsc_ptr `plusPtr` 10)) cwst) irs 
{-# LINE 171 "System/CWiid.hsc" #-}
  peek cwst = do
    rp <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) cwst
{-# LINE 173 "System/CWiid.hsc" #-}
    l <- ((\hsc_ptr -> peekByteOff hsc_ptr 1)) cwst
{-# LINE 174 "System/CWiid.hsc" #-}
    ru <- ((\hsc_ptr -> peekByteOff hsc_ptr 2)) cwst
{-# LINE 175 "System/CWiid.hsc" #-}
    ba <- ((\hsc_ptr -> peekByteOff hsc_ptr 3)) cwst
{-# LINE 176 "System/CWiid.hsc" #-}
    bu <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) cwst
{-# LINE 177 "System/CWiid.hsc" #-}
    ac0 <- ((\hsc_ptr -> peekByteOff hsc_ptr 6)) cwst
{-# LINE 178 "System/CWiid.hsc" #-}
    ac1 <- ((\hsc_ptr -> peekByteOff hsc_ptr 7)) cwst
{-# LINE 179 "System/CWiid.hsc" #-}
    ac2 <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) cwst
{-# LINE 180 "System/CWiid.hsc" #-}
    irs <- peekArray cwiidIrSrcCount (((\hsc_ptr -> hsc_ptr `plusPtr` 10)) cwst)
{-# LINE 181 "System/CWiid.hsc" #-}
    return $ CWiidState rp l ru ba bu [ fromIntegral (ac0 :: CUChar)
                                      , fromIntegral (ac1 :: CUChar)
                                      , fromIntegral (ac2 :: CUChar)]
                                      irs

-- * Infrared

-- | Maximum number of infrared points detected.
--   By default (according to cwiid) it should be 4.
cwiidIrSrcCount :: Int
cwiidIrSrcCount = (4)
{-# LINE 192 "System/CWiid.hsc" #-}

-- struct cwiid_ir_src {
-- 	char valid;
-- 	uint16_t pos[2];
-- 	int8_t size;
-- };
--
-- The following model is weaker than the counterpart in C (see above). We do
-- so in order to provide something more "natural" in Haskell, but it might
-- be better to use a more precise datatype.

-- | Internal representation of an infrared point. You should no use it
--   unless you know what you are doing; use 'CWiidIR' instead.
data CWiidIRSrc = CWiidIRSrc
  { cwiidIRSrcValid :: Bool
  , cwiidIRSrcPosX  :: Int
  , cwiidIRSrcPosY  :: Int
  , cwiidIRSrcSize  :: Int
  }
 deriving Show

instance Storable CWiidIRSrc where
  sizeOf = const (8)
{-# LINE 215 "System/CWiid.hsc" #-}
  alignment = sizeOf
  poke cwst (CWiidIRSrc valid posX posY sz) = do
    ((\hsc_ptr -> pokeByteOff hsc_ptr 0))  cwst ((if valid then (-1) else 0) :: CChar)
{-# LINE 218 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 2)) cwst (fromIntegral posX :: CUShort)
{-# LINE 219 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 4)) cwst (fromIntegral posY :: CUShort)
{-# LINE 220 "System/CWiid.hsc" #-}
    ((\hsc_ptr -> pokeByteOff hsc_ptr 6))   cwst (fromIntegral sz   :: CChar)
{-# LINE 221 "System/CWiid.hsc" #-}
  peek cwst = do
    valid <- ((\hsc_ptr -> peekByteOff hsc_ptr 0))  cwst
{-# LINE 223 "System/CWiid.hsc" #-}
    posX  <- ((\hsc_ptr -> peekByteOff hsc_ptr 2)) cwst
{-# LINE 224 "System/CWiid.hsc" #-}
    posY  <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) cwst
{-# LINE 225 "System/CWiid.hsc" #-}
    sz    <- ((\hsc_ptr -> peekByteOff hsc_ptr 6))   cwst
{-# LINE 226 "System/CWiid.hsc" #-}
    return $ CWiidIRSrc (not ((valid :: CChar) == 0))
                        (fromIntegral (posX :: CUShort))
                        (fromIntegral (posY :: CUShort))
                        (fromIntegral (sz :: CChar))

cwiidGetIR :: CWiidWiimote -> IO [CWiidIRSrc]
cwiidGetIR wm = 
  alloca $ \wiState -> do
    _ <- c_cwiid_get_state handle wiState
    ws <- peek wiState
    return (irSrc ws)
      where handle = unCWiidWiimote wm

-- * Leds
newtype CWiidLedFlag = CWiidLedFlag { unCWiidLedFlag :: Int }
                     deriving (Eq, Show)

-- | Flag with exactly led 1 enabled. Use 'combineCwiidLedFlag'
--   to create flags with several leds enabled.
cwiidLed1  :: CWiidLedFlag
cwiidLed1  = CWiidLedFlag 1

{-# LINE 248 "System/CWiid.hsc" #-}

-- | Flag with exactly led 2 enabled. Use 'combineCwiidLedFlag'
--   to create flags with several leds enabled.
cwiidLed2  :: CWiidLedFlag
cwiidLed2  = CWiidLedFlag 2

{-# LINE 254 "System/CWiid.hsc" #-}

-- | Flag with exactly led 2 enabled. Use 'combineCwiidLedFlag'
--   to create flags with several leds enabled.
cwiidLed3  :: CWiidLedFlag
cwiidLed3  = CWiidLedFlag 4

{-# LINE 260 "System/CWiid.hsc" #-}

-- | Flag with exactly led 4 enabled. Use 'combineCwiidLedFlag'
--   to create flags with several leds enabled.
cwiidLed4  :: CWiidLedFlag
cwiidLed4  = CWiidLedFlag 8

{-# LINE 266 "System/CWiid.hsc" #-}

-- | Enable/disable certain leds.
--
--   Use 'cwiidLed1' .. 'cwiidLed4' together with 'combineCwiidLedFlag'
--   to create a flag with just the leds you want enabled and change
--   all at once with one operation.
cwiidSetLed :: CWiidWiimote -> CWiidLedFlag -> IO CInt
cwiidSetLed wm leds = c_cwiid_set_led handle ledUChars
  where handle    = unCWiidWiimote wm
        ledUChars = fromIntegral (unCWiidLedFlag leds)

-- | Combine several led flags into one led flag with those leds
--   enabled and all other leds disabled.

combineCwiidLedFlag :: [CWiidLedFlag] -> CWiidLedFlag
combineCwiidLedFlag = CWiidLedFlag . foldr ((.|.) . unCWiidLedFlag) 0

-- * Buttons

newtype CWiidBtnFlag = CWiidBtnFlag { unCWiidBtnFlag :: Int }
                     deriving (Eq, Show)
cwiidBtn2      :: CWiidBtnFlag
cwiidBtn2      = CWiidBtnFlag 1
cwiidBtn1      :: CWiidBtnFlag
cwiidBtn1      = CWiidBtnFlag 2
cwiidBtnB      :: CWiidBtnFlag
cwiidBtnB      = CWiidBtnFlag 4
cwiidBtnA      :: CWiidBtnFlag
cwiidBtnA      = CWiidBtnFlag 8
cwiidBtnMinus  :: CWiidBtnFlag
cwiidBtnMinus  = CWiidBtnFlag 16
cwiidBtnHome   :: CWiidBtnFlag
cwiidBtnHome   = CWiidBtnFlag 128
cwiidBtnLeft   :: CWiidBtnFlag
cwiidBtnLeft   = CWiidBtnFlag 256
cwiidBtnRight  :: CWiidBtnFlag
cwiidBtnRight  = CWiidBtnFlag 512
cwiidBtnDown   :: CWiidBtnFlag
cwiidBtnDown   = CWiidBtnFlag 1024
cwiidBtnUp     :: CWiidBtnFlag
cwiidBtnUp     = CWiidBtnFlag 2048
cwiidBtnPlus   :: CWiidBtnFlag
cwiidBtnPlus   = CWiidBtnFlag 4096

{-# LINE 300 "System/CWiid.hsc" #-}

combineCwiidBtnFlag :: [CWiidBtnFlag] -> CWiidBtnFlag
combineCwiidBtnFlag = CWiidBtnFlag . foldr ((.|.) . unCWiidBtnFlag) 0

diffCwiidBtnFlag :: CWiidBtnFlag -> CWiidBtnFlag -> CWiidBtnFlag
diffCwiidBtnFlag a b = CWiidBtnFlag $ ai - (ai .&. bi)
  where ai = unCWiidBtnFlag a
        bi = unCWiidBtnFlag b

-- * Reception mode

-- | Reception modes that select which sensors/wiimote activity
-- we listen to.
newtype CWiidRptMode = CWiidRptMode { unCWiidRptMode :: CUChar }
  deriving (Eq, Show)

-- | Enable/disable reception of certain sensors.
-- Use 2 to enable buttons.
cwiidSetRptMode :: CWiidWiimote -> CUChar -> IO CInt
cwiidSetRptMode wm u = c_cwiid_set_rpt_mode handle u -- set BTN
  where handle = unCWiidWiimote wm

-- * Rumble

cwiidSetRumble :: CWiidWiimote -> CUChar -> IO CInt
cwiidSetRumble wm rm = c_cwiid_set_rumble handle rm
  where handle = unCWiidWiimote wm

-- * Buttons

-- | Returns a mask with the buttons that are currently pushed.
cwiidGetBtnState :: CWiidWiimote -> IO CWiidBtnFlag
cwiidGetBtnState wm =
  alloca $ \wiState -> do
    _ <- c_cwiid_get_state handle wiState
    ws <- peek wiState
    return $ CWiidBtnFlag $ buttons ws
      where handle = unCWiidWiimote wm

-- | Returns 'True' if the button indicated by the flag is pushed,
-- 'False' otherwise.
-- 
-- This is a pure function, so the first argument must be the
-- button flags as returned by 'cwiidGetBtnState'. 
cwiidIsBtnPushed :: CWiidBtnFlag -- ^ The button flags as returned by 'cwiidGetBtnState'. 
                 -> CWiidBtnFlag -- ^ A mask that flags the button/s that we want to check.
                 -> Bool         -- ^ 'True' if they are all pushed, 'False' otherwise.
cwiidIsBtnPushed flags btn =
  unCWiidBtnFlag flags .&. unCWiidBtnFlag btn == unCWiidBtnFlag btn

-- * Accelerometres

-- | Array of accelerometer information. It will always contain
-- exactly three elements.
-- 
-- * TODO: provide a more informative and restrictive interface
-- with exactly three named Int (byte?) fields.
--
newtype CWiidAcc = CWiidAcc { unCWiidAcc :: [Int] }
 deriving (Eq, Show)

-- | Obtain accelerometer information.
--   FIXME: read wmgui/main.c:cwiid_acc(1119) to understand how to use
--   this information, what else might need to be exported, and how
--   to calibrate the accelerometers.
cwiidGetAcc :: CWiidWiimote -> IO CWiidAcc
cwiidGetAcc wm =
  alloca $ \wiState -> do
    _ <- c_cwiid_get_state handle wiState
    ws <- peek wiState
    return $ CWiidAcc $ acc ws
      where handle = unCWiidWiimote wm
  
-- * Low-level bindings to C functions and back

-----------------------------------------------------------------------------
-- C land
---
-- Haskell => C
---

-- cwiid_wiimote_t *cwiid_open(bdaddr_t *bdaddr, int flags)
foreign import ccall safe "cwiid_open" c_cwiid_open
  :: Ptr CWiidBdaddr -> CInt -> IO (Ptr ())

-- typedef unsigned char             uint8_t
-- int cwiid_set_led(cwiid_wiimote_t *wiimote, uint8_t led)
foreign import ccall safe "cwiid_set_led" c_cwiid_set_led
  :: Ptr () -> CUChar -> IO CInt

-- int cwiid_set_rpt_mode(cwiid_wiimote_t *wiimote, uint8_t rpt_mode);
foreign import ccall safe "cwiid_set_rpt_mode" c_cwiid_set_rpt_mode
  :: Ptr () -> CUChar -> IO CInt

-- int cwiid_set_rumble(cwiid_wiimote_t *wiimote, uint8_t rumble);
foreign import ccall safe "cwiid_set_rumble" c_cwiid_set_rumble
  :: Ptr () -> CUChar -> IO CInt

-- int cwiid_get_state(cwiid_wiimote_t *wiimote, struct cwiid_state *state);
foreign import ccall safe "cwiid_get_state" c_cwiid_get_state
  :: Ptr () -> Ptr CWiidState -> IO CInt


-- C => Haskell
---

-- int cwiid_set_mesg_callback(cwiid_wiimote_t *wiimote,
--                             cwiid_mesg_callback_t *callback)
-- xxxxx
-- typedef void cwiid_mesg_callback_t(cwiid_wiimote_t *, int,
--                                    union cwiid_mesg [], struct timespec *)
-- xxxxx