Add tar GNUmakefile target.
[haskell/symantic.git] / symantic-lib / Language / Symantic / Lib / Foldable.hs
index c64d0af03d7f993ef4aaeaca46554f5ecc4aad7e..94e582322d98dc0eddca2ec7db3ab06665c2fd0a 100644 (file)
@@ -25,7 +25,7 @@ import Language.Symantic.Lib.Num (tyNum)
 import Language.Symantic.Lib.Ord (tyOrd)
 
 -- * Class 'Sym_Foldable'
-type instance Sym (Proxy Foldable) = Sym_Foldable
+type instance Sym Foldable = Sym_Foldable
 class Sym_Foldable term where
        foldMap    :: Foldable f => Monoid m      => term (a -> m) -> term (f a) -> term m
        foldr      :: Foldable f                  => term (a -> b -> b) -> term b -> term (f a) -> term b
@@ -237,13 +237,15 @@ instance (Sym_Foldable r1, Sym_Foldable r2) => Sym_Foldable (Dup r1 r2) where
 instance (Sym_Foldable term, Sym_Lambda term) => Sym_Foldable (BetaT term)
 
 -- Typing
+instance NameTyOf Foldable where
+       nameTyOf _c = ["Foldable"] `Mod` "Foldable"
 instance FixityOf Foldable
 instance ClassInstancesFor Foldable
 instance TypeInstancesFor Foldable
 
 -- Compiling
 instance Gram_Term_AtomsFor src ss g Foldable
-instance (Source src, Inj_Sym ss Foldable) => ModuleFor src ss Foldable where
+instance (Source src, SymInj ss Foldable) => ModuleFor src ss Foldable where
        moduleFor = ["Foldable"] `moduleWhere`
         [ "foldMap" := teFoldable_foldMap
         , "foldr"   := teFoldable_foldr
@@ -266,15 +268,15 @@ instance (Source src, Inj_Sym ss Foldable) => ModuleFor src ss Foldable where
 tyFoldable :: Source src => Type src vs a -> Type src vs (Foldable a)
 tyFoldable a = tyConstLen @(K Foldable) @Foldable (lenVars a) `tyApp` a
 
-t0 :: Source src => Inj_Len vs => Inj_Kind (K t) =>
+t0 :: Source src => LenInj vs => KindInj (K t) =>
       Type src (Proxy t ': vs) t
 t0 = tyVar "t" $ varZ
 
-t1 :: Source src => Inj_Len vs => Inj_Kind (K t) =>
+t1 :: Source src => LenInj vs => KindInj (K t) =>
       Type src (a ': Proxy t ': vs) t
 t1 = tyVar "t" $ VarS varZ
 
-t2 :: Source src => Inj_Len vs => Inj_Kind (K t) =>
+t2 :: Source src => LenInj vs => KindInj (K t) =>
       Type src (a ': b ': Proxy t ': vs) t
 t2 = tyVar "t" $ VarS $ VarS varZ
 
@@ -282,7 +284,7 @@ t2 = tyVar "t" $ VarS $ VarS varZ
 teFoldable_foldMap :: TermDef Foldable '[Proxy a, Proxy t, Proxy m] (Foldable t # Monoid m #> ((a -> m) -> t a -> m))
 teFoldable_foldMap = Term (tyFoldable t1 # tyMonoid m) ((a0 ~> m) ~> t1 `tyApp` a0 ~> m) $ teSym @Foldable $ lam2 foldMap
        where
-       m :: Source src => Inj_Len vs => Inj_Kind (K m) =>
+       m :: Source src => LenInj vs => KindInj (K m) =>
             Type src (a ': b ': Proxy m ': vs) m
        m = tyVar "m" $ VarS $ VarS varZ
 
@@ -330,7 +332,7 @@ teFoldable_asum = Term (tyFoldable t1 # tyAlternative f2) (t1 `tyApp` (f2 `tyApp
 
 {- TODO: when MonadPlus will be supported
 teFoldable_msum ::
- Source src => Inj_Sym ss Foldable =>
+ Source src => SymInj ss Foldable =>
  Term src ss ts '[Proxy a, Proxy t, Proxy f] ((Foldable t # MonadPlus f) #> (t (f a) -> f a))
 teFoldable_msum =
        Term ((tyFoldable t1 # (tyConst @(K MonadPlus) @MonadPlus `tyApp` f2))) (t1 `tyApp` (f2 `tyApp` a0) ~> (f2 `tyApp` a0)) $