{-# LANGUAGE OverloadedStrings #-}

module Tesla.Car.Command.SpeedLimit (
  speedLimit, activateSpeedLimit, deactivateSpeedLimit, clearSpeedLimitPIN
  ) where

import           Control.Monad.IO.Class (MonadIO (..))
import           Network.Wreq           (FormParam (..))
import           Tesla.Car.Command

speedLimit :: MonadIO m => Int -> Car m CommandResponse
speedLimit :: Int -> Car m CommandResponse
speedLimit Int
to = String -> [FormParam] -> Car m CommandResponse
forall (m :: * -> *) p.
(MonadIO m, Postable p) =>
String -> p -> Car m CommandResponse
runCmd String
"speed_limit_set_limit" [ByteString
"limit_mph" ByteString -> Int -> FormParam
forall v. FormValue v => ByteString -> v -> FormParam
:= Int
to ]

speedo :: MonadIO m => String -> Int -> Car m CommandResponse
speedo :: String -> Int -> Car m CommandResponse
speedo String
c Int
pin = String -> [FormParam] -> Car m CommandResponse
forall (m :: * -> *) p.
(MonadIO m, Postable p) =>
String -> p -> Car m CommandResponse
runCmd String
c [ByteString
"pin" ByteString -> Int -> FormParam
forall v. FormValue v => ByteString -> v -> FormParam
:= Int
pin ]

activateSpeedLimit :: MonadIO m => Int -> Car m CommandResponse
activateSpeedLimit :: Int -> Car m CommandResponse
activateSpeedLimit = String -> Int -> Car m CommandResponse
forall (m :: * -> *).
MonadIO m =>
String -> Int -> Car m CommandResponse
speedo String
"speed_limit_activate"

deactivateSpeedLimit :: MonadIO m => Int -> Car m CommandResponse
deactivateSpeedLimit :: Int -> Car m CommandResponse
deactivateSpeedLimit = String -> Int -> Car m CommandResponse
forall (m :: * -> *).
MonadIO m =>
String -> Int -> Car m CommandResponse
speedo String
"speed_limit_deactivate"

clearSpeedLimitPIN :: MonadIO m => Int -> Car m CommandResponse
clearSpeedLimitPIN :: Int -> Car m CommandResponse
clearSpeedLimitPIN = String -> Int -> Car m CommandResponse
forall (m :: * -> *).
MonadIO m =>
String -> Int -> Car m CommandResponse
speedo String
"speed_limit_clear_pin"