{-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -- | Expression for 'Applicative'. module Language.Symantic.Expr.Applicative where import Control.Applicative (Applicative) import qualified Control.Applicative as Applicative import Control.Monad import qualified Data.Function as Fun import Data.Proxy (Proxy(..)) import Data.Type.Equality ((:~:)(Refl)) import Prelude hiding (Functor(..), (<$>), Applicative(..), id, const) import Language.Symantic.Type import Language.Symantic.Repr import Language.Symantic.Trans.Common import Language.Symantic.Expr.Root import Language.Symantic.Expr.Error import Language.Symantic.Expr.From import Language.Symantic.Expr.Lambda import Language.Symantic.Expr.Functor -- * Class 'Sym_Applicative' -- | Symantic. class Sym_Functor repr => Sym_Applicative repr where pure :: Applicative f => repr a -> repr (f a) (<*>) :: Applicative f => repr (f ((->) a b)) -> repr (f a) -> repr (f b) default pure :: (Trans t repr, Applicative f) => t repr a -> t repr (f a) default (<*>) :: (Trans t repr, Applicative f) => t repr (f ((->) a b)) -> t repr (f a) -> t repr (f b) pure = trans_map1 pure (<*>) = trans_map2 (<*>) (*>) :: Applicative f => repr (f a) -> repr (f b) -> repr (f b) (<*) :: Applicative f => repr (f a) -> repr (f b) -> repr (f a) x *> y = (lam Fun.id <$ x) <*> y x <* y = (lam (lam . Fun.const) <$> x) <*> y infixl 4 *> infixl 4 <* infixl 4 <*> instance Sym_Applicative Repr_Host where pure = liftM Applicative.pure (<*>) = liftM2 (Applicative.<*>) instance Sym_Applicative Repr_Text where pure = repr_text_app1 "pure" (<*>) = repr_text_infix "<*>" (Precedence 4) (<* ) = repr_text_infix "<*" (Precedence 4) ( *>) = repr_text_infix "*>" (Precedence 4) instance (Sym_Applicative r1, Sym_Applicative r2) => Sym_Applicative (Repr_Dup r1 r2) where pure (a1 `Repr_Dup` a2) = pure a1 `Repr_Dup` pure a2 (<*>) (f1 `Repr_Dup` f2) (m1 `Repr_Dup` m2) = (<*>) f1 m1 `Repr_Dup` (<*>) f2 m2 -- * Type 'Expr_Applicative' -- | Expression. data Expr_Applicative (root:: *) type instance Root_of_Expr (Expr_Applicative root) = root type instance Type_of_Expr (Expr_Applicative root) = No_Type type instance Sym_of_Expr (Expr_Applicative root) repr = (Sym_Applicative repr) type instance Error_of_Expr ast (Expr_Applicative root) = No_Error_Expr -- | Parse 'pure'. pure_from :: forall root ty ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_Applicative root) , Type0_Eq ty , Type1_From ast ty , Expr_From ast root , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast) (Error_of_Expr ast root) , Root_of_Expr root ~ root , Type1_Constraint Applicative ty ) => ast -> ast -> ExprFrom ast (Expr_Applicative 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) Fun.id $ type1_from (Proxy::Proxy ty) ast_f $ \_f ty_f -> Right $ expr_from (Proxy::Proxy root) ast_a ctx $ \(ty_a::ty h_a) (Forall_Repr_with_Context a) -> let ty_fa = ty_f ty_a in check_type1_constraint ex (Proxy::Proxy Applicative) ast ty_fa $ \Dict -> k ty_fa $ Forall_Repr_with_Context $ \c -> pure (a c) -- | Parse '<*>'. ltstargt_from :: forall root ty ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_Applicative root) , Expr_From ast root , Type0_Eq ty , Type1_Eq ty , Type0_Lift Type_Fun (Type_of_Expr root) , Type0_Unlift Type_Fun (Type_of_Expr root) , Type1_Unlift (Type_of_Expr root) , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast) (Error_of_Expr ast root) , Root_of_Expr root ~ root , Type1_Constraint Applicative ty ) => ast -> ast -> ExprFrom ast (Expr_Applicative 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::ty h_fg) (Forall_Repr_with_Context fg) -> expr_from (Proxy::Proxy root) ast_fa ctx $ \(ty_fa::ty h_fa) (Forall_Repr_with_Context fa) -> check_type1 ex ast ty_fg $ \(Type1 _f (ty_g::ty h_g), _) -> check_type1 ex ast ty_fa $ \(Type1 f ty_fa_a, Type1_Lift ty_f) -> check_type1_eq ex ast ty_fg ty_fa $ \Refl -> check_type_fun ex ast ty_g $ \(Type2 Proxy ty_g_a ty_g_b) -> check_type1_constraint ex (Proxy::Proxy Applicative) ast ty_fa $ \Dict -> check_type0_eq ex ast ty_g_a ty_fa_a $ \Refl -> k (Type_Root $ ty_f $ Type1 f ty_g_b) $ Forall_Repr_with_Context $ \c -> (<*>) (fg c) (fa c)