{-# LANGUAGE OverloadedStrings #-} module Main where import Data.Conduit.RemoteOp (remoteOp, sshargs) import Data.Monoid ((<>)) import Data.String.Conversions import qualified Data.Text as T import Network.OnRmt import Test.Framework import Test.Framework.Providers.HUnit import Test.HUnit main = defaultMain tests tests = [ testGroup "Parameters" [ testCase "App Name Parameter" test_an0 , testCase "Parallelization Parameter" test_an1 , testCase "Direct SSH Parameter" test_an2 ] , testGroup "RemoteOps" [ testCase "SSH Direct Args" test_ro0 , testCase "SSH Bounce Args" test_ro1 -- testCase "remote echo" test_ro1 ] ] test_an0 = "test app" @=? (appName $ OnRmtParams "test app" 0 False) test_an1 = 0 @=? (maxParallel $ OnRmtParams "test app" 0 False) test_an2 = False @=? (directSSH $ OnRmtParams "test app" 0 False) common_ssh_args = [ "-A" , "-o", "ControlPath none" , "-o", "VisualHostKey no" , "-o", "KbdInteractiveAuthentication no" , "-o", "StrictHostKeyChecking no" , "-o", "CheckHostIP no" , "-o", "ForwardX11 no" , "-o", "ForwardX11Trusted no" ] test_ro0 = common_ssh_args <> ["hostname", "foo\nbar\n"] @=? sshargs True "hostname" ["foo", "bar"] test_ro1 = [ "-t", "-t" ] <> common_ssh_args <> [ "localhost", "ssh", "'-A'" , "'-o'", "'ControlPath none'" , "'-o'", "'VisualHostKey no'" , "'-o'", "'KbdInteractiveAuthentication no'" , "'-o'", "'StrictHostKeyChecking no'" , "'-o'", "'CheckHostIP no'" , "'-o'", "'ForwardX11 no'" , "'-o'", "'ForwardX11Trusted no'" , "host-name", "hi\n"] @=? sshargs False "host-name" ["hi"] -- test_ro1 = "howdy ho" @=? remoteOp "localhost" "echo howdy ho" foo