]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/Applicative.hs
Integer, Integral, Num
[haskell/symantic.git] / Language / Symantic / Expr / Applicative.hs
1 {-# LANGUAGE DefaultSignatures #-}
2 {-# LANGUAGE GADTs #-}
3 {-# LANGUAGE FlexibleContexts #-}
4 {-# LANGUAGE FlexibleInstances #-}
5 {-# LANGUAGE MultiParamTypeClasses #-}
6 {-# LANGUAGE Rank2Types #-}
7 {-# LANGUAGE ScopedTypeVariables #-}
8 {-# LANGUAGE TypeFamilies #-}
9 {-# LANGUAGE TypeOperators #-}
10 {-# OPTIONS_GHC -fno-warn-orphans #-}
11 -- | Expression for 'Applicative'.
12 module Language.Symantic.Expr.Applicative where
13
14 import Control.Applicative (Applicative)
15 import Data.Proxy (Proxy(..))
16 import Data.Type.Equality ((:~:)(Refl))
17 import Prelude hiding (Functor(..), (<$>), Applicative(..), id, const)
18 import qualified Data.Function as Fun
19
20 import Language.Symantic.Type
21 import Language.Symantic.Trans.Common
22 import Language.Symantic.Expr.Root
23 import Language.Symantic.Expr.Error
24 import Language.Symantic.Expr.From
25 import Language.Symantic.Expr.Lambda
26 import Language.Symantic.Expr.Functor
27
28 -- * Class 'Sym_Applicative'
29 -- | Symantic.
30 class Sym_Functor repr => Sym_Applicative repr where
31 pure :: Applicative f => repr a -> repr (f a)
32 (<*>) :: Applicative f => repr (f ((->) a b)) -> repr (f a) -> repr (f b)
33 default pure :: (Trans t repr, Applicative f) => t repr a -> t repr (f a)
34 default (<*>) :: (Trans t repr, Applicative f)
35 => t repr (f ((->) a b)) -> t repr (f a) -> t repr (f b)
36 pure = trans_map1 pure
37 (<*>) = trans_map2 (<*>)
38 (*>) :: Applicative f => repr (f a) -> repr (f b) -> repr (f b)
39 (<*) :: Applicative f => repr (f a) -> repr (f b) -> repr (f a)
40 x *> y = (lam Fun.id <$ x) <*> y
41 x <* y = (lam (lam . Fun.const) <$> x) <*> y
42 infixl 4 *>
43 infixl 4 <*
44 infixl 4 <*>
45
46 -- * Type 'Expr_Applicative'
47 -- | Expression.
48 data Expr_Applicative (root:: *)
49 type instance Root_of_Expr (Expr_Applicative root) = root
50 type instance Type_of_Expr (Expr_Applicative root) = No_Type
51 type instance Sym_of_Expr (Expr_Applicative root) repr = (Sym_Applicative repr)
52 type instance Error_of_Expr ast (Expr_Applicative root) = No_Error_Expr
53
54 -- | Parse 'pure'.
55 pure_from
56 :: forall root ty ast hs ret.
57 ( ty ~ Type_Root_of_Expr (Expr_Applicative root)
58 , Eq_Type ty
59 , Type1_from ast ty
60 , Expr_from ast root
61 , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast)
62 (Error_of_Expr ast root)
63 , Root_of_Expr root ~ root
64 , Constraint_Type1 Applicative ty
65 ) => ast -> ast
66 -> Expr_From ast (Expr_Applicative root) hs ret
67 pure_from ast_f ast_a ex ast ctx k =
68 -- pure :: Applicative f => a -> f a
69 either (\err -> Left $ error_expr ex $ Error_Expr_Type err ast) Fun.id $
70 type1_from (Proxy::Proxy ty) ast_f $ \_f ty_f -> Right $
71 expr_from (Proxy::Proxy root) ast_a ctx $
72 \(ty_a::ty h_a) (Forall_Repr_with_Context a) ->
73 let ty_fa = ty_f ty_a in
74 check_constraint_type1 ex (Proxy::Proxy Applicative) ast ty_fa $ \Dict ->
75 k ty_fa $ Forall_Repr_with_Context $
76 \c -> pure (a c)
77
78 -- | Parse '<*>'.
79 ltstargt_from
80 :: forall root ty ast hs ret.
81 ( ty ~ Type_Root_of_Expr (Expr_Applicative root)
82 , Eq_Type ty
83 , Eq_Type1 ty
84 , Expr_from ast root
85 , Lift_Type Type_Fun (Type_of_Expr root)
86 , Unlift_Type Type_Fun (Type_of_Expr root)
87 , Unlift_Type1 (Type_of_Expr root)
88 , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast)
89 (Error_of_Expr ast root)
90 , Root_of_Expr root ~ root
91 , Constraint_Type1 Applicative ty
92 ) => ast -> ast
93 -> Expr_From ast (Expr_Applicative root) hs ret
94 ltstargt_from ast_fg ast_fa ex ast ctx k =
95 -- (<*>) :: Applicative f => f (a -> b) -> f a -> f b
96 expr_from (Proxy::Proxy root) ast_fg ctx $
97 \(ty_fg::ty h_fg) (Forall_Repr_with_Context fg) ->
98 expr_from (Proxy::Proxy root) ast_fa ctx $
99 \(ty_fa::ty h_fa) (Forall_Repr_with_Context fa) ->
100 check_type1 ex ast ty_fg $ \(Type_Type1 _f (ty_g::ty h_g), _) ->
101 check_type1 ex ast ty_fa $ \(Type_Type1 f ty_fa_a, Lift_Type1 ty_f) ->
102 check_eq_type1 ex ast ty_fg ty_fa $ \Refl ->
103 check_type_fun ex ast ty_g $ \(Type_Type2 Proxy ty_g_a ty_g_b
104 :: Type_Fun ty h_g) ->
105 check_constraint_type1 ex (Proxy::Proxy Applicative) ast ty_fa $ \Dict ->
106 check_eq_type ex ast ty_g_a ty_fa_a $ \Refl ->
107 k (Type_Root $ ty_f $ Type_Type1 f ty_g_b) $ Forall_Repr_with_Context $
108 \c -> (<*>) (fg c) (fa c)