never executed always true always false
    1 {-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-}
    2 {-# LANGUAGE UndecidableInstances #-}
    3 
    4 module Conjure.Language.Expression.Op.And where
    5 
    6 import Conjure.Prelude
    7 import Conjure.Language.Expression.Op.Internal.Common
    8 
    9 import qualified Data.Aeson as JSON             -- aeson
   10 import qualified Data.Aeson.KeyMap as KM
   11 
   12 import qualified Data.Vector as V               -- vector
   13 
   14 
   15 data OpAnd x = OpAnd x
   16     deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic)
   17 
   18 instance Serialize x => Serialize (OpAnd x)
   19 instance Hashable  x => Hashable  (OpAnd x)
   20 instance ToJSON    x => ToJSON    (OpAnd x) where toJSON = genericToJSON jsonOptions
   21 instance FromJSON  x => FromJSON  (OpAnd x) where parseJSON = genericParseJSON jsonOptions
   22 
   23 instance BinaryOperator (OpAnd x) where
   24     opLexeme _ = L_And
   25 
   26 instance (TypeOf x, Pretty x, ExpressionLike x) => TypeOf (OpAnd x) where
   27     typeOf p@(OpAnd x) = do
   28         ty <- typeOf x
   29         case ty of
   30             TypeList TypeAny -> return TypeBool
   31             TypeList TypeBool -> return TypeBool
   32             TypeMatrix _ TypeAny -> return TypeBool
   33             TypeMatrix _ TypeBool -> return TypeBool
   34             TypeSet TypeBool -> return TypeBool
   35             TypeMSet TypeBool -> return TypeBool
   36             TypeAny -> return TypeBool
   37             _ -> raiseTypeError $ vcat [ pretty p
   38                                        , "The argument has type:" <+> pretty ty
   39                                        ]
   40 
   41 instance (OpAnd x :< x) => SimplifyOp OpAnd x where
   42     simplifyOp (OpAnd x)
   43         | Just xs <- listOut x
   44         , let filtered = filter (/= fromBool False) xs
   45         , length filtered /= length xs      -- there were false's
   46         = return $ fromBool False
   47     simplifyOp (OpAnd x)
   48         | Just xs <- listOut x
   49         , let filtered = filter (/= fromBool True) xs
   50         , length filtered /= length xs      -- there were true's
   51         = return $ inject $ OpAnd $ fromList filtered
   52     simplifyOp _ = na "simplifyOp{OpAnd}"
   53 
   54 instance (Pretty x, ExpressionLike x) => Pretty (OpAnd x) where
   55     prettyPrec prec op@(OpAnd x) | Just [a,b] <- listOut x = prettyPrecBinOp prec [op] a b
   56     prettyPrec _ (OpAnd x) = "and" <> prParens (pretty x)
   57 
   58 instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (OpAnd x) where
   59     varSymBreakingDescription (OpAnd x) | Just xs <- listOut x = JSON.Object $ KM.fromList
   60         [ ("type", JSON.String "OpAnd")
   61         , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription xs)
   62         , ("symmetricChildren", JSON.Bool True)
   63         ]
   64     varSymBreakingDescription (OpAnd x) = JSON.Object $ KM.fromList
   65         [ ("type", JSON.String "OpAnd")
   66         , ("children", varSymBreakingDescription x)
   67         ]