never executed always true always false
1 {-# LANGUAGE DeriveGeneric, DeriveDataTypeable, DeriveFunctor, DeriveTraversable, DeriveFoldable #-}
2
3 module Conjure.Language.Expression.Op.CatchUndef where
4
5 import Conjure.Prelude
6 import Conjure.Language.Expression.Op.Internal.Common
7
8 import qualified Data.Aeson as JSON -- aeson
9 import qualified Data.Aeson.KeyMap as KM
10
11 import qualified Data.Vector as V -- vector
12
13
14 -- | Two arguments:
15 -- 1st: In-Value
16 -- 2nd: Default
17 -- Evaluates to: In-Value if it is defined
18 -- Default if In-Value is undefined
19 data OpCatchUndef x = OpCatchUndef x x
20 deriving (Eq, Ord, Show, Data, Functor, Traversable, Foldable, Typeable, Generic)
21
22 instance Serialize x => Serialize (OpCatchUndef x)
23 instance Hashable x => Hashable (OpCatchUndef x)
24 instance ToJSON x => ToJSON (OpCatchUndef x) where toJSON = genericToJSON jsonOptions
25 instance FromJSON x => FromJSON (OpCatchUndef x) where parseJSON = genericParseJSON jsonOptions
26
27 instance (TypeOf x, Pretty x) => TypeOf (OpCatchUndef x) where
28 typeOf p@(OpCatchUndef x d) = do
29 tyX <- typeOf x
30 tyD <- typeOf d
31 if typesUnify [tyX, tyD]
32 then return (mostDefined [tyX, tyD])
33 else raiseTypeError p
34
35 instance SimplifyOp OpCatchUndef x where
36 simplifyOp _ = na "simplifyOp{OpCatchUndef}"
37
38 instance Pretty x => Pretty (OpCatchUndef x) where
39 prettyPrec _ (OpCatchUndef a b) = "catchUndef" <> prettyList prParens "," [a, b]
40
41 instance (VarSymBreakingDescription x, ExpressionLike x) => VarSymBreakingDescription (OpCatchUndef x) where
42 varSymBreakingDescription (OpCatchUndef x y) = JSON.Object $ KM.fromList
43 [ ("type", JSON.String "OpCatchUndef")
44 , ("children", JSON.Array $ V.fromList [ varSymBreakingDescription x
45 , varSymBreakingDescription y
46 ])
47 ]