{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -- | Expression for 'MonoFunctor'. module Language.Symantic.Expr.MonoFunctor 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.MonoTraversable as MT import Data.MonoTraversable (MonoFunctor) 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 import Data.Text -- * Class 'Sym_MonoFunctor' -- | Symantic. class Sym_Lambda repr => Sym_MonoFunctor repr where omap :: MonoFunctor m => repr (MT.Element m -> MT.Element m) -> repr m -> repr m default omap :: (Trans t repr, MonoFunctor m) => t repr (MT.Element m -> MT.Element m) -> t repr m -> t repr m omap = trans_map2 omap instance Sym_MonoFunctor Repr_Host where omap = liftM2 MT.omap instance Sym_MonoFunctor Repr_Text where omap = repr_text_app2 "omap" instance ( Sym_MonoFunctor r1 , Sym_MonoFunctor r2 ) => Sym_MonoFunctor (Dup r1 r2) where omap (f1 `Dup` f2) (m1 `Dup` m2) = omap f1 m1 `Dup` omap f2 m2 -- * Type 'Expr_MonoFunctor' -- | Expression. data Expr_MonoFunctor (root:: *) type instance Root_of_Expr (Expr_MonoFunctor root) = root type instance Type_of_Expr (Expr_MonoFunctor root) = No_Type type instance Sym_of_Expr (Expr_MonoFunctor root) repr = (Sym_MonoFunctor repr) type instance Error_of_Expr ast (Expr_MonoFunctor root) = No_Error_Expr -- * Type 'TypeFamily_MonoElement' -- | Proxy type for 'MT.Element'. data TypeFamily_MonoElement type instance Host_of_TypeFamily TypeFamily_MonoElement h = MT.Element h instance TypeFamily TypeFamily_MonoElement (Type_Bool root) instance TypeFamily TypeFamily_MonoElement (Type_Char root) instance TypeFamily TypeFamily_MonoElement (Type_Int root) instance TypeFamily TypeFamily_MonoElement (Type_Integer root) instance TypeFamily TypeFamily_MonoElement (Type_Ordering root) instance Lift_Type_Root (Type_Type0 (Proxy (MT.Element Text))) root => TypeFamily TypeFamily_MonoElement (Type_Text root) where typeFamily _at Type_Type0{} = Just type_type0 instance TypeFamily TypeFamily_MonoElement (Type_Unit root) instance TypeFamily TypeFamily_MonoElement (Type_Var0 root) instance TypeFamily TypeFamily_MonoElement (Type_Var1 root) instance TypeFamily TypeFamily_MonoElement (Type_IO root) where typeFamily _at (Type_Type1 _px a) = Just a instance TypeFamily TypeFamily_MonoElement (Type_List root) where typeFamily _at (Type_Type1 _px a) = Just a instance TypeFamily TypeFamily_MonoElement (Type_Maybe root) where typeFamily _at (Type_Type1 _px a) = Just a instance TypeFamily TypeFamily_MonoElement (Type_Either root) where typeFamily _at (Type_Type2 _px _l r) = Just r instance TypeFamily TypeFamily_MonoElement (Type_Fun root) where typeFamily _at (Type_Type2 _px _r a) = Just a instance TypeFamily TypeFamily_MonoElement (Type_Map root) where typeFamily _at (Type_Type2 _px _k a) = Just a instance TypeFamily TypeFamily_MonoElement (Type_Tuple2 root) where typeFamily _at (Type_Type2 _px _a b) = Just b -- | Parse 'omap'. omap_from :: forall root ty ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_MonoFunctor root) , Eq_Type ty , Expr_from ast root , Lift_Type Type_Fun (Type_of_Expr root) , Unlift_Type Type_Fun (Type_of_Expr root) , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast) (Error_of_Expr ast root) , Root_of_Expr root ~ root , Constraint_Type MonoFunctor ty , TypeFamily TypeFamily_MonoElement ty ) => ast -> ast -> Expr_From ast (Expr_MonoFunctor root) hs ret omap_from ast_f ast_m ex ast ctx k = -- NOTE: omap :: (TypeFamily_MonoElement mono -> TypeFamily_MonoElement mono) -> mono -> mono expr_from (Proxy::Proxy root) ast_f ctx $ \(ty_f::ty h_f) (Forall_Repr_with_Context f) -> expr_from (Proxy::Proxy root) ast_m ctx $ \(ty_m::ty h_m) (Forall_Repr_with_Context m) -> check_type_fun ex ast ty_f $ \(Type_Type2 Proxy ty_f_a ty_f_b :: Type_Fun ty h_f) -> check_constraint_type ex (Proxy::Proxy MonoFunctor) ast ty_m $ \Dict -> check_eq_type ex ast ty_f_a ty_f_b $ \Refl -> check_TypeFamily (Proxy::Proxy TypeFamily_MonoElement) ex ast ty_m $ \ty_m_ele -> check_eq_type ex ast ty_f_a ty_m_ele $ \Refl -> k ty_m $ Forall_Repr_with_Context $ \c -> omap (f c) (m c)