{-# LANGUAGE OverloadedStrings #-}

{- |
Module      : Network.MPD.Commands.Mount
Copyright   : (c) Joachim Fasting 2014
License     : MIT

Maintainer  : joachifm@fastmail.fm
Stability   : stable
Portability : unportable

Mounting remote storage.
-}

module Network.MPD.Commands.Mount
  ( mount
  , unmount
  , listMounts
  , listNeighbors
  ) where

import qualified Network.MPD.Applicative.Internal as A
import qualified Network.MPD.Applicative.Mount as A
import           Network.MPD.Core

mount :: (MonadMPD m) => String -> String -> m ()
mount :: String -> String -> m ()
mount String
p = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (String -> Command ()) -> String -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> Command ()
A.mount String
p

unmount :: (MonadMPD m) => String -> m ()
unmount :: String -> m ()
unmount = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (String -> Command ()) -> String -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Command ()
A.unmount

listMounts :: (MonadMPD m) => m [(String, String)]
listMounts :: m [(String, String)]
listMounts = Command [(String, String)] -> m [(String, String)]
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command [(String, String)]
A.listMounts

listNeighbors :: (MonadMPD m) => m [(String, String)]
listNeighbors :: m [(String, String)]
listNeighbors = Command [(String, String)] -> m [(String, String)]
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command [(String, String)]
A.listNeighbors