Test.hs (4530B)
1 #!/usr/bin/env nix-shell 2 #!nix-shell -i runhaskell -p "haskellPackages.ghcWithPackages(p: with p; [hspec process])" -p nix 3 {-# LANGUAGE OverloadedStrings #-} 4 import Test.Hspec 5 import System.Process 6 import qualified Data.Text as Text 7 import Data.Text (Text) 8 import Control.Monad.IO.Class (liftIO) 9 import Data.List (find) 10 11 -- nixos-19-09 is used so hopefully it will have a different libc than 12 -- the current `<nixpkgs>` used in a current nixOS system, so it will trigger the 13 -- driver failure. 14 -- Run `./Test.hs --match "/Sanity/"` to ensure that non wrapped 15 -- binaries fails on NixOS. 16 17 currentChannel = "channel:nixos-19.09-small" 18 19 -- | Utils function: run a command and returns its output. 20 processOutput p args = Text.strip . Text.pack <$> readCreateProcess ((proc (Text.unpack p) (Text.unpack <$> args)) { std_err = Inherit }) "" 21 22 -- * OpenGL 23 24 -- | Returns the path to the nixGLXXX binary. 25 getNixGLBin version = (<>("/bin/"<>version)) <$> processOutput "nix-build" ["./", "-A", version, "-I", "nixpkgs=" <> currentChannel] 26 27 -- | Returns the vendor string associated with a glxinfo wrapped by a nixGL. 28 getVendorString io = do 29 output <- Text.lines <$> io 30 pure $ Text.unpack <$> find ("OpenGL version string"`Text.isPrefixOf`) output 31 32 -- | Checks that a nixGL wrapper works with glxinfo 32 & 64 bits. 33 checkOpenGL_32_64 glxinfo32 glxinfo64 vendorName nixGLName = do 34 beforeAll (getNixGLBin nixGLName) $ do 35 it "32 bits" $ \nixGLBin -> do 36 Just vendorString <- getVendorString (processOutput nixGLBin [glxinfo32, "-B"]) 37 vendorString `shouldContain` vendorName 38 39 it "64 bits" $ \nixGLBin -> do 40 Just vendorString <- getVendorString (processOutput nixGLBin [glxinfo64, "-B"]) 41 vendorString `shouldContain` vendorName 42 43 -- * Vulkan 44 45 -- | Heuristic to detect if vulkan work. `driverName` must appears in the output 46 checkVulkanIsWorking io = do 47 res <- io 48 res `shouldSatisfy` ("driverName"`Text.isInfixOf`) 49 50 -- | Checks that a nixGL wrapper works with glxinfo 32 & 64 bits. 51 checkVulkan_32_64 vulkaninfo32 vulkaninfo64 vendorName nixGLName = do 52 beforeAll (getNixGLBin nixGLName) $ do 53 it "32 bits" $ \nixGLBin -> do 54 checkVulkanIsWorking (processOutput nixGLBin [vulkaninfo32]) 55 56 it "64 bits" $ \nixGLBin -> do 57 checkVulkanIsWorking (processOutput nixGLBin [vulkaninfo64]) 58 59 60 main = do 61 putStrLn "Running tests for nixGL" 62 putStrLn "It can take a while, this will build and test all drivers in the background" 63 glxinfo64 <- (<>"/bin/glxinfo") <$> processOutput "nix-build" [currentChannel, "-A", "glxinfo"] 64 glxinfo32 <- (<>"/bin/glxinfo") <$> processOutput "nix-build" [currentChannel, "-A", "pkgsi686Linux.glxinfo"] 65 66 vulkaninfo64 <- (<>"/bin/vulkaninfo") <$> processOutput "nix-build" [currentChannel, "-A", "vulkan-tools"] 67 vulkaninfo32 <- (<>"/bin/vulkaninfo") <$> processOutput "nix-build" [currentChannel, "-A", "pkgsi686Linux.vulkan-tools"] 68 69 let checkOpenGL = checkOpenGL_32_64 glxinfo32 glxinfo64 70 checkVulkan = checkVulkan_32_64 vulkaninfo32 vulkaninfo64 71 72 hspec $ do 73 -- This category ensure that tests are failing if not run with nixGL 74 -- This allows testing on nixOS 75 describe "Sanity" $ do 76 describe "OpenGL" $ do 77 it "fails with unwrapped glxinfo64" $ do 78 vendorString <- getVendorString (processOutput glxinfo64 ["-B"]) 79 vendorString `shouldBe` Nothing 80 81 it "fails with unwrapped glxinfo32" $ do 82 vendorString <- getVendorString (processOutput glxinfo32 ["-B"]) 83 vendorString `shouldBe` Nothing 84 describe "Vulkan" $ do 85 it "fails with unwrapped vulkaninfo64" $ do 86 processOutput vulkaninfo64 [] `shouldThrow` anyIOException 87 88 it "fails with unwrapped vulkaninfo32" $ do 89 processOutput vulkaninfo32 [] `shouldThrow` anyIOException 90 91 describe "NixGL" $ do 92 describe "Mesa" $ do 93 describe "OpenGL" $ do 94 checkOpenGL "Mesa" "nixGLIntel" 95 describe "Vulkan" $ do 96 checkVulkan "Mesa" "nixVulkanIntel" 97 98 describe "Nvidia - Bumblebee" $ do 99 describe "OpenGL" $ do 100 checkOpenGL "NVIDIA" "nixGLNvidiaBumblebee" 101 xdescribe "Vulkan" $ do 102 -- Not tested: I don't have the hardware (@guibou) 103 checkVulkan "NVIDIA" "nixVulkanNvidiaBumblebee" 104 105 -- TODO: check Nvidia (I don't have this hardware) 106 describe "Nvidia" $ do 107 describe "OpenGL" $ do 108 checkOpenGL "NVIDIA" "nixGLNvidia" 109 describe "Vulkan" $ do 110 checkVulkan "NVIDIA" "nixVulkanNvidia"