{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}
module Language.LSP.Types.Common where
import Control.Applicative
import Control.DeepSeq
import Data.Aeson
import GHC.Generics
data a |? b = InL a
| InR b
deriving (Read,Show,Eq,Ord,Generic)
infixr |?
toEither :: a |? b -> Either a b
toEither (InL a) = Left a
toEither (InR b) = Right b
instance (ToJSON a, ToJSON b) => ToJSON (a |? b) where
toJSON (InL x) = toJSON x
toJSON (InR x) = toJSON x
instance (FromJSON a, FromJSON b) => FromJSON (a |? b) where
parseJSON v = InR <$> parseJSON v <|> InL <$> parseJSON v
instance (NFData a, NFData b) => NFData (a |? b)
newtype List a = List [a]
deriving (Show,Read,Eq,Ord,Semigroup,Monoid,Functor,Foldable,Traversable,Generic)
instance NFData a => NFData (List a)
instance (ToJSON a) => ToJSON (List a) where
toJSON (List ls) = toJSON ls
instance (FromJSON a) => FromJSON (List a) where
parseJSON Null = return (List [])
parseJSON v = List <$> parseJSON v
data Empty = Empty deriving (Eq,Ord,Show)
instance ToJSON Empty where
toJSON Empty = Null
instance FromJSON Empty where
parseJSON Null = pure Empty
parseJSON _ = mempty