{-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -- | Symantic for @If@. module Language.Symantic.Lib.If where import qualified Data.Text as Text import Language.Symantic import Language.Symantic.Lib.Bool (tyBool) import Language.Symantic.Lib.Function (a0) -- * Type 'If' data If -- * Class 'Sym_If' type instance Sym If = Sym_If class Sym_If term where if_ :: term Bool -> term a -> term a -> term a default if_ :: Sym_If (UnT term) => Trans term => term Bool -> term a -> term a -> term a if_ = trans3 if_ -- Interpreting instance Sym_If Eval where if_ (Eval b) ok ko = if b then ok else ko instance Sym_If View where if_ (View cond) (View ok) (View ko) = View $ \po v -> parenInfix po op $ Text.concat [ "if ", cond (op, SideL) v , " then ", ok (op, SideL) v , " else ", ko (op, SideL) v ] where op = infixN 2 instance (Sym_If r1, Sym_If r2) => Sym_If (Dup r1 r2) where if_ = dup3 @Sym_If if_ -- Transforming instance (Sym_If term, Sym_Lambda term) => Sym_If (BetaT term) -- Typing instance NameTyOf If where nameTyOf _c = ["If"] `Mod` "If" instance ClassInstancesFor If instance TypeInstancesFor If -- Compiling instance Gram_Term_AtomsFor src ss g If -- TODO: some support for if-then-else or ternary (?:) operator instance ModuleFor src ss If -- ** 'Type's -- ** 'Term's teIf_if :: TermDef If '[Proxy a] (() #> (Bool -> a -> a -> a)) teIf_if = Term noConstraint (tyBool ~> a0 ~> a0 ~> a0) $ teSym @If $ lam3 if_