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