{-# LANGUAGE StandaloneDeriving #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Dhall.Syntax.Instances.Ord () where
import Dhall.Syntax.Binding
import Dhall.Syntax.Chunks
import Dhall.Syntax.Const
import Dhall.Syntax.Expr
import Dhall.Syntax.FunctionBinding
import Dhall.Syntax.Import
import Dhall.Syntax.Instances.Eq ()
import Dhall.Syntax.RecordField
import Dhall.Syntax.Types
import Dhall.Syntax.Var
deriving instance Ord Const
deriving instance Ord Var
deriving instance (Ord s, Ord a) => Ord (Binding s a)
deriving instance (Ord s, Ord a) => Ord (Chunks s a)
deriving instance Ord PreferAnnotation
deriving instance (Ord s, Ord a) => Ord (RecordField s a)
deriving instance (Ord s, Ord a) => Ord (FunctionBinding s a)
deriving instance Ord s => Ord (FieldSelection s)
deriving instance Ord WithComponent
deriving instance (Ord s, Ord a) => Ord (Expr s a)
deriving instance Ord Directory
deriving instance Ord File
deriving instance Ord FilePrefix
deriving instance Ord Scheme
deriving instance Ord URL
deriving instance Ord ImportType
deriving instance Ord ImportMode
deriving instance Ord ImportHashed
deriving instance Ord Import
instance Ord DhallDouble where
compare :: DhallDouble -> DhallDouble -> Ordering
compare a :: DhallDouble
a@(DhallDouble Double
a') b :: DhallDouble
b@(DhallDouble Double
b') =
if DhallDouble
a forall a. Eq a => a -> a -> Bool
== DhallDouble
b
then Ordering
EQ
else forall a. Ord a => a -> a -> Ordering
compare Double
a' Double
b'