Repr_Dup helpers
authorJulien Moutinho <julm+symantic@autogeree.net>
Thu, 17 Nov 2016 01:32:14 +0000 (02:32 +0100)
committerJulien Moutinho <julm+symantic@autogeree.net>
Thu, 17 Nov 2016 01:33:55 +0000 (02:33 +0100)
37 files changed:
Language/Symantic/Expr/Bool.hs
Language/Symantic/Expr/Char.hs
Language/Symantic/Expr/Either.hs
Language/Symantic/Expr/Eq.hs
Language/Symantic/Expr/Foldable.hs
Language/Symantic/Expr/Functor.hs
Language/Symantic/Expr/IO.hs
Language/Symantic/Expr/If.hs
Language/Symantic/Expr/Int.hs
Language/Symantic/Expr/Integer.hs
Language/Symantic/Expr/Integral.hs
Language/Symantic/Expr/Lambda.hs
Language/Symantic/Expr/List.hs
Language/Symantic/Expr/Map.hs
Language/Symantic/Expr/Maybe.hs
Language/Symantic/Expr/Monad.hs
Language/Symantic/Expr/MonoFunctor.hs
Language/Symantic/Expr/Monoid.hs
Language/Symantic/Expr/Num.hs
Language/Symantic/Expr/Ord.hs
Language/Symantic/Expr/Text.hs
Language/Symantic/Expr/Traversable.hs
Language/Symantic/Expr/Tuple.hs
Language/Symantic/Repr/Dup.hs
Language/Symantic/Repr/Text.hs
Language/Symantic/Type/Bool.hs
Language/Symantic/Type/Char.hs
Language/Symantic/Type/Either.hs
Language/Symantic/Type/Fun.hs
Language/Symantic/Type/IO.hs
Language/Symantic/Type/Int.hs
Language/Symantic/Type/Integer.hs
Language/Symantic/Type/List.hs
Language/Symantic/Type/Maybe.hs
Language/Symantic/Type/Text.hs
Language/Symantic/Type/Tuple.hs
Language/Symantic/Type/Unit.hs

index 03b364c1e2369dae02537d73353d13a9d4f54fad..9aaea7e23381dd55aace5668f21dbc501db0f00e 100644 (file)
@@ -10,6 +10,7 @@ module Language.Symantic.Expr.Bool where
 import Control.Monad
 import qualified Data.Bool as Bool
 import Data.Monoid
+import Data.Proxy
 import qualified Data.Text as Text
 import Prelude hiding ((&&), not, (||))
 
@@ -60,11 +61,14 @@ instance Sym_Bool Repr_Text where
        (||) = repr_text_infix "||"    (Precedence 5)
        xor  = repr_text_infix "`xor`" (Precedence 5)
 instance (Sym_Bool r1, Sym_Bool r2) => Sym_Bool (Repr_Dup r1 r2) where
-       bool x                                     = bool x     `Repr_Dup` bool x
-       not  (x1 `Repr_Dup` x2)                    = not  x1    `Repr_Dup` not  x2
-       (&&) (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) = (&&) x1 y1 `Repr_Dup` (&&) x2 y2
-       (||) (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) = (||) x1 y1 `Repr_Dup` (||) x2 y2
-       xor  (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) = xor  x1 y1 `Repr_Dup` xor  x2 y2
+       bool x = bool x `Repr_Dup` bool x
+       not  = repr_dup1 sym_Bool not
+       (&&) = repr_dup2 sym_Bool (&&)
+       (||) = repr_dup2 sym_Bool (||)
+       xor  = repr_dup2 sym_Bool xor
+
+sym_Bool :: Proxy Sym_Bool
+sym_Bool = Proxy
 
 -- * Type 'Expr_Bool'
 -- | Expression.
index aa79d293209d8f334c74929309f65bfe66aa2cb0..89dcb642dd9824591f0ef8e3a413443b600912d2 100644 (file)
@@ -9,6 +9,7 @@ module Language.Symantic.Expr.Char where
 
 import Control.Monad
 import qualified Data.Char as Char
+import Data.Proxy
 import qualified Data.Text as Text
 
 import Language.Symantic.Type
@@ -36,13 +37,12 @@ instance Sym_Char Repr_Text where
        char a = Repr_Text $ \_p _v ->
                Text.pack (show a)
        char_toUpper = repr_text_app1 "char_toUpper"
-instance
- ( Sym_Char r1
- , Sym_Char r2
- ) => Sym_Char (Repr_Dup r1 r2) where
-       char x = char x `Repr_Dup` char x
-       char_toUpper (c1 `Repr_Dup` c2) =
-               char_toUpper c1 `Repr_Dup` char_toUpper c2
+instance (Sym_Char r1, Sym_Char r2) => Sym_Char (Repr_Dup r1 r2) where
+       char x       = char x `Repr_Dup` char x
+       char_toUpper = repr_dup1 sym_Char char_toUpper
+
+sym_Char :: Proxy Sym_Char
+sym_Char = Proxy
 
 -- * Type 'Expr_Char'
 -- | Expression.
index f535a1eeabac196ad63872e4a1cf9bc030c82e1c..0d539ea69c712dca7db77663f9c509de2fabad3b 100644 (file)
@@ -36,8 +36,11 @@ instance Sym_Either Repr_Text where
        right = repr_text_app1 "right"
        left  = repr_text_app1 "left"
 instance (Sym_Either r1, Sym_Either r2) => Sym_Either (Repr_Dup r1 r2) where
-       left  (l1 `Repr_Dup` l2) = left  l1 `Repr_Dup` left  l2
-       right (r1 `Repr_Dup` r2) = right r1 `Repr_Dup` right r2
+       left  = repr_dup1 sym_Either left
+       right = repr_dup1 sym_Either right
+
+sym_Either :: Proxy Sym_Either
+sym_Either = Proxy
 
 -- * Type 'Expr_Either'
 -- | Expression.
index 39cdb2c35c9246dbbc67c2a24e40d51648ce7cb6..e83f551df9dabb57a2cff9bda2c12beeb1d02ab4 100644 (file)
@@ -47,8 +47,11 @@ instance Sym_Eq Repr_Text where
        (==) = repr_text_infix "==" (Precedence 4)
        (/=) = repr_text_infix "/=" (Precedence 4)
 instance (Sym_Eq r1, Sym_Eq r2) => Sym_Eq (Repr_Dup r1 r2) where
-       (==) (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) = (==) x1 y1 `Repr_Dup` (==) x2 y2
-       (/=) (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) = (/=) x1 y1 `Repr_Dup` (/=) x2 y2
+       (==) = repr_dup2 sym_Eq (==)
+       (/=) = repr_dup2 sym_Eq (/=)
+
+sym_Eq :: Proxy Sym_Eq
+sym_Eq = Proxy
 
 -- * Type 'Expr_Eq'
 -- | Expression.
index bb1817447d703b5cd19be53474ba1de3df40383f..65905b19a007857d24965edaa8ddeef24b579ed4 100644 (file)
 -- | Expression for 'Foldable'.
 module Language.Symantic.Expr.Foldable where
 
-import Control.Monad
+import Control.Monad (liftM, liftM2, liftM3)
 import Data.Monoid
 import Data.Foldable (Foldable)
 import qualified Data.Foldable as Foldable
 import Data.Proxy (Proxy(..))
 import Data.Type.Equality ((:~:)(Refl))
-import Prelude hiding ((<$>), Foldable(..))
+import Prelude hiding ((<$>), Foldable(..)
+ , all, and, any, concat, concatMap, mapM_
+ , notElem, or, sequence_)
 
 import Language.Symantic.Type
 import Language.Symantic.Repr
@@ -31,92 +33,202 @@ import Language.Symantic.Trans.Common
 -- * Class 'Sym_Foldable'
 -- | Symantic.
 class Sym_Foldable repr where
-       foldMap :: (Foldable f, Monoid m) => repr (a -> m) -> repr (f a) -> repr m
-       foldr   :: Foldable f => repr (a -> b -> b) -> repr b -> repr (f a) -> repr b
-       foldr'  :: Foldable f => repr (a -> b -> b) -> repr b -> repr (f a) -> repr b
-       foldl   :: Foldable f => repr (b -> a -> b) -> repr b -> repr (f a) -> repr b
-       foldl'  :: Foldable f => repr (b -> a -> b) -> repr b -> repr (f a) -> repr b
-       length  :: Foldable f => repr (f a) -> repr Int
-       null    :: Foldable f => repr (f a) -> repr Bool
-       minimum :: (Foldable f, Ord a) => repr (f a) -> repr a
-       maximum :: (Foldable f, Ord a) => repr (f a) -> repr a
-       elem    :: (Foldable f, Eq  a) => repr a -> repr (f a) -> repr Bool
-       sum     :: (Foldable f, Num a) => repr (f a) -> repr a
-       product :: (Foldable f, Num a) => repr (f a) -> repr a
-       toList  :: Foldable f => repr (f a) -> repr [a]
-       default foldMap :: (Trans t repr, Foldable f, Monoid m) => t repr (a -> m) -> t repr (f a) -> t repr m
-       default foldr   :: (Trans t repr, Foldable f) => t repr (a -> b -> b) -> t repr b -> t repr (f a) -> t repr b
-       default foldr'  :: (Trans t repr, Foldable f) => t repr (a -> b -> b) -> t repr b -> t repr (f a) -> t repr b
-       default foldl   :: (Trans t repr, Foldable f) => t repr (b -> a -> b) -> t repr b -> t repr (f a) -> t repr b
-       default foldl'  :: (Trans t repr, Foldable f) => t repr (b -> a -> b) -> t repr b -> t repr (f a) -> t repr b
-       default length  :: (Trans t repr, Foldable f) => t repr (f a) -> t repr Int
-       default null    :: (Trans t repr, Foldable f) => t repr (f a) -> t repr Bool
-       default minimum :: (Trans t repr, Foldable f, Ord a) => t repr (f a) -> t repr a
-       default maximum :: (Trans t repr, Foldable f, Ord a) => t repr (f a) -> t repr a
-       default elem    :: (Trans t repr, Foldable f, Eq  a) => t repr a -> t repr (f a) -> t repr Bool
-       default sum     :: (Trans t repr, Foldable f, Num a) => t repr (f a) -> t repr a
-       default product :: (Trans t repr, Foldable f, Num a) => t repr (f a) -> t repr a
-       default toList  :: (Trans t repr, Foldable f) => t repr (f a) -> t repr [a]
-       foldMap = trans_map2 foldMap
-       foldr   = trans_map3 foldr
-       foldr'  = trans_map3 foldr'
-       foldl   = trans_map3 foldl
-       foldl'  = trans_map3 foldl'
-       length  = trans_map1 length
-       null    = trans_map1 null
-       minimum = trans_map1 minimum
-       maximum = trans_map1 maximum
-       elem    = trans_map2 elem
-       sum     = trans_map1 sum
-       product = trans_map1 product
-       toList  = trans_map1 toList
+       foldMap    :: (Foldable f, Monoid m) => repr (a -> m) -> repr (f a) -> repr m
+       foldr      :: Foldable f => repr (a -> b -> b) -> repr b -> repr (f a) -> repr b
+       foldr'     :: Foldable f => repr (a -> b -> b) -> repr b -> repr (f a) -> repr b
+       foldl      :: Foldable f => repr (b -> a -> b) -> repr b -> repr (f a) -> repr b
+       foldl'     :: Foldable f => repr (b -> a -> b) -> repr b -> repr (f a) -> repr b
+       length     :: Foldable f => repr (f a) -> repr Int
+       null       :: Foldable f => repr (f a) -> repr Bool
+       minimum    :: (Foldable f, Ord a) => repr (f a) -> repr a
+       maximum    :: (Foldable f, Ord a) => repr (f a) -> repr a
+       elem       :: (Foldable f, Eq  a) => repr a -> repr (f a) -> repr Bool
+       sum        :: (Foldable f, Num a) => repr (f a) -> repr a
+       product    :: (Foldable f, Num a) => repr (f a) -> repr a
+       toList     :: Foldable f => repr (f a) -> repr [a]
+       all        :: Foldable f => repr (a -> Bool) -> repr (f a) -> repr Bool
+       and        :: Foldable f => repr (f Bool) -> repr Bool
+       any        :: Foldable f => repr (a -> Bool) -> repr (f a) -> repr Bool
+       concat     :: Foldable f => repr (f [a]) -> repr [a]
+       concatMap  :: Foldable f => repr (a -> [b]) -> repr (f a) -> repr [b]
+       find       :: Foldable f => repr (a -> Bool) -> repr (f a) -> repr (Maybe a)
+       foldlM     :: (Foldable f, Monad m) => repr (b -> a -> m b) -> repr b -> repr (f a) -> repr (m b)
+       foldrM     :: (Foldable f, Monad m) => repr (a -> b -> m b) -> repr b -> repr (f a) -> repr (m b)
+       forM_      :: (Foldable f, Monad m) => repr (f a) -> repr (a -> m b) -> repr (m ())
+       for_       :: (Foldable f, Applicative p) => repr (f a) -> repr (a -> p b) -> repr (p ())
+       mapM_      :: (Foldable f, Monad m) => repr (a -> m b) -> repr (f a) -> repr (m ())
+       maximumBy  :: Foldable f => repr (a -> a -> Ordering) -> repr (f a) -> repr a
+       minimumBy  :: Foldable f => repr (a -> a -> Ordering) -> repr (f a) -> repr a
+       notElem    :: (Foldable f, Eq a) => repr a -> repr (f a) -> repr Bool
+       or         :: Foldable f => repr (f Bool) -> repr Bool
+       sequenceA_ :: (Foldable f, Applicative p) => repr (f (p a)) -> repr (p ())
+       sequence_  :: (Foldable f, Monad m) => repr (f (m a)) -> repr (m ())
+       traverse_  :: (Foldable f, Applicative p) => repr (a -> p b) -> repr (f a) -> repr (p ())
+       -- asum :: (Foldable t, GHC.Base.Alternative f) => t (f a) -> f a
+       -- msum :: (Foldable t, GHC.Base.MonadPlus m) => t (m a) -> m a
+
+       default foldMap    :: (Trans t repr, Foldable f, Monoid m) => t repr (a -> m) -> t repr (f a) -> t repr m
+       default foldr      :: (Trans t repr, Foldable f) => t repr (a -> b -> b) -> t repr b -> t repr (f a) -> t repr b
+       default foldr'     :: (Trans t repr, Foldable f) => t repr (a -> b -> b) -> t repr b -> t repr (f a) -> t repr b
+       default foldl      :: (Trans t repr, Foldable f) => t repr (b -> a -> b) -> t repr b -> t repr (f a) -> t repr b
+       default foldl'     :: (Trans t repr, Foldable f) => t repr (b -> a -> b) -> t repr b -> t repr (f a) -> t repr b
+       default length     :: (Trans t repr, Foldable f) => t repr (f a) -> t repr Int
+       default null       :: (Trans t repr, Foldable f) => t repr (f a) -> t repr Bool
+       default minimum    :: (Trans t repr, Foldable f, Ord a) => t repr (f a) -> t repr a
+       default maximum    :: (Trans t repr, Foldable f, Ord a) => t repr (f a) -> t repr a
+       default elem       :: (Trans t repr, Foldable f, Eq  a) => t repr a -> t repr (f a) -> t repr Bool
+       default sum        :: (Trans t repr, Foldable f, Num a) => t repr (f a) -> t repr a
+       default product    :: (Trans t repr, Foldable f, Num a) => t repr (f a) -> t repr a
+       default toList     :: (Trans t repr, Foldable f) => t repr (f a) -> t repr [a]
+       default all        :: (Trans t repr, Foldable f) => t repr (a -> Bool) -> t repr (f a) -> t repr Bool
+       default and        :: (Trans t repr, Foldable f) => t repr (f Bool) -> t repr Bool
+       default any        :: (Trans t repr, Foldable f) => t repr (a -> Bool) -> t repr (f a) -> t repr Bool
+       default concat     :: (Trans t repr, Foldable f) => t repr (f [a]) -> t repr [a]
+       default concatMap  :: (Trans t repr, Foldable f) => t repr (a -> [b]) -> t repr (f a) -> t repr [b]
+       default find       :: (Trans t repr, Foldable f) => t repr (a -> Bool) -> t repr (f a) -> t repr (Maybe a)
+       default foldlM     :: (Trans t repr, Foldable f, Monad m) => t repr (b -> a -> m b) -> t repr b -> t repr (f a) -> t repr (m b)
+       default foldrM     :: (Trans t repr, Foldable f, Monad m) => t repr (a -> b -> m b) -> t repr b -> t repr (f a) -> t repr (m b)
+       default forM_      :: (Trans t repr, Foldable f, Monad m) => t repr (f a) -> t repr (a -> m b) -> t repr (m ())
+       default for_       :: (Trans t repr, Foldable f, Applicative p) => t repr (f a) -> t repr (a -> p b) -> t repr (p ())
+       default mapM_      :: (Trans t repr, Foldable f, Monad m) => t repr (a -> m b) -> t repr (f a) -> t repr (m ())
+       default maximumBy  :: (Trans t repr, Foldable f) => t repr (a -> a -> Ordering) -> t repr (f a) -> t repr a
+       default minimumBy  :: (Trans t repr, Foldable f) => t repr (a -> a -> Ordering) -> t repr (f a) -> t repr a
+       default notElem    :: (Trans t repr, Foldable f, Eq a) => t repr a -> t repr (f a) -> t repr Bool
+       default or         :: (Trans t repr, Foldable f) => t repr (f Bool) -> t repr Bool
+       default sequenceA_ :: (Trans t repr, Foldable f, Applicative p) => t repr (f (p a)) -> t repr (p ())
+       default sequence_  :: (Trans t repr, Foldable f, Monad m) => t repr (f (m a)) -> t repr (m ())
+       default traverse_  :: (Trans t repr, Foldable f, Applicative p) => t repr (a -> p b) -> t repr (f a) -> t repr (p ())
+       
+       foldMap    = trans_map2 foldMap
+       foldr      = trans_map3 foldr
+       foldr'     = trans_map3 foldr'
+       foldl      = trans_map3 foldl
+       foldl'     = trans_map3 foldl'
+       length     = trans_map1 length
+       null       = trans_map1 null
+       minimum    = trans_map1 minimum
+       maximum    = trans_map1 maximum
+       elem       = trans_map2 elem
+       sum        = trans_map1 sum
+       product    = trans_map1 product
+       toList     = trans_map1 toList
+       all        = trans_map2 all
+       and        = trans_map1 and
+       any        = trans_map2 any
+       concat     = trans_map1 concat
+       concatMap  = trans_map2 concatMap
+       find       = trans_map2 find
+       foldlM     = trans_map3 foldlM
+       foldrM     = trans_map3 foldrM
+       forM_      = trans_map2 forM_
+       for_       = trans_map2 for_
+       mapM_      = trans_map2 mapM_
+       maximumBy  = trans_map2 maximumBy
+       minimumBy  = trans_map2 minimumBy
+       notElem    = trans_map2 notElem
+       or         = trans_map1 or
+       sequenceA_ = trans_map1 sequenceA_
+       sequence_  = trans_map1 sequence_
+       traverse_  = trans_map2 traverse_
 instance Sym_Foldable Repr_Host where
-       foldMap = liftM2 Foldable.foldMap
-       foldr   = liftM3 Foldable.foldr
-       foldr'  = liftM3 Foldable.foldr'
-       foldl   = liftM3 Foldable.foldl
-       foldl'  = liftM3 Foldable.foldl'
-       null    = liftM  Foldable.null
-       length  = liftM  Foldable.length
-       minimum = liftM  Foldable.minimum
-       maximum = liftM  Foldable.maximum
-       elem    = liftM2 Foldable.elem
-       sum     = liftM  Foldable.sum
-       product = liftM  Foldable.product
-       toList  = liftM  Foldable.toList
+       foldMap    = liftM2 Foldable.foldMap
+       foldr      = liftM3 Foldable.foldr
+       foldr'     = liftM3 Foldable.foldr'
+       foldl      = liftM3 Foldable.foldl
+       foldl'     = liftM3 Foldable.foldl'
+       null       = liftM  Foldable.null
+       length     = liftM  Foldable.length
+       minimum    = liftM  Foldable.minimum
+       maximum    = liftM  Foldable.maximum
+       elem       = liftM2 Foldable.elem
+       sum        = liftM  Foldable.sum
+       product    = liftM  Foldable.product
+       toList     = liftM  Foldable.toList
+       all        = liftM2 Foldable.all
+       and        = liftM  Foldable.and
+       any        = liftM2 Foldable.any
+       concat     = liftM  Foldable.concat
+       concatMap  = liftM2 Foldable.concatMap
+       find       = liftM2 Foldable.find
+       foldlM     = liftM3 Foldable.foldlM
+       foldrM     = liftM3 Foldable.foldrM
+       forM_      = liftM2 Foldable.forM_
+       for_       = liftM2 Foldable.for_
+       mapM_      = liftM2 Foldable.mapM_
+       maximumBy  = liftM2 Foldable.maximumBy
+       minimumBy  = liftM2 Foldable.minimumBy
+       notElem    = liftM2 Foldable.notElem
+       or         = liftM  Foldable.or
+       sequenceA_ = liftM  Foldable.sequenceA_
+       sequence_  = liftM  Foldable.sequence_
+       traverse_  = liftM2 Foldable.traverse_
 instance Sym_Foldable Repr_Text where
-       foldMap = repr_text_app2 "foldMap"
-       foldr   = repr_text_app3 "foldr"
-       foldr'  = repr_text_app3 "foldr'"
-       foldl   = repr_text_app3 "foldl"
-       foldl'  = repr_text_app3 "foldl'"
-       null    = repr_text_app1 "null"
-       length  = repr_text_app1 "length"
-       minimum = repr_text_app1 "minimum"
-       maximum = repr_text_app1 "maximum"
-       elem    = repr_text_app2 "elem"
-       sum     = repr_text_app1 "sum"
-       product = repr_text_app1 "product"
-       toList  = repr_text_app1 "toList"
+       foldMap    = repr_text_app2 "foldMap"
+       foldr      = repr_text_app3 "foldr"
+       foldr'     = repr_text_app3 "foldr'"
+       foldl      = repr_text_app3 "foldl"
+       foldl'     = repr_text_app3 "foldl'"
+       null       = repr_text_app1 "null"
+       length     = repr_text_app1 "length"
+       minimum    = repr_text_app1 "minimum"
+       maximum    = repr_text_app1 "maximum"
+       elem       = repr_text_app2 "elem"
+       sum        = repr_text_app1 "sum"
+       product    = repr_text_app1 "product"
+       toList     = repr_text_app1 "toList"
+       all        = repr_text_app2 "all"
+       and        = repr_text_app1 "and"
+       any        = repr_text_app2 "any"
+       concat     = repr_text_app1 "concat"
+       concatMap  = repr_text_app2 "concatMap"
+       find       = repr_text_app2 "find"
+       foldlM     = repr_text_app3 "foldlM"
+       foldrM     = repr_text_app3 "foldrM"
+       forM_      = repr_text_app2 "forM_"
+       for_       = repr_text_app2 "for_"
+       mapM_      = repr_text_app2 "mapM_"
+       maximumBy  = repr_text_app2 "maximumBy"
+       minimumBy  = repr_text_app2 "minimumBy"
+       notElem    = repr_text_app2 "notElem"
+       or         = repr_text_app1 "or"
+       sequenceA_ = repr_text_app1 "sequenceA_"
+       sequence_  = repr_text_app1 "sequence_"
+       traverse_  = repr_text_app2 "traverse_"
 instance (Sym_Foldable r1, Sym_Foldable r2) => Sym_Foldable (Repr_Dup r1 r2) where
-       foldMap (f1 `Repr_Dup` f2) (m1 `Repr_Dup` m2) =
-               foldMap f1 m1 `Repr_Dup` foldMap f2 m2
-       foldr (f1 `Repr_Dup` f2) (a1 `Repr_Dup` a2) (m1 `Repr_Dup` m2) =
-               foldr f1 a1 m1 `Repr_Dup` foldr f2 a2 m2
-       foldr' (f1 `Repr_Dup` f2) (a1 `Repr_Dup` a2) (m1 `Repr_Dup` m2) =
-               foldr' f1 a1 m1 `Repr_Dup` foldr' f2 a2 m2
-       foldl (f1 `Repr_Dup` f2) (a1 `Repr_Dup` a2) (m1 `Repr_Dup` m2) =
-               foldl f1 a1 m1 `Repr_Dup` foldl f2 a2 m2
-       foldl' (f1 `Repr_Dup` f2) (a1 `Repr_Dup` a2) (m1 `Repr_Dup` m2) =
-               foldl' f1 a1 m1 `Repr_Dup` foldl' f2 a2 m2
-       length  (f1 `Repr_Dup` f2) = length  f1 `Repr_Dup` length  f2
-       null    (f1 `Repr_Dup` f2) = null    f1 `Repr_Dup` null    f2
-       minimum (f1 `Repr_Dup` f2) = minimum f1 `Repr_Dup` minimum f2
-       maximum (f1 `Repr_Dup` f2) = maximum f1 `Repr_Dup` maximum f2
-       elem    (a1 `Repr_Dup` a2) (f1 `Repr_Dup` f2) = elem a1 f1 `Repr_Dup` elem a2 f2
-       sum     (f1 `Repr_Dup` f2) = sum f1 `Repr_Dup` sum f2
-       product (f1 `Repr_Dup` f2) = product f1 `Repr_Dup` product f2
-       toList  (f1 `Repr_Dup` f2) = toList f1 `Repr_Dup` toList f2
+       foldMap    = repr_dup2 sym_Foldable foldMap
+       foldr      = repr_dup3 sym_Foldable foldr
+       foldr'     = repr_dup3 sym_Foldable foldr'
+       foldl      = repr_dup3 sym_Foldable foldl
+       foldl'     = repr_dup3 sym_Foldable foldl'
+       null       = repr_dup1 sym_Foldable null
+       length     = repr_dup1 sym_Foldable length
+       minimum    = repr_dup1 sym_Foldable minimum
+       maximum    = repr_dup1 sym_Foldable maximum
+       elem       = repr_dup2 sym_Foldable elem
+       sum        = repr_dup1 sym_Foldable sum
+       product    = repr_dup1 sym_Foldable product
+       toList     = repr_dup1 sym_Foldable toList
+       all        = repr_dup2 sym_Foldable all
+       and        = repr_dup1 sym_Foldable and
+       any        = repr_dup2 sym_Foldable any
+       concat     = repr_dup1 sym_Foldable concat
+       concatMap  = repr_dup2 sym_Foldable concatMap
+       find       = repr_dup2 sym_Foldable find
+       foldlM     = repr_dup3 sym_Foldable foldlM
+       foldrM     = repr_dup3 sym_Foldable foldrM
+       forM_      = repr_dup2 sym_Foldable forM_
+       for_       = repr_dup2 sym_Foldable for_
+       mapM_      = repr_dup2 sym_Foldable mapM_
+       maximumBy  = repr_dup2 sym_Foldable maximumBy
+       minimumBy  = repr_dup2 sym_Foldable minimumBy
+       notElem    = repr_dup2 sym_Foldable notElem
+       or         = repr_dup1 sym_Foldable or
+       sequenceA_ = repr_dup1 sym_Foldable sequenceA_
+       sequence_  = repr_dup1 sym_Foldable sequence_
+       traverse_  = repr_dup2 sym_Foldable traverse_
+
+sym_Foldable :: Proxy Sym_Foldable
+sym_Foldable = Proxy
 
 -- * Type 'Expr_Foldable'
 -- | Expression.
index c5bfd566c1e06369055ad9cec2580e9e9055e79c..07ff42a9dc3a65be9e44af6e317fbc1a298da288 100644 (file)
@@ -15,7 +15,7 @@ module Language.Symantic.Expr.Functor where
 import Control.Monad (liftM2)
 import Data.Proxy (Proxy(..))
 import Data.Type.Equality ((:~:)(Refl))
-import Prelude hiding (fmap)
+import Prelude hiding (fmap, (<$))
 import qualified Data.Function as Fun
 import qualified Data.Functor as Functor
 
@@ -45,12 +45,16 @@ infixl 4 <$
 
 instance Sym_Functor Repr_Host where
        fmap = liftM2 Functor.fmap
+       (<$) = liftM2 (Functor.<$)
 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 = repr_dup2 sym_Functor fmap
+       (<$) = repr_dup2 sym_Functor (<$)
+
+sym_Functor :: Proxy Sym_Functor
+sym_Functor = Proxy
 
 -- | 'fmap' alias.
 (<$>) :: (Sym_Functor repr, Functor f)
@@ -82,7 +86,7 @@ fmap_from
  ) => 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
+ -- 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 $
index e341c30d78daa2534607d3d00e66513bdbe363d7..af74ec04341891b12108d4ff81a68927ac13c11c 100644 (file)
@@ -39,10 +39,11 @@ instance Sym_IO Repr_Text where
        io_hClose   = repr_text_app1 "io_hClose"
        io_openFile = repr_text_app2 "io_openFile"
 instance (Sym_IO r1, Sym_IO r2) => Sym_IO (Repr_Dup r1 r2) where
-       io_hClose (h1 `Repr_Dup` h2) =
-               io_hClose h1 `Repr_Dup` io_hClose h2
-       io_openFile (f1 `Repr_Dup` f2) (m1 `Repr_Dup` m2) =
-               io_openFile f1 m1 `Repr_Dup` io_openFile f2 m2
+       io_hClose   = repr_dup1 sym_IO io_hClose
+       io_openFile = repr_dup2 sym_IO io_openFile
+
+sym_IO :: Proxy Sym_IO
+sym_IO = Proxy
 
 -- * Type 'Expr_IO'
 -- | Expression.
index ba538b1eb140f0348d7bd0f9ed8843d9a092abb8..27254623fd74bbe2be3efabc1f9af1cd31a97624 100644 (file)
@@ -37,8 +37,10 @@ instance Sym_If Repr_Text where
                        " else " <> ko p' v
 
 instance (Sym_If r1, Sym_If r2) => Sym_If (Repr_Dup r1 r2) where
-       if_ (c1 `Repr_Dup` c2) (ok1 `Repr_Dup` ok2) (ko1 `Repr_Dup` ko2) =
-               if_ c1 ok1 ko1 `Repr_Dup` if_ c2 ok2 ko2
+       if_ = repr_dup3 sym_If if_
+
+sym_If :: Proxy Sym_If
+sym_If = Proxy
 
 -- * Class 'Sym_When'
 -- | Symantic.
@@ -56,8 +58,10 @@ instance Sym_When Repr_Text where
                        "when " <> cond p' v <>
                        " " <> ok p' v
 instance (Sym_When r1, Sym_When r2) => Sym_When (Repr_Dup r1 r2) where
-       when (c1 `Repr_Dup` c2) (ok1 `Repr_Dup` ok2) =
-               when c1 ok1 `Repr_Dup` when c2 ok2
+       when = repr_dup2 sym_When when
+
+sym_When :: Proxy Sym_When
+sym_When = Proxy
 
 -- * Type 'Expr_If'
 -- | Expression.
index c34c445f8d1b219e250e56e0d149d0ec35616864..a9fb101a6363a7552bc051646d122d0d0ce04ffe 100644 (file)
@@ -6,6 +6,7 @@
 -- | Expression for 'Int'.
 module Language.Symantic.Expr.Int where
 
+import Data.Proxy
 import qualified Data.Text as Text
 
 import Language.Symantic.Type
@@ -29,6 +30,9 @@ instance Sym_Int Repr_Text where
 instance (Sym_Int r1, Sym_Int r2) => Sym_Int (Repr_Dup r1 r2) where
        int x = int x `Repr_Dup` int x
 
+sym_Int :: Proxy Sym_Int
+sym_Int = Proxy
+
 -- * Type 'Expr_Int'
 -- | Expression.
 data Expr_Int (root:: *)
index 5eeee65c6cb38acaf9ae5b9239ec33e49a676e34..fbb479f678d8bea5575f0ad4e6df6d98ec23908b 100644 (file)
@@ -6,6 +6,7 @@
 -- | Expression for 'Integer'.
 module Language.Symantic.Expr.Integer where
 
+import Data.Proxy
 import qualified Data.Text as Text
 
 import Language.Symantic.Type
@@ -26,12 +27,12 @@ instance Sym_Integer Repr_Host where
 instance Sym_Integer Repr_Text where
        integer a = Repr_Text $ \_p _v ->
                Text.pack (show a)
-instance
- ( Sym_Integer r1
- , Sym_Integer r2
- ) => Sym_Integer (Repr_Dup r1 r2) where
+instance (Sym_Integer r1, Sym_Integer r2) => Sym_Integer (Repr_Dup r1 r2) where
        integer x = integer x `Repr_Dup` integer x
 
+sym_Integer :: Proxy Sym_Integer
+sym_Integer = Proxy
+
 -- * Type 'Expr_Integer'
 -- | Expression.
 data Expr_Integer (root:: *)
index 6ae9710bdd66541294ff98baccfa4aee079b3b98..d1a77f1ca1d451dc44a20ef1e01aeee0fa81ec54 100644 (file)
@@ -69,20 +69,17 @@ instance Sym_Integral Repr_Text where
        quotRem   = repr_text_app2 "quotRem"
        divMod    = repr_text_app2 "divMod"
        toInteger = repr_text_app1 "toInteger"
-instance
- ( Sym_Integral r1
- , Sym_Integral r2
- ) => Sym_Integral (Repr_Dup r1 r2) where
-       quot      (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) = quot      x1 y1 `Repr_Dup` quot      x2 y2
-       div       (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) = div       x1 y1 `Repr_Dup` div       x2 y2
-       rem       (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) = rem       x1 y1 `Repr_Dup` rem       x2 y2
-       mod       (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) = mod       x1 y1 `Repr_Dup` mod       x2 y2
-       quotRem   (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) = quotRem   x1 y1 `Repr_Dup` quotRem   x2 y2
-       divMod    (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) = divMod    x1 y1 `Repr_Dup` divMod    x2 y2
-       toInteger (x1 `Repr_Dup` x2)                    = toInteger x1    `Repr_Dup` toInteger x2
+instance (Sym_Integral r1, Sym_Integral r2) => Sym_Integral (Repr_Dup r1 r2) where
+       quot      = repr_dup2 sym_Integral quot
+       rem       = repr_dup2 sym_Integral rem
+       div       = repr_dup2 sym_Integral div
+       mod       = repr_dup2 sym_Integral mod
+       quotRem   = repr_dup2 sym_Integral quotRem
+       divMod    = repr_dup2 sym_Integral divMod
+       toInteger = repr_dup1 sym_Integral toInteger
 
-precedence_Integral :: Precedence
-precedence_Integral  = Precedence 7
+sym_Integral :: Proxy Sym_Integral
+sym_Integral = Proxy
 
 -- * Type 'Expr_Integral'
 -- | Expression.
index 8bb598652465d8ecef36865b938a0394406b21ce..97fb0aecf7a0ad68f510b6292ed1836327a2886c 100644 (file)
@@ -80,7 +80,10 @@ instance Sym_Lambda Repr_Text where
        const = repr_text_app2 "const"
        flip  = repr_text_app1 "flip"
 instance (Sym_Lambda r1, Sym_Lambda r2) => Sym_Lambda (Repr_Dup r1 r2) where
-       ($$) (f1 `Repr_Dup` f2) (x1 `Repr_Dup` x2) = ($$) f1 x1 `Repr_Dup` ($$) f2 x2
+       ($$) = repr_dup2 sym_Lambda ($$)
+
+sym_Lambda :: Proxy Sym_Lambda
+sym_Lambda = Proxy
 
 -- * Type 'Expr_Lambda'
 -- | Expression.
index a54c95f49012bab78915799b93fca9c4609947f1..64d18ebdda62bda540a04499f2ea407522e54dc4 100644 (file)
@@ -69,19 +69,19 @@ instance Sym_List Repr_Text where
        list_zipWith = repr_text_app3 "list_zipWith"
        list_reverse = repr_text_app1 "list_reverse"
 instance (Sym_List r1, Sym_List r2) => Sym_List (Repr_Dup r1 r2) where
-       list_empty = list_empty `Repr_Dup` list_empty
-       list_cons (a1 `Repr_Dup` a2) (l1 `Repr_Dup` l2) = list_cons a1 l1 `Repr_Dup` list_cons a2 l2
+       list_empty = repr_dup0 sym_List list_empty
+       list_cons  = repr_dup2 sym_List list_cons
        list l =
                let (l1, l2) =
                        foldr (\(x1 `Repr_Dup` x2) (xs1, xs2) ->
                                (x1:xs1, x2:xs2)) ([], []) l in
                list l1 `Repr_Dup` list l2
-       list_filter (f1 `Repr_Dup` f2) (l1 `Repr_Dup` l2) =
-               list_filter f1 l1 `Repr_Dup` list_filter f2 l2
-       list_zipWith (f1 `Repr_Dup` f2) (la1 `Repr_Dup` la2) (lb1 `Repr_Dup` lb2) =
-               list_zipWith f1 la1 lb1 `Repr_Dup` list_zipWith f2 la2 lb2
-       list_reverse (l1 `Repr_Dup` l2) =
-               list_reverse l1 `Repr_Dup` list_reverse l2
+       list_filter  = repr_dup2 sym_List list_filter
+       list_zipWith = repr_dup3 sym_List list_zipWith
+       list_reverse = repr_dup1 sym_List list_reverse
+
+sym_List :: Proxy Sym_List
+sym_List = Proxy
 
 -- * Type 'Expr_List'
 -- | Expression.
index 1bf7b1268f4e4163022e36c0221a0693b0080591..7c50979c634405a8ddbbf9de5e5ffe5c09402087 100644 (file)
@@ -78,24 +78,18 @@ instance Sym_Map Repr_Text where
        map_difference   = repr_text_app2 "map_difference"
        map_foldrWithKey = repr_text_app3 "map_foldrWithKey"
 instance (Sym_Map r1, Sym_Map r2) => Sym_Map (Repr_Dup r1 r2) where
-       map_from_list (l1 `Repr_Dup` l2) =
-               map_from_list l1 `Repr_Dup` map_from_list l2
-       mapWithKey (f1 `Repr_Dup` f2) (m1 `Repr_Dup` m2) =
-               mapWithKey f1 m1 `Repr_Dup` mapWithKey f2 m2
-       map_lookup (k1 `Repr_Dup` k2) (m1 `Repr_Dup` m2) =
-               map_lookup k1 m1 `Repr_Dup` map_lookup k2 m2
-       map_keys (m1 `Repr_Dup` m2) =
-               map_keys m1 `Repr_Dup` map_keys m2
-       map_member (k1 `Repr_Dup` k2) (m1 `Repr_Dup` m2) =
-               map_member k1 m1 `Repr_Dup` map_member k2 m2
-       map_insert (k1 `Repr_Dup` k2) (a1 `Repr_Dup` a2) (m1 `Repr_Dup` m2) =
-               map_insert k1 a1 m1 `Repr_Dup` map_insert k2 a2 m2
-       map_delete (k1 `Repr_Dup` k2) (m1 `Repr_Dup` m2) =
-               map_delete k1 m1 `Repr_Dup` map_delete k2 m2
-       map_difference (ma1 `Repr_Dup` ma2) (mb1 `Repr_Dup` mb2) =
-               map_difference ma1 mb1 `Repr_Dup` map_difference ma2 mb2
-       map_foldrWithKey (f1 `Repr_Dup` f2) (b1 `Repr_Dup` b2) (m1 `Repr_Dup` m2) =
-               map_foldrWithKey f1 b1 m1 `Repr_Dup` map_foldrWithKey f2 b2 m2
+       map_from_list    = repr_dup1 sym_Map map_from_list
+       mapWithKey       = repr_dup2 sym_Map mapWithKey
+       map_lookup       = repr_dup2 sym_Map map_lookup
+       map_keys         = repr_dup1 sym_Map map_keys
+       map_member       = repr_dup2 sym_Map map_member
+       map_insert       = repr_dup3 sym_Map map_insert
+       map_delete       = repr_dup2 sym_Map map_delete
+       map_difference   = repr_dup2 sym_Map map_difference
+       map_foldrWithKey = repr_dup3 sym_Map map_foldrWithKey
+
+sym_Map :: Proxy Sym_Map
+sym_Map = Proxy
 
 -- | Parsing utility to check that the given type is a 'Type_List'
 -- or raise 'Error_Expr_Type_mismatch'.
index f8a326a0860e75361a66378b9dc1608e252403d9..4d4269ef1fb327af8b1c4cb091f5a45a282f88bd 100644 (file)
@@ -30,7 +30,7 @@ import Language.Symantic.Trans.Common
 class Sym_Maybe repr where
        nothing :: repr (Maybe a)
        just    :: repr a -> repr (Maybe a)
-       maybe :: repr b -> repr ((->) a b) -> repr (Maybe a) -> repr b
+       maybe   :: repr b -> repr ((->) a b) -> repr (Maybe a) -> repr b
        
        default nothing :: Trans t repr => t repr (Maybe a)
        default just    :: Trans t repr => t repr a -> t repr (Maybe a)
@@ -44,16 +44,16 @@ instance Sym_Maybe Repr_Host where
        just    = liftM Just
        maybe   = liftM3 Maybe.maybe
 instance Sym_Maybe Repr_Text where
-       nothing =
-               Repr_Text $ \_p _v ->
-                       "nothing"
-       just  = repr_text_app1 "just"
-       maybe = repr_text_app3 "maybe"
+       nothing = repr_text_app0 "nothing"
+       just    = repr_text_app1 "just"
+       maybe   = repr_text_app3 "maybe"
 instance (Sym_Maybe r1, Sym_Maybe r2) => Sym_Maybe (Repr_Dup r1 r2) where
-       nothing = nothing `Repr_Dup` nothing
-       just (a1 `Repr_Dup` a2) = just a1 `Repr_Dup` just a2
-       maybe (m1 `Repr_Dup` m2) (n1 `Repr_Dup` n2) (j1 `Repr_Dup` j2) =
-               maybe m1 n1 j1 `Repr_Dup` maybe m2 n2 j2
+       nothing = repr_dup0 sym_Maybe nothing
+       just    = repr_dup1 sym_Maybe just
+       maybe   = repr_dup3 sym_Maybe maybe
+
+sym_Maybe :: Proxy Sym_Maybe
+sym_Maybe = Proxy
 
 -- * Type 'Expr_Maybe'
 -- | Expression.
index ad6f4b23ef5d72cc2045d07308d44c4ad5adf42e..6986f139839d1c4cd0026c8adf80062856801648 100644 (file)
@@ -48,15 +48,12 @@ instance Sym_Monad Repr_Host where
 instance Sym_Monad Repr_Text where
        return = repr_text_app1 "return"
        (>>=)  = repr_text_infix ">>=" (Precedence 1)
+instance (Sym_Monad r1, Sym_Monad r2) => Sym_Monad (Repr_Dup r1 r2) where
+       return = repr_dup1 sym_Monad return
+       (>>=)  = repr_dup2 sym_Monad (>>=)
 
-instance
- ( Sym_Monad r1
- , Sym_Monad r2
- ) => Sym_Monad (Repr_Dup r1 r2) where
-       return (a1 `Repr_Dup` a2) =
-               return a1 `Repr_Dup` return a2
-       (>>=) (m1 `Repr_Dup` m2) (f1 `Repr_Dup` f2) =
-               (>>=) m1 f1 `Repr_Dup` (>>=) m2 f2
+sym_Monad :: Proxy Sym_Monad
+sym_Monad = Proxy
 
 -- * Type 'Expr_Monad'
 -- | Expression.
index 78911b64c05c4a37b6686fd32dbc7c62a6bf19bd..92183c920c411b46b5cfe216e3985b969dd68e48 100644 (file)
@@ -32,20 +32,19 @@ import Language.Symantic.Trans.Common
 -- * 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 :: MonoFunctor o => repr (MT.Element o -> MT.Element o) -> repr o -> repr o
+       default omap :: (Trans t repr, MonoFunctor o)
+        => t repr (MT.Element o -> MT.Element o) -> t repr o -> t repr o
        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 (Repr_Dup r1 r2) where
-       omap (f1 `Repr_Dup` f2) (m1 `Repr_Dup` m2) =
-               omap f1 m1 `Repr_Dup` omap f2 m2
+instance (Sym_MonoFunctor r1, Sym_MonoFunctor r2) => Sym_MonoFunctor (Repr_Dup r1 r2) where
+       omap = repr_dup2 sym_MonoFunctor omap
+
+sym_MonoFunctor :: Proxy Sym_MonoFunctor
+sym_MonoFunctor = Proxy
 
 -- * Type 'Expr_MonoFunctor'
 -- | Expression.
@@ -71,7 +70,7 @@ omap_from
  ) => ast -> ast
  -> ExprFrom ast (Expr_MonoFunctor root) hs ret
 omap_from ast_f ast_m ex ast ctx k =
- -- NOTE: omap :: (Element mono -> Element mono) -> mono -> mono
+ -- omap :: (Element mono -> Element 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 $
index 8fa6b1c41883061b4c5e350e4f5afd32fa3c0d10..d3f91f7a0c43908024a50cd7b4449e243e26e876 100644 (file)
@@ -38,8 +38,14 @@ instance Sym_Monoid Repr_Host where
        mempty  = Repr_Host Monoid.mempty
        mappend = liftM2 Monoid.mappend
 instance Sym_Monoid Repr_Text where
-       mempty  = Repr_Text $ \_p _v -> "mempty"
+       mempty  = repr_text_app0 "mempty"
        mappend = repr_text_app2 "mappend"
+instance (Sym_Monoid r1, Sym_Monoid r2) => Sym_Monoid (Repr_Dup r1 r2) where
+       mempty  = repr_dup0 sym_Monoid mempty
+       mappend = repr_dup2 sym_Monoid mappend
+
+sym_Monoid :: Proxy Sym_Monoid
+sym_Monoid = Proxy
 
 -- | 'mappend' alias.
 (<>) ::
index 4d409528c553da1f98381ce8bb904d28e22e3ccf..11a30fba7dc599a21006294f72b71bccc905e194 100644 (file)
@@ -69,13 +69,16 @@ instance Sym_Num Repr_Text where
        (*)         = repr_text_infix "-" (Precedence 7)
        fromInteger = repr_text_app1 "fromInteger"
 instance (Sym_Num r1, Sym_Num r2) => Sym_Num (Repr_Dup r1 r2) where
-       abs    (x1 `Repr_Dup` x2)                    = abs x1    `Repr_Dup` abs x2
-       negate (x1 `Repr_Dup` x2)                    = negate x1 `Repr_Dup` negate x2
-       signum (x1 `Repr_Dup` x2)                    = signum x1 `Repr_Dup` signum x2
-       (+)    (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) = (+) x1 y1 `Repr_Dup` (+) x2 y2
-       (-)    (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) = (-) x1 y1 `Repr_Dup` (-) x2 y2
-       (*)    (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) = (*) x1 y1 `Repr_Dup` (*) x2 y2
-       fromInteger (x1 `Repr_Dup` x2) = fromInteger x1 `Repr_Dup` fromInteger x2
+       abs         = repr_dup1 sym_Num abs
+       negate      = repr_dup1 sym_Num negate
+       signum      = repr_dup1 sym_Num signum
+       (+)         = repr_dup2 sym_Num (+)
+       (-)         = repr_dup2 sym_Num (-)
+       (*)         = repr_dup2 sym_Num (*)
+       fromInteger = repr_dup1 sym_Num fromInteger
+
+sym_Num :: Proxy Sym_Num
+sym_Num = Proxy
 
 -- * Type 'Expr_Num'
 -- | Expression.
index 0b4a2617194ddc19be54a11e1e28a3ac1c6d49e9..9f13260f7a4bf20df74e8b1db07aa8fe3a33182e 100644 (file)
@@ -67,31 +67,24 @@ instance Sym_Ord Repr_Host where
        min     = liftM2 Ord.min
        max     = liftM2 Ord.max
 instance Sym_Ord Repr_Text where
-       compare = repr_text_app2 "compare"
+       compare = repr_text_app2  "compare"
        (<)     = repr_text_infix "<"  (Precedence 4)
        (<=)    = repr_text_infix "<=" (Precedence 4)
        (>)     = repr_text_infix ">"  (Precedence 4)
        (>=)    = repr_text_infix ">=" (Precedence 4)
-       min     = repr_text_app2 "min"
-       max     = repr_text_app2 "max"
-instance
- ( Sym_Ord r1
- , Sym_Ord r2
- ) => Sym_Ord (Repr_Dup r1 r2) where
-       compare (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) =
-               compare x1 y1 `Repr_Dup` compare x2 y2
-       (<) (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) =
-               (<) x1 y1 `Repr_Dup` (<) x2 y2
-       (<=) (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) =
-               (<=) x1 y1 `Repr_Dup` (<=) x2 y2
-       (>) (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) =
-               (>) x1 y1 `Repr_Dup` (>) x2 y2
-       (>=) (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) =
-               (>=) x1 y1 `Repr_Dup` (>=) x2 y2
-       min (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) =
-               min x1 y1 `Repr_Dup` min x2 y2
-       max (x1 `Repr_Dup` x2) (y1 `Repr_Dup` y2) =
-               max x1 y1 `Repr_Dup` max x2 y2
+       min     = repr_text_app2  "min"
+       max     = repr_text_app2  "max"
+instance (Sym_Ord r1, Sym_Ord r2) => Sym_Ord (Repr_Dup r1 r2) where
+       compare = repr_dup2 sym_Ord compare
+       (<)     = repr_dup2 sym_Ord (<)
+       (<=)    = repr_dup2 sym_Ord (<=)
+       (>)     = repr_dup2 sym_Ord (>)
+       (>=)    = repr_dup2 sym_Ord (>=)
+       min     = repr_dup2 sym_Ord min
+       max     = repr_dup2 sym_Ord max
+
+sym_Ord :: Proxy Sym_Ord
+sym_Ord = Proxy
 
 -- * Type 'Expr_Ord'
 -- | Expression.
index 5e07f61acf8ebd13d54f1e03d64307907c774241..142c59d1b149709c10d84bc071085dc51699b0ce 100644 (file)
@@ -6,6 +6,7 @@
 -- | Expression for 'Text'.
 module Language.Symantic.Expr.Text where
 
+import Data.Proxy
 import Data.Text (Text)
 import qualified Data.Text as Text
 
@@ -26,12 +27,12 @@ instance Sym_Text Repr_Host where
        text = Repr_Host
 instance Sym_Text Repr_Text where
        text a = Repr_Text $ \_p _v -> Text.pack (show a)
-instance
- ( Sym_Text r1
- , Sym_Text r2
- ) => Sym_Text (Repr_Dup r1 r2) where
+instance (Sym_Text r1, Sym_Text r2) => Sym_Text (Repr_Dup r1 r2) where
        text x = text x `Repr_Dup` text x
 
+sym_Text :: Proxy Sym_Text
+sym_Text = Proxy
+
 -- * Type 'Expr_Text'
 -- | Expression.
 data Expr_Text (root:: *)
index 9a7d7aefd81cff5b5e1027c680c5c0355a1729f7..b57510bdfebffe25e9bbd4edc548d9b79df26ee5 100644 (file)
@@ -41,12 +41,11 @@ 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 (Repr_Dup r1 r2) where
-       traverse (f1 `Repr_Dup` f2) (m1 `Repr_Dup` m2) =
-               traverse f1 m1 `Repr_Dup` traverse f2 m2
+instance (Sym_Traversable r1, Sym_Traversable r2) => Sym_Traversable (Repr_Dup r1 r2) where
+       traverse = repr_dup2 sym_Traversable traverse
+
+sym_Traversable :: Proxy Sym_Traversable
+sym_Traversable = Proxy
 
 -- * Type 'Expr_Traversable'
 -- | Expression.
index d77aa8e7edfcfdefce8deddbe355caed484a731b..9f3f7410014bca67d3b68a5077d70570113dd397 100644 (file)
@@ -47,14 +47,13 @@ instance Sym_Tuple2 Repr_Text where
                        "(" <> a p' v <> ", " <> b p' v <> ")"
        fst = repr_text_app1 "fst"
        snd = repr_text_app1 "snd"
-instance
- ( Sym_Tuple2 r1
- , Sym_Tuple2 r2
- ) => Sym_Tuple2 (Repr_Dup r1 r2) where
-       tuple2 (a1 `Repr_Dup` a2) (b1 `Repr_Dup` b2) =
-               tuple2 a1 b1 `Repr_Dup` tuple2 a2 b2
-       fst (t1 `Repr_Dup` t2) = fst t1 `Repr_Dup` fst t2
-       snd (t1 `Repr_Dup` t2) = snd t1 `Repr_Dup` snd t2
+instance (Sym_Tuple2 r1, Sym_Tuple2 r2) => Sym_Tuple2 (Repr_Dup r1 r2) where
+       tuple2 = repr_dup2 sym_Tuple2 tuple2
+       fst    = repr_dup1 sym_Tuple2 fst
+       snd    = repr_dup1 sym_Tuple2 snd
+
+sym_Tuple2 :: Proxy Sym_Tuple2
+sym_Tuple2 = Proxy
 
 -- * Type 'Expr_Tuple2'
 -- | Expression.
index 55221c499785a999b79a6f76781841ff39a681e8..cd07e3c7fa2296c7f8bb965861940dee41e36e95 100644 (file)
@@ -1,7 +1,9 @@
+{-# LANGUAGE ConstraintKinds #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE Rank2Types #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE UndecidableInstances #-}
 -- | Interpreter to duplicate the representation of an expression
 -- 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
index e98317a95b27e26f9656192910e7f0efb6c8d5fe..00b6f7654cce7bc73aa811f82fb7e0a0a3dfc4e1 100644 (file)
@@ -37,6 +37,8 @@ text_from_expr r = unRepr_Text r precedence_Toplevel 0
 -- * Helpers
 
 -- ** Helpers for lambda applications
+repr_text_app0 :: Text -> Repr_Text h
+repr_text_app0 name = Repr_Text $ \_p _v -> name
 repr_text_app1
  :: Text
  -> Repr_Text a1
index 22d174b576ce7dd8fc5796098bfc1840b2c03c23..656304561e51fe68d1153b57cb6764ed7b326e2f 100644 (file)
@@ -28,8 +28,8 @@ instance Type0_Constraint Ord (Type_Bool root) where
 instance Type0_Constraint Monoid (Type_Bool root)
 instance Type0_Constraint Num (Type_Bool root)
 instance Type0_Constraint Integral (Type_Bool root)
-instance Type0_Constraint MT.MonoFunctor (Type_Bool root)
 instance Type0_Family Type_Family_MonoElement (Type_Bool root)
+instance Type0_Constraint MT.MonoFunctor (Type_Bool root)
 instance String_from_Type (Type_Bool root) where
        string_from_type _ = "Bool"
 
index fb8f41bdc3ccf45419b1b52c3da86441e7cbf4d1..be052f96f894fdfe39e7098679d7ff6c48677fbd 100644 (file)
@@ -29,8 +29,8 @@ instance Type0_Constraint Ord (Type_Char root) where
 instance Type0_Constraint Monoid (Type_Char root)
 instance Type0_Constraint Num (Type_Char root)
 instance Type0_Constraint Integral (Type_Char root)
-instance Type0_Constraint MT.MonoFunctor (Type_Char root)
 instance Type0_Family Type_Family_MonoElement (Type_Char root)
+instance Type0_Constraint MT.MonoFunctor (Type_Char root)
 instance String_from_Type (Type_Char root) where
        string_from_type _ = "Char"
 
index aa66a817dc94714af3d4705b868a0fc6338525e3..4d99116eebc5c5524a1c7d04263a7f5afe356393 100644 (file)
@@ -56,6 +56,8 @@ instance
        type0_constraint _c _ = Nothing
 instance Type0_Constraint Num (Type_Either root)
 instance Type0_Constraint Integral (Type_Either root)
+instance Type0_Family Type_Family_MonoElement (Type_Either root) where
+       type0_family _at (Type2 _px _l r) = Just r
 instance Type0_Constraint MT.MonoFunctor (Type_Either root) where
        type0_constraint _c Type2{} = Just Dict
 instance Type1_Constraint Functor (Type_Either root) where
@@ -68,8 +70,6 @@ instance Type1_Constraint Foldable (Type_Either root) where
        type1_constraint _c Type2{} = Just Dict
 instance Type1_Constraint Monad (Type_Either root) where
        type1_constraint _c Type2{} = Just Dict
-instance Type0_Family Type_Family_MonoElement (Type_Either root) where
-       type0_family _at (Type2 _px _l r) = Just r
 instance -- Type0_Eq
  Type0_Eq root =>
  Type0_Eq (Type_Either root) where
index 6ea443776580a9501c3c118d354dabfca0386360..bde249ef31e04dc1323cdf1b9e70ee39484f3737 100644 (file)
@@ -53,6 +53,8 @@ instance
        type0_constraint _c _ = Nothing
 instance Type0_Constraint Num (Type_Fun root)
 instance Type0_Constraint Integral (Type_Fun root)
+instance Type0_Family Type_Family_MonoElement (Type_Fun root) where
+       type0_family _at (Type2 _px _r a) = Just a
 instance Type0_Constraint MT.MonoFunctor (Type_Fun root) where
        type0_constraint _c Type2{} = Just Dict
 instance Type1_Constraint Functor (Type_Fun root) where
@@ -63,8 +65,6 @@ instance Type1_Constraint Foldable (Type_Fun root)
 instance Type1_Constraint Traversable (Type_Fun root)
 instance Type1_Constraint Monad (Type_Fun root) where
        type1_constraint _c Type2{} = Just Dict
-instance Type0_Family Type_Family_MonoElement (Type_Fun root) where
-       type0_family _at (Type2 _px _r a) = Just a
 
 instance -- Type0_Eq
  Type0_Eq root =>
index 502b6565e00498e0fe6fa298af7d67efe12a191b..42071c7682ba9befff37a9e700d21d1332f1c39a 100644 (file)
@@ -32,6 +32,8 @@ instance Type0_Constraint Ord (Type_IO root)
 instance Type0_Constraint Monoid (Type_IO root)
 instance Type0_Constraint Num (Type_IO root)
 instance Type0_Constraint Integral (Type_IO root)
+instance Type0_Family Type_Family_MonoElement (Type_IO root) where
+       type0_family _at (Type1 _px a) = Just a
 instance Type0_Constraint MT.MonoFunctor (Type_IO root) where
        type0_constraint _c Type1{} = Just Dict
 instance Type1_Constraint Functor (Type_IO root) where
@@ -40,8 +42,6 @@ instance Type1_Constraint Applicative (Type_IO root) where
        type1_constraint _c Type1{} = Just Dict
 instance Type1_Constraint Monad (Type_IO root) where
        type1_constraint _c Type1{} = Just Dict
-instance Type0_Family Type_Family_MonoElement (Type_IO root) where
-       type0_family _at (Type1 _px a) = Just a
 instance -- Type0_Eq
  Type0_Eq root =>
  Type0_Eq (Type_IO root) where
index 72eb2aa29cf540db27fbfba60d5d17115b523bd4..f22c8c27afc983a5b1c8a9b8fb0373874a2180c6 100644 (file)
@@ -31,8 +31,8 @@ instance Type0_Constraint Num (Type_Int root) where
        type0_constraint _c Type0{} = Just Dict
 instance Type0_Constraint Integral (Type_Int root) where
        type0_constraint _c Type0{} = Just Dict
-instance Type0_Constraint MT.MonoFunctor (Type_Int root)
 instance Type0_Family Type_Family_MonoElement (Type_Int root)
+instance Type0_Constraint MT.MonoFunctor (Type_Int root)
 instance String_from_Type (Type_Int root) where
        string_from_type _ = "Int"
 
index 4631144eaccef8d2003e5de3e706998389699489..afe34603bea0c7c8d34ac516da4ad57cfdca3a3d 100644 (file)
@@ -31,8 +31,8 @@ instance Type0_Constraint Num (Type_Integer root) where
        type0_constraint _c Type0{} = Just Dict
 instance Type0_Constraint Integral (Type_Integer root) where
        type0_constraint _c Type0{} = Just Dict
-instance Type0_Constraint MT.MonoFunctor (Type_Integer root)
 instance Type0_Family Type_Family_MonoElement (Type_Integer root)
+instance Type0_Constraint MT.MonoFunctor (Type_Integer root)
 instance String_from_Type (Type_Integer root) where
        string_from_type _ = "Integer"
 
index 1c97ee8c3d358004fa99dfd59bb129307a03419d..4429c7dce47cabb80cd0d53e87c406291d46d378 100644 (file)
@@ -37,6 +37,8 @@ instance Type0_Constraint Monoid (Type_List root) where
        type0_constraint _c Type1{} = Just Dict
 instance Type0_Constraint Num (Type_List root)
 instance Type0_Constraint Integral (Type_List root)
+instance Type0_Family Type_Family_MonoElement (Type_List root) where
+       type0_family _at (Type1 _px a) = Just a
 instance Type0_Constraint MT.MonoFunctor (Type_List root) where
        type0_constraint _c Type1{} = Just Dict
 instance Type1_Constraint Functor (Type_List root) where
@@ -49,8 +51,6 @@ instance Type1_Constraint Traversable (Type_List root) where
        type1_constraint _c Type1{} = Just Dict
 instance Type1_Constraint Monad (Type_List root) where
        type1_constraint _c Type1{} = Just Dict
-instance Type0_Family Type_Family_MonoElement (Type_List root) where
-       type0_family _at (Type1 _px a) = Just a
 instance -- Type0_Eq
  Type0_Eq root =>
  Type0_Eq (Type_List root) where
index 214f294bc9737e72044d3fb88a2b6315a27c947e..ca810bb9666a3bd5be174aa7443ca35c045072fe 100644 (file)
@@ -40,6 +40,8 @@ instance Type0_Constraint Monoid root => Type0_Constraint Monoid (Type_Maybe roo
        type0_constraint _c _ = Nothing
 instance Type0_Constraint Num (Type_Maybe root)
 instance Type0_Constraint Integral (Type_Maybe root)
+instance Type0_Family Type_Family_MonoElement (Type_Maybe root) where
+       type0_family _at (Type1 _px a) = Just a
 instance Type0_Constraint MT.MonoFunctor (Type_Maybe root) where
        type0_constraint _c Type1{} = Just Dict
 instance Type1_Constraint Functor (Type_Maybe root) where
@@ -52,8 +54,6 @@ instance Type1_Constraint Traversable (Type_Maybe root) where
        type1_constraint _c (Type1 _ _) = Just Dict
 instance Type1_Constraint Monad (Type_Maybe root) where
        type1_constraint _c Type1{} = Just Dict
-instance Type0_Family Type_Family_MonoElement (Type_Maybe root) where
-       type0_family _at (Type1 _px a) = Just a
 instance -- Type0_Eq
  Type0_Eq root =>
  Type0_Eq (Type_Maybe root) where
index 65a375babe124a5cf4f63c61073f660d56a1e57a..d8223adcaf176f5b4769d6cb178c3bac78853c6d 100644 (file)
@@ -32,11 +32,11 @@ instance Type0_Constraint Monoid (Type_Text root) where
        type0_constraint _c Type0{} = Just Dict
 instance Type0_Constraint Num (Type_Text root)
 instance Type0_Constraint Integral (Type_Text root)
-instance Type0_Constraint MT.MonoFunctor (Type_Text root) where
-       type0_constraint _c Type0{} = Just Dict
 instance Type_Root_Lift (Type0 (Proxy (MT.Element Text))) root =>
          Type0_Family Type_Family_MonoElement (Type_Text root) where
        type0_family _at Type0{} = Just type0
+instance Type0_Constraint MT.MonoFunctor (Type_Text root) where
+       type0_constraint _c Type0{} = Just Dict
 instance -- String_from_Type
  String_from_Type (Type_Text root) where
        string_from_type _ = "Text"
index e4bb79f5b4b45c8b923af722e6f57ac5cb6469a3..f4552048b8efc31a517461cae751a0bf70a47876 100644 (file)
@@ -59,6 +59,8 @@ instance
        type0_constraint _c _ = Nothing
 instance Type0_Constraint Num (Type_Tuple2 root)
 instance Type0_Constraint Integral (Type_Tuple2 root)
+instance Type0_Family Type_Family_MonoElement (Type_Tuple2 root) where
+       type0_family _at (Type2 _px _a b) = Just b
 instance Type0_Constraint MT.MonoFunctor (Type_Tuple2 root) where
        type0_constraint _c Type2{} = Just Dict
 instance Type1_Constraint Functor (Type_Tuple2 root) where
@@ -74,8 +76,6 @@ instance Type1_Constraint Foldable (Type_Tuple2 root) where
        type1_constraint _c Type2{} = Just Dict
 instance Type1_Constraint Traversable (Type_Tuple2 root) where
        type1_constraint _c Type2{} = Just Dict
-instance Type0_Family Type_Family_MonoElement (Type_Tuple2 root) where
-       type0_family _at (Type2 _px _a b) = Just b
 instance -- Type0_Eq
  Type0_Eq root =>
  Type0_Eq (Type_Tuple2 root) where
index 5e1846c5a289d2b6f881ce09467a3212bc168355..9193b9ecf3764c9562bca32b39a785fdb2fd6b4e 100644 (file)
@@ -29,8 +29,8 @@ instance Type0_Constraint Ord (Type_Unit root) where
 instance Type0_Constraint Monoid (Type_Unit root)
 instance Type0_Constraint Num (Type_Unit root)
 instance Type0_Constraint Integral (Type_Unit root)
-instance Type0_Constraint MT.MonoFunctor (Type_Unit root)
 instance Type0_Family Type_Family_MonoElement (Type_Unit root)
+instance Type0_Constraint MT.MonoFunctor (Type_Unit root)
 instance String_from_Type (Type_Unit root) where
        string_from_type _ = "()"