{-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# 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 Control.Monad import Data.Traversable (Traversable) import qualified Data.Traversable as Traversable import Data.Proxy (Proxy(..)) import Data.Type.Equality ((:~:)(Refl)) import Prelude hiding (Traversable(..)) 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.Expr.Applicative import Language.Symantic.Trans.Common -- * Class 'Sym_Traversable' -- | Symantic. class Sym_Applicative repr => Sym_Traversable repr where traverse :: (Traversable t, Applicative f) => repr ((->) a (f b)) -> repr (t a) -> repr (f (t b)) default traverse :: (Trans tr repr, Traversable t, Applicative f) => tr repr ((->) a (f b)) -> tr repr (t a) -> tr repr (f (t b)) traverse = trans_map2 traverse instance Sym_Traversable Repr_Host where traverse = liftM2 Traversable.traverse instance Sym_Traversable Repr_Text where traverse = repr_text_app2 "traverse" instance ( Sym_Traversable r1 , Sym_Traversable r2 ) => Sym_Traversable (Dup r1 r2) where traverse (f1 `Dup` f2) (m1 `Dup` m2) = traverse f1 m1 `Dup` traverse f2 m2 -- * Type 'Expr_Traversable' -- | Expression. data Expr_Traversable (root:: *) type instance Root_of_Expr (Expr_Traversable root) = root type instance Type_of_Expr (Expr_Traversable root) = No_Type type instance Sym_of_Expr (Expr_Traversable root) repr = (Sym_Traversable repr) type instance Error_of_Expr ast (Expr_Traversable root) = No_Error_Expr traverse_from :: forall root ty ast hs ret. ( ty ~ Type_Root_of_Expr (Expr_Traversable root) , Type0_Eq ty , Type1_Eq ty , Expr_From ast root , 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 Applicative ty , Type1_Constraint Traversable ty ) => ast -> ast -> ExprFrom ast (Expr_Traversable 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::ty 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 $ \(Type2 Proxy ty_g_a ty_g_fb :: Type_Fun ty h_g) -> check_type1 ex ast ty_g_fb $ \(Type1 f ty_g_fb_b, Type1_Lift ty_f) -> check_type1 ex ast ty_ta $ \(Type1 t ty_ta_a, Type1_Lift ty_t) -> check_type1_constraint ex (Proxy::Proxy Applicative) ast ty_g_fb $ \Dict -> check_type1_constraint ex (Proxy::Proxy Traversable) ast ty_ta $ \Dict -> check_type0_eq ex ast ty_g_a ty_ta_a $ \Refl -> k ( Type_Root $ ty_f $ Type1 f $ Type_Root $ ty_t $ Type1 t ty_g_fb_b ) $ Forall_Repr_with_Context $ \c -> traverse (g c) (ta c)