1 {-# LANGUAGE UndecidableInstances #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 -- | Symantic for @If@.
4 module Language.Symantic.Lib.If where
6 import qualified Data.Text as Text
8 import Language.Symantic
9 import Language.Symantic.Lib.Bool (tyBool)
10 import Language.Symantic.Lib.Function (a0)
16 type instance Sym (Proxy If) = Sym_If
17 class Sym_If term where
18 if_ :: term Bool -> term a -> term a -> term a
19 default if_ :: Sym_If (UnT term) => Trans term => term Bool -> term a -> term a -> term a
23 instance Sym_If Eval where
24 if_ (Eval b) ok ko = if b then ok else ko
25 instance Sym_If View where
26 if_ (View cond) (View ok) (View ko) =
30 [ "if ", cond (op, SideL) v
31 , " then ", ok (op, SideL) v
32 , " else ", ko (op, SideL) v ]
34 instance (Sym_If r1, Sym_If r2) => Sym_If (Dup r1 r2) where
35 if_ = dup3 @Sym_If if_
38 instance (Sym_If term, Sym_Lambda term) => Sym_If (BetaT term)
41 instance ClassInstancesFor If
42 instance TypeInstancesFor If
45 instance Module src ss If
46 instance Gram_Term_AtomsFor src ss g If
47 -- TODO: some support for if-then-else or ternary (?:) operator
52 teIf_if :: TermDef If '[Proxy a] (Bool -> a -> a -> a)
53 teIf_if = Term noConstraint (tyBool ~> a0 ~> a0 ~> a0) $ teSym @If $ lam3 if_