never executed always true always false
1 {-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-}
2 {-# LANGUAGE UndecidableInstances #-}
3
4 module Conjure.Language.Expression.Op.Or 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 OpOr x = OpOr x
16 deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic)
17
18 instance Serialize x => Serialize (OpOr x)
19 instance Hashable x => Hashable (OpOr x)
20 instance ToJSON x => ToJSON (OpOr x) where toJSON = genericToJSON jsonOptions
21 instance FromJSON x => FromJSON (OpOr x) where parseJSON = genericParseJSON jsonOptions
22
23 instance BinaryOperator (OpOr x) where
24 opLexeme _ = L_Or
25
26 instance (TypeOf x, Pretty x, ExpressionLike x) => TypeOf (OpOr x) where
27 typeOf p@(OpOr 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 _ -> raiseTypeError $ vcat [ pretty p
37 , "The argument has type:" <+> pretty ty
38 ]
39
40 instance (OpOr x :< x) => SimplifyOp OpOr x where
41 simplifyOp (OpOr x)
42 | Just xs <- listOut x
43 , let filtered = filter (/= fromBool True) xs
44 , length filtered /= length xs -- there were true's
45 = return $ fromBool True
46 simplifyOp (OpOr x)
47 | Just xs <- listOut x
48 , let filtered = filter (/= fromBool False) xs
49 , length filtered /= length xs -- there were false's
50 = return $ inject $ OpOr $ fromList filtered
51 simplifyOp _ = na "simplifyOp{OpOr}"
52
53 instance (Pretty x, ExpressionLike x) => Pretty (OpOr x) where
54 prettyPrec prec op@(OpOr x) | Just [a,b] <- listOut x = prettyPrecBinOp prec [op] a b
55 prettyPrec _ (OpOr x) = "or" <> prParens (pretty x)
56
57 instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (OpOr x) where
58 varSymBreakingDescription (OpOr x) | Just xs <- listOut x = JSON.Object $ KM.fromList
59 [ ("type", JSON.String "OpOr")
60 , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription xs)
61 , ("symmetricChildren", JSON.Bool True)
62 ]
63 varSymBreakingDescription (OpOr x) = JSON.Object $ KM.fromList
64 [ ("type", JSON.String "OpOr")
65 , ("children", varSymBreakingDescription x)
66 ]