{-# 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 :: forall (m :: * -> *). MonadIO m => Int -> Car m CommandResponse speedLimit Int to = forall (m :: * -> *) p. (MonadIO m, Postable p) => String -> p -> Car m CommandResponse runCmd String "speed_limit_set_limit" [ByteString "limit_mph" forall v. FormValue v => ByteString -> v -> FormParam := Int to ] speedo :: MonadIO m => String -> Int -> Car m CommandResponse speedo :: forall (m :: * -> *). MonadIO m => String -> Int -> Car m CommandResponse speedo String c Int pin = forall (m :: * -> *) p. (MonadIO m, Postable p) => String -> p -> Car m CommandResponse runCmd String c [ByteString "pin" forall v. FormValue v => ByteString -> v -> FormParam := Int pin ] activateSpeedLimit :: MonadIO m => Int -> Car m CommandResponse activateSpeedLimit :: forall (m :: * -> *). MonadIO m => Int -> Car m CommandResponse activateSpeedLimit = forall (m :: * -> *). MonadIO m => String -> Int -> Car m CommandResponse speedo String "speed_limit_activate" deactivateSpeedLimit :: MonadIO m => Int -> Car m CommandResponse deactivateSpeedLimit :: forall (m :: * -> *). MonadIO m => Int -> Car m CommandResponse deactivateSpeedLimit = forall (m :: * -> *). MonadIO m => String -> Int -> Car m CommandResponse speedo String "speed_limit_deactivate" clearSpeedLimitPIN :: MonadIO m => Int -> Car m CommandResponse clearSpeedLimitPIN :: forall (m :: * -> *). MonadIO m => Int -> Car m CommandResponse clearSpeedLimitPIN = forall (m :: * -> *). MonadIO m => String -> Int -> Car m CommandResponse speedo String "speed_limit_clear_pin"