never executed always true always false
1 {-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-}
2 {-# LANGUAGE UndecidableInstances #-}
3
4 module Conjure.Language.Expression.Op.Product 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 OpProduct x = OpProduct x
16 deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic)
17
18 instance Serialize x => Serialize (OpProduct x)
19 instance Hashable x => Hashable (OpProduct x)
20 instance ToJSON x => ToJSON (OpProduct x) where toJSON = genericToJSON jsonOptions
21 instance FromJSON x => FromJSON (OpProduct x) where parseJSON = genericParseJSON jsonOptions
22
23 instance (TypeOf x, Pretty x, ExpressionLike x) => TypeOf (OpProduct x) where
24 typeOf p@(OpProduct x) = do
25 ty <- typeOf x
26 innerTy <- case ty of
27 TypeList t -> return t
28 TypeMatrix _ t -> return t
29 TypeSet t -> return t
30 TypeMSet t -> return t
31 _ -> raiseTypeError $ vcat [ pretty p
32 , "The argument has type:" <+> pretty ty
33 ]
34 case innerTy of
35 TypeAny | Just [] <- listOut x -> return (TypeInt TagInt)
36 TypeInt t | ?typeCheckerMode == RelaxedIntegerTags -> return (TypeInt t)
37 TypeInt TagInt -> return (TypeInt TagInt)
38 _ -> raiseTypeError $ vcat [ pretty p
39 , "The argument has type:" <+> pretty ty
40 ]
41
42 instance BinaryOperator (OpProduct x) where
43 opLexeme _ = L_Times
44
45 instance (OpProduct x :< x) => SimplifyOp OpProduct x where
46 simplifyOp (OpProduct x)
47 | Just xs <- listOut x
48 , let filtered = filter (/=0) xs
49 , length filtered /= length xs -- there were 0's
50 = return 0
51 simplifyOp (OpProduct x)
52 | Just xs <- listOut x
53 , let filtered = filter (/=1) xs
54 , length filtered /= length xs -- there were 1's
55 = case filtered of
56 [] -> return 1
57 [n] -> return n
58 _ -> return $ inject $ OpProduct $ fromList filtered
59 simplifyOp _ = na "simplifyOp{OpProduct}"
60
61 instance (Pretty x, ExpressionLike x) => Pretty (OpProduct x) where
62 prettyPrec prec op@(OpProduct x) | Just [a,b] <- listOut x = prettyPrecBinOp prec [op] a b
63 prettyPrec _ (OpProduct x) = "product" <> prParens (pretty x)
64
65 instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (OpProduct x) where
66 varSymBreakingDescription (OpProduct x) | Just xs <- listOut x = JSON.Object $ KM.fromList
67 [ ("type", JSON.String "OpProduct")
68 , ("children", JSON.Array $ V.fromList $ map varSymBreakingDescription xs)
69 , ("symmetricChildren", JSON.Bool True)
70 ]
71 varSymBreakingDescription (OpProduct x) = JSON.Object $ KM.fromList
72 [ ("type", JSON.String "OpProduct")
73 , ("children", varSymBreakingDescription x)
74 ]