{-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} -- | Expression for 'Applicative'. module Language.Symantic.Expr.Applicative where import Control.Applicative (Applicative) import Data.Proxy (Proxy(..)) import Data.Type.Equality ((:~:)(Refl)) import Prelude hiding (Applicative(..)) import Language.Symantic.Type import Language.Symantic.Trans.Common import Language.Symantic.Expr.Common import Language.Symantic.Expr.Lambda import Language.Symantic.Expr.Functor -- * Class 'Sym_Applicative' -- | Symantic. class Sym_Applicative repr where pure :: Applicative f => repr a -> repr (f a) -- (*>) :: Applicative f => repr (f a) -> repr (f b) -> repr (f b) -- (<*) :: Applicative f => repr (f a) -> repr (f b) -> repr (f a) default pure :: (Trans t repr, Applicative f) => t repr a -> t repr (f a) pure = trans_map1 pure -- * Class 'Sym_Applicative_Lam' -- | Symantic requiring a 'Lambda'. class Sym_Functor lam repr => Sym_Applicative_Lam lam repr where (<*>) :: Applicative_with_Lambda f => repr (f (Lambda lam a b)) -> repr (f a) -> repr (f b) -- (*>) :: Applicative f => repr (f a) -> repr (f b) -> repr (f b) -- (<*) :: Applicative f => repr (f a) -> repr (f b) -> repr (f a) default (<*>) :: (Trans t repr, Applicative_with_Lambda f) => t repr (f (Lambda lam a b)) -> t repr (f a) -> t repr (f b) -- default (*>) :: (Trans t, Applicative f) => t repr (f a) -> t repr (f b) -> t repr (f b) -- default (<*) :: (Trans t, Applicative f) => t repr (f a) -> t repr (f b) -> t repr (f a) (<*>) = trans_map2 (<*>) infixl 4 <*> -- ** Class 'Applicative_with_Lambda' -- | A class alias to join 'Traversable' to 'Applicative'. -- -- NOTE: see comment of 'Functor_with_Lambda'. class (Applicative f, Traversable f) => Applicative_with_Lambda f instance (Applicative f, Traversable f) => Applicative_with_Lambda f instance Constraint_Type1 Applicative_with_Lambda (Type_Type1 t1 root) instance Constraint_Type1 Applicative_with_Lambda (Type_Type2 c2 t2 root) instance Constraint_Type1 Applicative_with_Lambda (Type_Var root) -- * Type 'Expr_Applicative' -- | Expression. data Expr_Applicative (lam:: * -> *) (root:: *) type instance Root_of_Expr (Expr_Applicative lam root) = root type instance Type_of_Expr (Expr_Applicative lam root) = No_Type type instance Sym_of_Expr (Expr_Applicative lam root) repr = (Sym_Applicative repr, Sym_Applicative_Lam lam repr) type instance Error_of_Expr ast (Expr_Applicative lam root) = No_Error_Expr pure_from :: forall root ty ty_root lam ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_Applicative lam root) , ty_root ~ Type_Root_of_Expr root , Eq_Type (Type_Root_of_Expr root) , Type1_from ast (Type_Root_of_Expr root) , Expr_from ast root , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast) (Error_of_Expr ast root) , Root_of_Expr root ~ root , Constraint_Type1 Applicative_with_Lambda ty ) => ast -> ast -> Expr_From ast (Expr_Applicative lam root) hs ret pure_from ast_f ast_a ex ast ctx k = -- pure :: Applicative f => a -> f a either (\err -> Left $ error_expr ex $ Error_Expr_Type err ast) id $ type1_from (Proxy::Proxy ty_root) ast_f $ \_f ty_f -> Right $ expr_from (Proxy::Proxy root) ast_a ctx $ \(ty_a::Type_Root_of_Expr root h_a) (Forall_Repr_with_Context a) -> let ty_fa = ty_f ty_a in check_constraint1_type ex (Proxy::Proxy Applicative_with_Lambda) ast ty_fa $ \Dict -> k ty_fa $ Forall_Repr_with_Context $ \c -> pure (a c) ltstargt_from :: forall root ty lam ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_Applicative lam root) , String_from_Type ty , Eq_Type (Type_Root_of_Expr root) , Eq_Type1 (Type_Root_of_Expr root) , Expr_from ast root , Lift_Type (Type_Fun lam) (Type_of_Expr root) , Unlift_Type (Type_Fun lam) (Type_of_Expr root) , Unlift_Type1 (Type_of_Expr root) , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast) (Error_of_Expr ast root) , Root_of_Expr root ~ root , Constraint_Type1 Applicative_with_Lambda ty ) => ast -> ast -> Expr_From ast (Expr_Applicative lam root) hs ret ltstargt_from ast_fg ast_fa ex ast ctx k = -- (<*>) :: Applicative f => f (a -> b) -> f a -> f b expr_from (Proxy::Proxy root) ast_fg ctx $ \(ty_fg::Type_Root_of_Expr root h_fg) (Forall_Repr_with_Context fg) -> expr_from (Proxy::Proxy root) ast_fa ctx $ \(ty_fa::Type_Root_of_Expr root h_fa) (Forall_Repr_with_Context fa) -> check_type1 ex ast ty_fg $ \(Type_Type1 _f (ty_g::Type_Root_of_Expr root h_g), _) -> check_type1 ex ast ty_fa $ \(Type_Type1 f ty_fa_a, Lift_Type1 ty_f) -> check_eq_type1 ex ast ty_fg ty_fa $ \Refl -> check_type_fun ex ast ty_g $ \(ty_g_a `Type_Fun` ty_g_b :: Type_Fun lam (Type_Root_of_Expr root) h_g) -> check_constraint1_type ex (Proxy::Proxy Applicative_with_Lambda) ast ty_fa $ \Dict -> check_eq_type ex ast ty_g_a ty_fa_a $ \Refl -> k (Type_Root $ ty_f $ Type_Type1 f ty_g_b) $ Forall_Repr_with_Context $ \c -> (<*>) (fg c) (fa c)