{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} -- | Interpreter to duplicate the representation of an expression -- in order to evaluate it with different interpreters. -- -- NOTE: this is a more verbose, less clear, -- and maybe less efficient alternative -- to maintaining the universal polymorphism of @repr@ at parsing time -- as done with 'Forall_Repr_with_Context'; -- it is mainly here for the sake of curiosity. module Language.Symantic.Repr.Dup where import Data.Proxy -- | Interpreter's data. data Repr_Dup repr1 repr2 a = Repr_Dup { repr_dup_1 :: repr1 a , repr_dup_2 :: repr2 a } repr_dup0 :: (cl r, cl s) => Proxy cl -> (forall repr. cl repr => repr a) -> Repr_Dup r s a repr_dup0 _cl f = f `Repr_Dup` f repr_dup1 :: (cl r, cl s) => Proxy cl -> (forall repr. cl repr => repr a -> repr b) -> Repr_Dup r s a -> Repr_Dup r s b repr_dup1 _cl f (a1 `Repr_Dup` a2) = f a1 `Repr_Dup` f a2 repr_dup2 :: (cl r, cl s) => Proxy cl -> (forall repr. cl repr => repr a -> repr b -> repr c) -> Repr_Dup r s a -> Repr_Dup r s b -> Repr_Dup r s c repr_dup2 _cl f (a1 `Repr_Dup` a2) (b1 `Repr_Dup` b2) = f a1 b1 `Repr_Dup` f a2 b2 repr_dup3 :: (cl r, cl s) => Proxy cl -> (forall repr. cl repr => repr a -> repr b -> repr c -> repr d) -> Repr_Dup r s a -> Repr_Dup r s b -> Repr_Dup r s c -> Repr_Dup r s d repr_dup3 _cl f (a1 `Repr_Dup` a2) (b1 `Repr_Dup` b2) (c1 `Repr_Dup` c2) = f a1 b1 c1 `Repr_Dup` f a2 b2 c2