]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Expr/Functor.hs
init
[haskell/symantic.git] / Language / Symantic / Expr / Functor.hs
1 {-# LANGUAGE ConstraintKinds #-}
2 {-# LANGUAGE DefaultSignatures #-}
3 {-# LANGUAGE GADTs #-}
4 {-# LANGUAGE FlexibleContexts #-}
5 {-# LANGUAGE FlexibleInstances #-}
6 {-# LANGUAGE MultiParamTypeClasses #-}
7 {-# LANGUAGE ScopedTypeVariables #-}
8 {-# LANGUAGE TypeFamilies #-}
9 {-# LANGUAGE TypeOperators #-}
10 {-# LANGUAGE UndecidableInstances #-}
11 {-# OPTIONS_GHC -fno-warn-orphans #-}
12 -- | Expression for 'Functor'.
13 module Language.Symantic.Expr.Functor where
14
15 import Data.Proxy (Proxy(..))
16 import Data.Type.Equality ((:~:)(Refl))
17 import Prelude hiding (fmap)
18
19 import Language.Symantic.Type
20 import Language.Symantic.Trans.Common
21 import Language.Symantic.Expr.Common
22 import Language.Symantic.Expr.Lambda
23
24 -- * Class 'Sym_Functor'
25 -- | Symantic.
26 class Sym_Functor lam repr where
27 fmap
28 :: Functor f
29 => repr (Lambda lam a b)
30 -> repr (f a)
31 -> repr (f b)
32
33 default fmap
34 :: (Trans t repr, Functor f)
35 => t repr (Lambda lam a b)
36 -> t repr (f a)
37 -> t repr (f b)
38 fmap = trans_map2 fmap
39
40 -- | Convenient alias.
41 (<$>) ::
42 ( Sym_Functor lam repr
43 , Functor f )
44 => repr (Lambda lam a b)
45 -> repr (f a)
46 -> repr (f b)
47 (<$>) = fmap
48 infixl 4 <$>
49
50 -- * Type 'Expr_Functor'
51 -- | Expression.
52 data Expr_Functor (lam:: * -> *) (root:: *)
53 type instance Root_of_Expr (Expr_Functor lam root) = root
54 type instance Type_of_Expr (Expr_Functor lam root) = No_Type
55 type instance Sym_of_Expr (Expr_Functor lam root) repr = (Sym_Functor lam repr)
56 type instance Error_of_Expr ast (Expr_Functor lam root) = No_Error_Expr
57 instance Constraint_Type1 Functor (Type_Type0 px root)
58 instance Constraint_Type1 Functor (Type_Var1 root)
59 instance Constraint_Type1 Functor (Type_Type2 px root)
60
61 -- | Parse 'fmap'.
62 fmap_from
63 :: forall root ty lam ast hs ret.
64 ( ty ~ Type_Root_of_Expr (Expr_Functor lam root)
65 , String_from_Type ty
66 , Eq_Type (Type_Root_of_Expr root)
67 , Expr_from ast root
68 , Lift_Type (Type_Fun lam) (Type_of_Expr root)
69 , Unlift_Type (Type_Fun lam) (Type_of_Expr root)
70 , Unlift_Type1 (Type_of_Expr root)
71 , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast)
72 (Error_of_Expr ast root)
73 , Root_of_Expr root ~ root
74 , Constraint_Type1 Functor ty
75 ) => ast -> ast
76 -> Expr_From ast (Expr_Functor lam root) hs ret
77 fmap_from ast_g ast_fa ex ast ctx k =
78 -- NOTE: fmap :: Functor f => (a -> b) -> f a -> f b
79 expr_from (Proxy::Proxy root) ast_g ctx $
80 \(ty_g::Type_Root_of_Expr root h_g) (Forall_Repr_with_Context g) ->
81 expr_from (Proxy::Proxy root) ast_fa ctx $
82 \(ty_fa::Type_Root_of_Expr root h_fa) (Forall_Repr_with_Context fa) ->
83 check_type_fun ex ast ty_g $ \(Type_Type2 Proxy ty_g_a ty_g_b
84 :: Type_Fun lam (Type_Root_of_Expr root) h_g) ->
85 check_type1 ex ast ty_fa $ \(Type_Type1 f ty_fa_a, Lift_Type1 f_lift) ->
86 check_constraint1_type ex (Proxy::Proxy Functor) ast ty_fa $ \Dict ->
87 check_eq_type ex ast ty_g_a ty_fa_a $ \Refl ->
88 k (Type_Root $ f_lift $ Type_Type1 f ty_g_b) $ Forall_Repr_with_Context $
89 \c -> fmap (g c) (fa c)