{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} -- | Expression for 'Functor'. module Language.Symantic.Expr.Functor where import Data.Proxy (Proxy(..)) import Data.Type.Equality ((:~:)(Refl)) import Prelude hiding (fmap) import Language.Symantic.Type -- import Language.Symantic.Repr.Dup import Language.Symantic.Trans.Common import Language.Symantic.Expr.Common import Language.Symantic.Expr.Lambda -- | A class alias to add 'Traversable' to 'Functor'. -- -- NOTE: 'Traversable' is required by the 'Repr_Host' instance (which uses 'sequence'). -- Imposing this 'Traversable' class to mere 'Functor's is annoying -- because obviously not all data types have both -- an instance of 'Functor' and 'Traversable', -- but I cannot see another way to do when supporting 'val' and 'lazy' 'Lambda's -- whose @lam@ wrapping has to be extracted from @f (lam a)@ to @lam (f a)@, -- which is exactly which is done by @sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)@. class (Functor f, Traversable f) => Functor_with_Lambda f instance (Functor f, Traversable f) => Functor_with_Lambda f instance Constraint1_Type Functor_with_Lambda (Type_Fun lam root) instance Constraint1_Type Functor_with_Lambda (Type_Bool root) instance Constraint1_Type Functor_with_Lambda (Type_Int root) instance Constraint1_Type Functor_with_Lambda (Type_Var root) class Sym_Functor lam repr where fmap :: Functor_with_Lambda f => repr (Lambda lam a b) -> repr (f a) -> repr (f b) default fmap :: (Trans t repr, Functor_with_Lambda f) => t repr (Lambda lam a b) -> t repr (f a) -> t repr (f b) fmap = trans_map2 fmap -- * Type 'Expr_Functor' -- | Expression. data Expr_Functor (lam:: * -> *) (root:: *) type instance Root_of_Expr (Expr_Functor lam root) = root type instance Type_of_Expr (Expr_Functor lam root) = No_Type type instance Sym_of_Expr (Expr_Functor lam root) repr = (Sym_Functor lam repr) type instance Error_of_Expr ast (Expr_Functor lam root) = No_Error_Expr -- | Parse 'fmap'. fmap_from :: forall root ty lam ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_Functor lam root) , Eq_Type (Type_Root_of_Expr root) , Expr_from ast root , Type_Lift (Type_Fun lam) (Type_of_Expr root) , Type_Unlift (Type_Fun lam) (Type_of_Expr root) , Type_Unlift1 (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 , Constraint1_Type Functor_with_Lambda ty ) => ast -> ast -> Expr_From ast (Expr_Functor lam root) hs ret fmap_from ast_g ast_fa ex ast ctx k = -- NOTE: fmap :: Functor f => (a -> b) -> f a -> f b expr_from (Proxy::Proxy root) ast_g ctx $ \(ty_g::Type_Root_of_Expr root h_g) (Forall_Repr_with_Context g) -> expr_from (Proxy::Proxy root) ast_fa ctx $ \(ty_fa::Type_Root_of_Expr root h_fa) (Forall_Repr_with_Context fa) -> 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_type1 ex ast ty_fa $ \(Type_Type1 f ty_fa_a, Type_Lift1 f_lift) -> check_constraint1_type ex (Proxy::Proxy Functor_with_Lambda) ast ty_fa $ \Dict -> check_eq_type ex ast ty_g_a ty_fa_a $ \Refl -> k (Type_Root $ f_lift $ Type_Type1 f ty_g_b) $ Forall_Repr_with_Context $ \c -> fmap (g c) (fa c)