-------------------------------------------------------------------------------
-- |
-- Module      :  System.Hardware.Arduino.SamplePrograms.Analog
-- Copyright   :  (c) Levent Erkok
-- License     :  BSD3
-- Maintainer  :  erkokl@gmail.com
-- Stability   :  experimental
--
-- Reads the value of an analog input, controlled by a 10K potentiometer.
-------------------------------------------------------------------------------

module System.Hardware.Arduino.SamplePrograms.Analog where

import Control.Monad       (when)
import Control.Monad.Trans (liftIO)

import System.Hardware.Arduino

-- | Read the value of an analog input line. We will print the value
-- on the screen, and also blink a led on the Arduino based on the
-- value. The smaller the value, the faster the blink.
--
-- The circuit simply has a 10K potentiometer between 5V and GND, with
-- the wiper line connected to analog input 3. We also have a led between
-- pin 13 and GND.
--
--  <<http://github.com/LeventErkok/hArduino/raw/master/System/Hardware/Arduino/SamplePrograms/Schematics/Analog.png>>
analogVal :: IO ()
analogVal :: IO ()
analogVal = 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
pot PinMode
ANALOG
               Int
cur <- Pin -> Arduino Int
analogRead Pin
pot
               forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> IO ()
print Int
cur
               forall {b}. Int -> Arduino b
go Int
cur
  where led :: Pin
led = Word8 -> Pin
digital Word8
13
        pot :: Pin
pot = Word8 -> Pin
analog Word8
3
        go :: Int -> Arduino b
go Int
cur = do Pin -> Bool -> Arduino ()
digitalWrite Pin
led Bool
True
                    Int -> Arduino ()
delay Int
cur
                    Pin -> Bool -> Arduino ()
digitalWrite Pin
led Bool
False
                    Int -> Arduino ()
delay Int
cur
                    Int
new <- Pin -> Arduino Int
analogRead Pin
pot
                    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
cur forall a. Eq a => a -> a -> Bool
/= Int
new) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> IO ()
print Int
new
                    Int -> Arduino b
go Int
new