module OpenCascade.BRepBuilderAPI.WireError
( WireError (..)
) where

-- order must match the definition of BRepBuilderAPI_WireError
data WireError = WireDone | EmptyWire | DisconnectedWire | NonManifoldWire deriving (WireError -> WireError -> Bool
(WireError -> WireError -> Bool)
-> (WireError -> WireError -> Bool) -> Eq WireError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WireError -> WireError -> Bool
== :: WireError -> WireError -> Bool
$c/= :: WireError -> WireError -> Bool
/= :: WireError -> WireError -> Bool
Eq, Int -> WireError
WireError -> Int
WireError -> [WireError]
WireError -> WireError
WireError -> WireError -> [WireError]
WireError -> WireError -> WireError -> [WireError]
(WireError -> WireError)
-> (WireError -> WireError)
-> (Int -> WireError)
-> (WireError -> Int)
-> (WireError -> [WireError])
-> (WireError -> WireError -> [WireError])
-> (WireError -> WireError -> [WireError])
-> (WireError -> WireError -> WireError -> [WireError])
-> Enum WireError
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: WireError -> WireError
succ :: WireError -> WireError
$cpred :: WireError -> WireError
pred :: WireError -> WireError
$ctoEnum :: Int -> WireError
toEnum :: Int -> WireError
$cfromEnum :: WireError -> Int
fromEnum :: WireError -> Int
$cenumFrom :: WireError -> [WireError]
enumFrom :: WireError -> [WireError]
$cenumFromThen :: WireError -> WireError -> [WireError]
enumFromThen :: WireError -> WireError -> [WireError]
$cenumFromTo :: WireError -> WireError -> [WireError]
enumFromTo :: WireError -> WireError -> [WireError]
$cenumFromThenTo :: WireError -> WireError -> WireError -> [WireError]
enumFromThenTo :: WireError -> WireError -> WireError -> [WireError]
Enum)