-------------------------------------------------------------------------------
-- |
-- Module      :  System.Hardware.Arduino.SamplePrograms.JingleBells
-- Copyright   :  (c) Levent Erkok
-- License     :  BSD3
-- Maintainer  :  erkokl@gmail.com
-- Stability   :  experimental
--
-- A (pretty bad!) rendering of Jingle Bells on a piezo speaker
-------------------------------------------------------------------------------

module System.Hardware.Arduino.SamplePrograms.JingleBells where

import System.Hardware.Arduino
import System.Hardware.Arduino.Parts.Piezo

-- | Notes for jingle-bells. Expecting a nice rendering from this encoding
-- on a piezo speaker would be naive.. However, it's still recognizable!
jingleBells :: [(Note, Duration)]
jingleBells :: [(Note, Duration)]
jingleBells =  [(Note, Duration)]
m1 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m1 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m3 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m4 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
wait forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m5 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m6 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m7 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m8 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
wait
            forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m1 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m1 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m3 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m4 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
wait forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m5 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m6 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m15 forall a. [a] -> [a] -> [a]
++ [(Note, Duration)]
m16
  where m1 :: [(Note, Duration)]
m1   = [(Note
E, Duration
Quarter), (Note
E, Duration
Quarter), (Note
E, Duration
Half)]
        m3 :: [(Note, Duration)]
m3   = [(Note
E, Duration
Quarter), (Note
G, Duration
Quarter), (Note
C, Duration
Quarter), (Note
D, Duration
Quarter)]
        m4 :: [(Note, Duration)]
m4   = [(Note
E, Duration
Whole)]
        m5 :: [(Note, Duration)]
m5   = forall a. Int -> a -> [a]
replicate Int
4 (Note
F, Duration
Quarter)
        m6 :: [(Note, Duration)]
m6   = (Note
F, Duration
Quarter) forall a. a -> [a] -> [a]
: forall a. Int -> a -> [a]
replicate Int
3 (Note
E, Duration
Quarter)
        m7 :: [(Note, Duration)]
m7   = [(Note
E, Duration
Quarter), (Note
D, Duration
Quarter), (Note
D, Duration
Quarter), (Note
E, Duration
Quarter)]
        m8 :: [(Note, Duration)]
m8   = [(Note
D, Duration
Half), (Note
G, Duration
Half)]
        m15 :: [(Note, Duration)]
m15  = [(Note
G, Duration
Quarter), (Note
G, Duration
Quarter), (Note
F, Duration
Quarter), (Note
D, Duration
Quarter)]
        m16 :: [(Note, Duration)]
m16  = [(Note
C, Duration
Whole)]
        wait :: [(Note, Duration)]
wait = [(Note
R, Duration
Half)]

-- | Play the jingle-bells on a PWM line, attached to pin 3. We use a 
-- tempo of @75@; which is fairly fast. For a slower rendring try @150@
-- or higher values.
--
-- The circuit simple has a piezo speaker attached to pin 3.
--
--  <<http://github.com/LeventErkok/hArduino/raw/master/System/Hardware/Arduino/SamplePrograms/Schematics/Piezo.png>>
main :: IO ()
main :: IO ()
main = Bool -> FilePath -> Arduino () -> IO ()
withArduino Bool
False FilePath
"/dev/cu.usbmodemFD131" forall a b. (a -> b) -> a -> b
$ do
                Piezo
pz <- Int -> Pin -> Arduino Piezo
speaker Int
75 (Word8 -> Pin
pin Word8
3)
                Piezo -> [(Note, Duration)] -> Arduino ()
playNotes Piezo
pz [(Note, Duration)]
jingleBells