{-# LANGUAGE OverloadedStrings #-}

module Tesla.Car.Command.Windows (
  ventWindows, closeWindows, ventSunroof, closeSunroof
  ) where

import           Control.Monad.IO.Class (MonadIO (..))
import           Data.Text              (Text)
import           Network.Wreq           (FormParam (..))

import           Tesla.Car.Command

windowControl :: MonadIO m => Text -> (Double, Double) -> Car m CommandResponse
windowControl :: forall (m :: * -> *).
MonadIO m =>
Text -> (Double, Double) -> Car m CommandResponse
windowControl Text
x (Double
lat,Double
lon) = forall (m :: * -> *) p.
(MonadIO m, Postable p) =>
String -> p -> Car m CommandResponse
runCmd String
"window_control" [ ByteString
"command" forall v. FormValue v => ByteString -> v -> FormParam
:= Text
x, ByteString
"lat" forall v. FormValue v => ByteString -> v -> FormParam
:= Double
lat, ByteString
"lon" forall v. FormValue v => ByteString -> v -> FormParam
:= Double
lon]

ventWindows :: MonadIO m => Car m CommandResponse
ventWindows :: forall (m :: * -> *). MonadIO m => Car m CommandResponse
ventWindows = forall (m :: * -> *).
MonadIO m =>
Text -> (Double, Double) -> Car m CommandResponse
windowControl Text
"vent" (Double
0,Double
0)

closeWindows :: MonadIO m => (Double, Double) -> Car m CommandResponse
closeWindows :: forall (m :: * -> *).
MonadIO m =>
(Double, Double) -> Car m CommandResponse
closeWindows = forall (m :: * -> *).
MonadIO m =>
Text -> (Double, Double) -> Car m CommandResponse
windowControl Text
"close"

sc :: MonadIO m => Text -> Car m CommandResponse
sc :: forall (m :: * -> *). MonadIO m => Text -> Car m CommandResponse
sc Text
c = forall (m :: * -> *) p.
(MonadIO m, Postable p) =>
String -> p -> Car m CommandResponse
runCmd String
"sun_roof_control" [ ByteString
"state" forall v. FormValue v => ByteString -> v -> FormParam
:= Text
c ]

ventSunroof :: MonadIO m => Car m CommandResponse
ventSunroof :: forall (m :: * -> *). MonadIO m => Car m CommandResponse
ventSunroof = forall (m :: * -> *). MonadIO m => Text -> Car m CommandResponse
sc Text
"vent"

closeSunroof :: MonadIO m => Car m CommandResponse
closeSunroof :: forall (m :: * -> *). MonadIO m => Car m CommandResponse
closeSunroof = forall (m :: * -> *). MonadIO m => Text -> Car m CommandResponse
sc Text
"close"