-------------------------------------------------------------------------------
-- |
-- Module      :  System.Hardware.Arduino.SamplePrograms.Counter
-- Copyright   :  (c) Levent Erkok
-- License     :  BSD3
-- Maintainer  :  erkokl@gmail.com
-- Stability   :  experimental
--
-- Demonstrates using two push-buttons to count up and down.
-------------------------------------------------------------------------------

{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

module System.Hardware.Arduino.SamplePrograms.Counter where

import Control.Monad.Trans (liftIO)

import System.Hardware.Arduino

-- | Two push-button switches, controlling a counter value. We will increment
-- the counter if the first one (@bUp@) is pressed, and decrement the value if the
-- second one (@bDown@) is pressed. We also have a led connected to pin 13 (either use
-- the internal or connect an external one), that we light up when the counter value
-- is 0.
--
-- Wiring is very simple: Up-button connected to pin 4, Down-button connected
-- to pin 2, and a led on pin 13.
--
--  <<http://github.com/LeventErkok/hArduino/raw/master/System/Hardware/Arduino/SamplePrograms/Schematics/Counter.png>>
counter :: IO ()
counter :: IO ()
counter = Bool -> FilePath -> Arduino () -> IO ()
withArduino Bool
False FilePath
"/dev/cu.usbmodemFD131" forall a b. (a -> b) -> a -> b
$ do
            Pin -> PinMode -> Arduino ()
setPinMode Pin
led   PinMode
OUTPUT
            Pin -> PinMode -> Arduino ()
setPinMode Pin
bUp   PinMode
INPUT
            Pin -> PinMode -> Arduino ()
setPinMode Pin
bDown PinMode
INPUT
            forall {t} {b}. (Show t, Eq t, Num t) => t -> Arduino b
update (Int
0::Int)
 where bUp :: Pin
bUp   = Word8 -> Pin
digital Word8
4
       bDown :: Pin
bDown = Word8 -> Pin
digital Word8
2
       led :: Pin
led   = Word8 -> Pin
digital Word8
13
       update :: t -> Arduino b
update t
curVal = do
                forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> IO ()
print t
curVal
                Pin -> Bool -> Arduino ()
digitalWrite Pin
led (t
curVal forall a. Eq a => a -> a -> Bool
== t
0)
                ~[Bool
up, Bool
down] <- [Pin] -> Arduino [Bool]
waitAnyHigh [Pin
bUp, Pin
bDown]
                let newVal :: t
newVal = case (Bool
up, Bool
down) of
                               (Bool
True,  Bool
True)  -> t
curVal    -- simultaneous press
                               (Bool
True,  Bool
False) -> t
curValforall a. Num a => a -> a -> a
+t
1
                               (Bool
False, Bool
True)  -> t
curValforall a. Num a => a -> a -> a
-t
1
                               (Bool
False, Bool
False) -> t
curVal    -- can't happen
                t -> Arduino b
update t
newVal