Use orphan Ord instance for Value
This commit is contained in:
parent
8b6ebce8e7
commit
017a9402fe
|
@ -1,5 +1,5 @@
|
||||||
{-# LANGUAGE DuplicateRecordFields, OverloadedLists, StrictData #-}
|
{-# LANGUAGE DuplicateRecordFields, OverloadedLists, StrictData #-}
|
||||||
{-# OPTIONS_GHC -Wall #-}
|
{-# OPTIONS_GHC -Wall -Wno-orphans #-}
|
||||||
module Data.Language.Ruby.AST
|
module Data.Language.Ruby.AST
|
||||||
( Begin(..)
|
( Begin(..)
|
||||||
, Statement(..)
|
, Statement(..)
|
||||||
|
@ -30,8 +30,6 @@ import Frelude hiding (String)
|
||||||
import qualified Frelude
|
import qualified Frelude
|
||||||
import qualified Data.Aeson.Types as Aeson
|
import qualified Data.Aeson.Types as Aeson
|
||||||
import qualified Data.Vector as Vector
|
import qualified Data.Vector as Vector
|
||||||
import Data.Coerce
|
|
||||||
import Data.Word
|
|
||||||
|
|
||||||
kebabCase :: Frelude.String -> Frelude.String
|
kebabCase :: Frelude.String -> Frelude.String
|
||||||
kebabCase = Aeson.camelTo2 '-'
|
kebabCase = Aeson.camelTo2 '-'
|
||||||
|
@ -166,8 +164,7 @@ instance FromJSON Array where
|
||||||
newtype Anything = Anything Value
|
newtype Anything = Anything Value
|
||||||
|
|
||||||
deriving stock instance Show Anything
|
deriving stock instance Show Anything
|
||||||
instance Ord Anything where
|
deriving stock instance Ord Anything
|
||||||
compare = coerce compareValue
|
|
||||||
deriving stock instance Eq Anything
|
deriving stock instance Eq Anything
|
||||||
deriving stock instance Generic Anything
|
deriving stock instance Generic Anything
|
||||||
instance ToJSON Anything where
|
instance ToJSON Anything where
|
||||||
|
@ -369,27 +366,7 @@ instance FromJSON Defs where
|
||||||
<*> parseMaybe begin
|
<*> parseMaybe begin
|
||||||
_ -> empty
|
_ -> empty
|
||||||
|
|
||||||
compareValue :: Aeson.Value -> Aeson.Value -> Ordering
|
deriving stock instance Ord Aeson.Value
|
||||||
compareValue v0 v1 = case (v0, v1) of
|
|
||||||
(Object o0, Object o1) -> mconcat $ zipWith go (toList o0) (toList o1)
|
|
||||||
where
|
|
||||||
go (t0, v0') (t1, v1') = compare t0 t1 <> compareValue v0' v1'
|
|
||||||
(Aeson.Array a0, Aeson.Array a1) -> mconcat $ zipWith compareValue (toList a0) (toList a1)
|
|
||||||
(Aeson.String s0, Aeson.String s1) -> compare s0 s1
|
|
||||||
(Number n0, Number n1) -> compare n0 n1
|
|
||||||
(Bool b0, Bool b1) -> compare b0 b1
|
|
||||||
(Null, Null) -> EQ
|
|
||||||
_ -> (compare `on` cons) v0 v1
|
|
||||||
where
|
|
||||||
-- Enumerate constructors.
|
|
||||||
cons :: Aeson.Value -> Word8
|
|
||||||
cons = \case
|
|
||||||
Object{} -> 0
|
|
||||||
Aeson.Array{} -> 1
|
|
||||||
Aeson.String{} -> 2
|
|
||||||
Number{} -> 3
|
|
||||||
Bool{} -> 4
|
|
||||||
Null{} -> 5
|
|
||||||
|
|
||||||
newtype Sym = Sym Atom
|
newtype Sym = Sym Atom
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue