{-# LINE 1 "src/Gpu/Vulkan/Exception/Middle/Internal.hsc" #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE ExistentialQuantification #-} {-# OPTIONS_GHC -Wall -fno-warn-tabs -fno-warn-orphans #-} module Gpu.Vulkan.Exception.Middle.Internal where import Control.Exception import Control.Exception.Hierarchy import Data.List.NonEmpty (NonEmpty, nonEmpty) import Gpu.Vulkan.Exception.Enum data MultiResult = MultiResult (NonEmpty (Int, Result)) deriving Int -> MultiResult -> ShowS [MultiResult] -> ShowS MultiResult -> String (Int -> MultiResult -> ShowS) -> (MultiResult -> String) -> ([MultiResult] -> ShowS) -> Show MultiResult forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> MultiResult -> ShowS showsPrec :: Int -> MultiResult -> ShowS $cshow :: MultiResult -> String show :: MultiResult -> String $cshowList :: [MultiResult] -> ShowS showList :: [MultiResult] -> ShowS Show exceptionHierarchy Nothing $ ExNode "E" [ ExType ''Result, ExType ''MultiResult ] throwUnlessSuccess :: Result -> IO () throwUnlessSuccess :: Result -> IO () throwUnlessSuccess = [Result] -> Result -> IO () throwUnless [Result Success] throwUnless :: [Result] -> Result -> IO () throwUnless :: [Result] -> Result -> IO () throwUnless [Result] sccs Result r | Result r Result -> [Result] -> Bool forall a. Eq a => a -> [a] -> Bool forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool `elem` [Result] sccs = () -> IO () forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pure () | Bool otherwise = Result -> IO () forall a e. (?callStack::CallStack, Exception e) => e -> a throw Result r throwUnlessSuccesses :: [Result] -> IO () throwUnlessSuccesses :: [Result] -> IO () throwUnlessSuccesses = [Result] -> [Result] -> IO () throwUnlesses [Result Success] throwUnlesses :: [Result] -> [Result] -> IO () throwUnlesses :: [Result] -> [Result] -> IO () throwUnlesses [Result] sccs [Result] rs = do let irs :: [(Int, Result)] irs = [Int] -> [Result] -> [(Int, Result)] forall a b. [a] -> [b] -> [(a, b)] zip [Int 0 ..] [Result] rs irs' :: [(Int, Result)] irs' = ((Int, Result) -> Bool) -> [(Int, Result)] -> [(Int, Result)] forall a. (a -> Bool) -> [a] -> [a] filter ((Result -> [Result] -> Bool forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool `notElem` [Result] sccs) (Result -> Bool) -> ((Int, Result) -> Result) -> (Int, Result) -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c . (Int, Result) -> Result forall a b. (a, b) -> b snd) [(Int, Result)] irs case [(Int, Result)] -> Maybe (NonEmpty (Int, Result)) forall a. [a] -> Maybe (NonEmpty a) nonEmpty [(Int, Result)] irs' of Maybe (NonEmpty (Int, Result)) Nothing -> () -> IO () forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pure () Just NonEmpty (Int, Result) r -> MultiResult -> IO () forall a e. (?callStack::CallStack, Exception e) => e -> a throw (MultiResult -> IO ()) -> MultiResult -> IO () forall a b. (a -> b) -> a -> b $ NonEmpty (Int, Result) -> MultiResult MultiResult NonEmpty (Int, Result) r