{-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -- | Expression for 'Traversable'. module Language.Symantic.Expr.Traversable where import Data.Traversable (Traversable) import Data.Proxy (Proxy(..)) import Data.Type.Equality ((:~:)(Refl)) import Prelude hiding (Traversable(..)) import Language.Symantic.Type import Language.Symantic.Trans.Common import Language.Symantic.Expr.Root import Language.Symantic.Expr.Error import Language.Symantic.Expr.From import Language.Symantic.Expr.Lambda import Language.Symantic.Expr.Applicative -- * Class 'Sym_Traversable' -- | Symantic. class ( Sym_Applicative repr , Sym_Applicative_Lam lam repr ) => Sym_Traversable lam repr where traverse :: (Traversable t, Applicative f) => repr (Lambda lam a (f b)) -> repr (t a) -> repr (f (t b)) default traverse :: (Trans tr repr, Traversable t, Applicative f) => tr repr (Lambda lam a (f b)) -> tr repr (t a) -> tr repr (f (t b)) traverse = trans_map2 traverse -- * Type 'Expr_Traversable' -- | Expression. data Expr_Traversable (lam:: * -> *) (root:: *) type instance Root_of_Expr (Expr_Traversable lam root) = root type instance Type_of_Expr (Expr_Traversable lam root) = No_Type type instance Sym_of_Expr (Expr_Traversable lam root) repr = (Sym_Traversable lam repr) type instance Error_of_Expr ast (Expr_Traversable lam root) = No_Error_Expr instance Constraint_Type1 Traversable (Type_Type0 px root) instance Constraint_Type1 Traversable (Type_Var1 root) traverse_from :: forall root ty lam ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_Traversable lam root) , Eq_Type (Type_Root_of_Expr root) , Eq_Type1 (Type_Root_of_Expr root) , Expr_from ast root , Lift_Type (Type_Fun lam) (Type_of_Expr root) , Unlift_Type (Type_Fun lam) (Type_of_Expr root) , Unlift_Type1 (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_Type1 Applicative ty , Constraint_Type1 Traversable ty ) => ast -> ast -> Expr_From ast (Expr_Traversable lam root) hs ret traverse_from ast_g ast_ta ex ast ctx k = -- traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t 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_ta ctx $ \ty_ta (Forall_Repr_with_Context ta) -> check_type_fun ex ast ty_g $ \(Type_Type2 Proxy ty_g_a ty_g_fb :: Type_Fun lam (Type_Root_of_Expr root) h_g) -> check_type1 ex ast ty_g_fb $ \(Type_Type1 f ty_g_fb_b, Lift_Type1 ty_f) -> check_type1 ex ast ty_ta $ \(Type_Type1 t ty_ta_a, Lift_Type1 ty_t) -> check_constraint_type1 ex (Proxy::Proxy Applicative) ast ty_g_fb $ \Dict -> check_constraint_type1 ex (Proxy::Proxy Traversable) ast ty_ta $ \Dict -> check_eq_type ex ast ty_g_a ty_ta_a $ \Refl -> k ( Type_Root $ ty_f $ Type_Type1 f $ Type_Root $ ty_t $ Type_Type1 t ty_g_fb_b ) $ Forall_Repr_with_Context $ \c -> traverse (g c) (ta c)