{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -- | Expression for 'Functor'. module Language.Symantic.Expr.Functor where import Control.Monad (liftM2) import Data.Proxy (Proxy(..)) import Data.Type.Equality ((:~:)(Refl)) import Prelude hiding (fmap) import qualified Data.Function as Fun import qualified Data.Functor as Functor import Language.Symantic.Type import Language.Symantic.Repr import Language.Symantic.Expr.Root import Language.Symantic.Expr.Error import Language.Symantic.Expr.From import Language.Symantic.Expr.Lambda import Language.Symantic.Trans.Common -- * Class 'Sym_Functor' -- | Symantic. class Sym_Lambda repr => Sym_Functor repr where fmap :: Functor f => repr (a -> b) -> repr (f a) -> repr (f b) default fmap :: (Trans t repr, Functor f) => t repr (a -> b) -> t repr (f a) -> t repr (f b) fmap = trans_map2 fmap (<$) :: Functor f => repr a -> repr (f b) -> repr (f a) (<$) a = fmap (lam (Fun.const a)) infixl 4 <$ instance Sym_Functor Repr_Host where fmap = liftM2 Functor.fmap instance Sym_Functor Repr_Text where fmap = repr_text_app2 "fmap" (<$) = repr_text_infix "<$" (Precedence 4) instance (Sym_Functor r1, Sym_Functor r2) => Sym_Functor (Repr_Dup r1 r2) where fmap (f1 `Repr_Dup` f2) (m1 `Repr_Dup` m2) = fmap f1 m1 `Repr_Dup` fmap f2 m2 -- | 'fmap' alias. (<$>) :: (Sym_Functor repr, Functor f) => repr (a -> b) -> repr (f a) -> repr (f b) (<$>) = fmap infixl 4 <$> -- * Type 'Expr_Functor' -- | Expression. data Expr_Functor (root:: *) type instance Root_of_Expr (Expr_Functor root) = root type instance Type_of_Expr (Expr_Functor root) = No_Type type instance Sym_of_Expr (Expr_Functor root) repr = (Sym_Functor repr) type instance Error_of_Expr ast (Expr_Functor root) = No_Error_Expr -- | Parse 'fmap'. fmap_from :: forall root ty ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_Functor root) , Expr_From ast root , Type0_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 Functor ty ) => ast -> ast -> ExprFrom ast (Expr_Functor 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::ty h_g) (Forall_Repr_with_Context g) -> expr_from (Proxy::Proxy root) ast_fa ctx $ \(ty_fa::ty h_fa) (Forall_Repr_with_Context fa) -> check_type_fun ex ast ty_g $ \(Type2 Proxy ty_g_a ty_g_b) -> check_type1 ex ast ty_fa $ \(Type1 f ty_fa_a, Type1_Lift f_lift) -> check_type1_constraint ex (Proxy::Proxy Functor) ast ty_fa $ \Dict -> check_type0_eq ex ast ty_g_a ty_fa_a $ \Refl -> k (Type_Root $ f_lift $ Type1 f ty_g_b) $ Forall_Repr_with_Context $ \c -> fmap (g c) (fa c)