]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/Applicative.hs
init
[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 {-# LANGUAGE UndecidableInstances #-}
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 (Applicative(..))
18
19 import Language.Symantic.Type
20 -- import Language.Symantic.Repr.Dup
21 import Language.Symantic.Trans.Common
22 import Language.Symantic.Expr.Common
23 import Language.Symantic.Expr.Lambda
24 import Language.Symantic.Expr.Functor
25
26 -- * Class 'Sym_Applicative'
27 -- | Symantic.
28 class Sym_Applicative repr where
29 pure :: Applicative f => repr a -> repr (f a)
30 -- (*>) :: Applicative f => repr (f a) -> repr (f b) -> repr (f b)
31 -- (<*) :: Applicative f => repr (f a) -> repr (f b) -> repr (f a)
32
33 default pure :: (Trans t repr, Applicative f) => t repr a -> t repr (f a)
34 pure = trans_map1 pure
35
36 -- * Class 'Sym_Applicative_Lam'
37 -- | Symantic requiring a 'Lambda'.
38 class Sym_Functor lam repr => Sym_Applicative_Lam lam repr where
39 (<*>) :: Applicative_with_Lambda f => repr (f (Lambda lam a b)) -> repr (f a) -> repr (f b)
40 -- (*>) :: Applicative f => repr (f a) -> repr (f b) -> repr (f b)
41 -- (<*) :: Applicative f => repr (f a) -> repr (f b) -> repr (f a)
42
43 default (<*>) :: (Trans t repr, Applicative_with_Lambda f) => t repr (f (Lambda lam a b)) -> t repr (f a) -> t repr (f b)
44 -- default (*>) :: (Trans t, Applicative f) => t repr (f a) -> t repr (f b) -> t repr (f b)
45 -- default (<*) :: (Trans t, Applicative f) => t repr (f a) -> t repr (f b) -> t repr (f a)
46 (<*>) = trans_map2 (<*>)
47 infixl 4 <*>
48
49 -- ** Class 'Applicative_with_Lambda'
50 -- | A class alias to join 'Traversable' to 'Applicative'.
51 --
52 -- NOTE: see comment of 'Functor_with_Lambda'.
53 class (Applicative f, Traversable f) => Applicative_with_Lambda f
54 instance (Applicative f, Traversable f) => Applicative_with_Lambda f
55 instance Constraint1_Type Applicative_with_Lambda (Type_Fun lam root)
56 instance Constraint1_Type Applicative_with_Lambda (Type_Bool root)
57 instance Constraint1_Type Applicative_with_Lambda (Type_Int root)
58 instance Constraint1_Type Applicative_with_Lambda (Type_Ordering root)
59 instance Constraint1_Type Applicative_with_Lambda (Type_Unit root)
60 instance Constraint1_Type Applicative_with_Lambda (Type_Var root)
61
62 -- * Type 'Expr_Applicative'
63 -- | Expression.
64 data Expr_Applicative (lam:: * -> *) (root:: *)
65 type instance Root_of_Expr (Expr_Applicative lam root) = root
66 type instance Type_of_Expr (Expr_Applicative lam root) = No_Type
67 type instance Sym_of_Expr (Expr_Applicative lam root) repr = (Sym_Applicative repr, Sym_Applicative_Lam lam repr)
68 type instance Error_of_Expr ast (Expr_Applicative lam root) = No_Error_Expr
69
70 pure_from
71 :: forall root ty ty_root lam ast hs ret.
72 ( ty ~ Type_Root_of_Expr (Expr_Applicative lam root)
73 , ty_root ~ Type_Root_of_Expr root
74 , Eq_Type (Type_Root_of_Expr root)
75 , Type1_from ast (Type_Root_of_Expr root)
76 , Expr_from ast root
77 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
78 (Error_of_Expr ast root)
79 , Root_of_Expr root ~ root
80 , Constraint1_Type Applicative_with_Lambda ty
81 ) => ast -> ast
82 -> Expr_From ast (Expr_Applicative lam root) hs ret
83 pure_from ast_f ast_a ex ast ctx k =
84 -- pure :: Applicative f => a -> f a
85 either (\err -> Left $ error_expr ex $ Error_Expr_Type err ast) id $
86 type1_from (Proxy::Proxy ty_root) ast_f $ \_f ty_f -> Right $
87 expr_from (Proxy::Proxy root) ast_a ctx $
88 \(ty_a::Type_Root_of_Expr root h_a) (Forall_Repr_with_Context a) ->
89 let ty_fa = ty_f ty_a in
90 check_constraint1_type ex (Proxy::Proxy Applicative_with_Lambda) ast ty_fa $ \Dict ->
91 k ty_fa $ Forall_Repr_with_Context $
92 \c -> pure (a c)
93
94 ltstargt_from
95 :: forall root ty lam ast hs ret.
96 ( ty ~ Type_Root_of_Expr (Expr_Applicative lam root)
97 , String_from_Type ty
98 , Eq_Type (Type_Root_of_Expr root)
99 , Eq_Type1 (Type_Root_of_Expr root)
100 , Expr_from ast root
101 , Type_Lift (Type_Fun lam) (Type_of_Expr root)
102 , Type_Unlift (Type_Fun lam) (Type_of_Expr root)
103 , Unlift_Type1 (Type_of_Expr root)
104 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
105 (Error_of_Expr ast root)
106 , Root_of_Expr root ~ root
107 , Constraint1_Type Applicative_with_Lambda ty
108 ) => ast -> ast
109 -> Expr_From ast (Expr_Applicative lam root) hs ret
110 ltstargt_from ast_fg ast_fa ex ast ctx k =
111 -- (<*>) :: Applicative f => f (a -> b) -> f a -> f b
112 expr_from (Proxy::Proxy root) ast_fg ctx $
113 \(ty_fg::Type_Root_of_Expr root h_fg) (Forall_Repr_with_Context fg) ->
114 expr_from (Proxy::Proxy root) ast_fa ctx $
115 \(ty_fa::Type_Root_of_Expr root h_fa) (Forall_Repr_with_Context fa) ->
116 check_type1 ex ast ty_fg $ \(Type_Type1 _f (ty_g::Type_Root_of_Expr root h_g), _) ->
117 check_type1 ex ast ty_fa $ \(Type_Type1 f ty_fa_a, Type_Lift1 ty_f) ->
118 check_eq_type1 ex ast ty_fg ty_fa $ \Refl ->
119 check_type_fun ex ast ty_g $ \(ty_g_a `Type_Fun` ty_g_b
120 :: Type_Fun lam (Type_Root_of_Expr root) h_g) ->
121 check_constraint1_type ex (Proxy::Proxy Applicative_with_Lambda) ast ty_fa $ \Dict ->
122 check_eq_type ex ast ty_g_a ty_fa_a $ \Refl ->
123 k (Type_Root $ ty_f $ Type_Type1 f ty_g_b) $ Forall_Repr_with_Context $
124 \c -> (<*>) (fg c) (fa c)