mirror of
https://github.com/coot/free-category.git
synced 2024-11-22 16:22:05 +03:00
Fixed ghc-8.10.1 errors
This commit is contained in:
parent
1ad08548dd
commit
e646191f3c
@ -1,3 +1,10 @@
|
||||
index-state: 2020-05-15T00:00:00Z
|
||||
packages: free-category.cabal
|
||||
examples/examples.cabal
|
||||
|
||||
-- free-algebras-0.0.8.2 with ghc-8.10.1 support
|
||||
source-repository-package
|
||||
type: git
|
||||
location: https://github.com/coot/free-algebras
|
||||
tag: 5a60cb63ff3e4aab44a2e270dd31d736abd9b0f5
|
||||
--sha256: 0iim1s19rd75v4kax5fnzway35bjykh55vr8qicc16n316700zhz
|
||||
|
@ -1,6 +1,6 @@
|
||||
cabal-version: >= 2.0
|
||||
name: free-category
|
||||
version: 0.0.4.1
|
||||
version: 0.0.4.2
|
||||
synopsis: efficient data types for free categories and arrows
|
||||
description:
|
||||
Provide various data types for free categories / type aligned queues, type
|
||||
@ -23,7 +23,7 @@ extra-source-files:
|
||||
bench/report-O1.md
|
||||
bench/report-O2.md
|
||||
stability: experimental
|
||||
tested-with: GHC==8.0.2, GHC==8.2.2, GHC==8.4.4, GHC==8.6.5, GHC==8.8.1
|
||||
tested-with: GHC==8.6.5, GHC==8.8.3, GHC==8.10.1
|
||||
|
||||
source-repository head
|
||||
type: git
|
||||
|
@ -127,20 +127,20 @@ fromC :: C f a b -> ListTr f a b
|
||||
fromC = hoistFreeH2
|
||||
{-# INLINE fromC #-}
|
||||
|
||||
liftC :: forall (f :: k -> k -> *) a b.
|
||||
liftC :: forall k (f :: k -> k -> *) a b.
|
||||
f a b
|
||||
-> C f a b
|
||||
liftC = \f -> C $ \k -> k f
|
||||
{-# INLINE [1] liftC #-}
|
||||
|
||||
consC :: forall (f :: k -> k -> *) a b c.
|
||||
consC :: forall k (f :: k -> k -> *) a b c.
|
||||
f b c
|
||||
-> C f a b
|
||||
-> C f a c
|
||||
consC bc ab = liftC bc `composeC` ab
|
||||
{-# INLINE [1] consC #-}
|
||||
|
||||
foldNatC :: forall (f :: k -> k -> *) c a b.
|
||||
foldNatC :: forall k (f :: k -> k -> *) c a b.
|
||||
Category c
|
||||
=> (forall x y. f x y -> c x y)
|
||||
-> C f a b
|
||||
|
@ -75,7 +75,8 @@ newtype Op (f :: k -> k -> *) (a :: k) (b :: k) = Op { runOp :: f b a }
|
||||
|
||||
-- | 'Op' is an endo-functor of the category of categories.
|
||||
--
|
||||
hoistOp :: forall (f :: k -> k -> *)
|
||||
hoistOp :: forall k
|
||||
(f :: k -> k -> *)
|
||||
(g :: k -> k -> *)
|
||||
a b.
|
||||
(forall x y. f x y -> g x y)
|
||||
@ -129,7 +130,7 @@ lengthListTr :: ListTr f a b -> Int
|
||||
lengthListTr NilTr = 0
|
||||
lengthListTr (ConsTr _ xs) = 1 + lengthListTr xs
|
||||
|
||||
composeL :: forall (f :: k -> k -> *) x y z.
|
||||
composeL :: forall k (f :: k -> k -> *) x y z.
|
||||
ListTr f y z
|
||||
-> ListTr f x y
|
||||
-> ListTr f x z
|
||||
@ -137,12 +138,12 @@ composeL (ConsTr x xs) ys = ConsTr x (xs . ys)
|
||||
composeL NilTr ys = ys
|
||||
{-# INLINE [1] composeL #-}
|
||||
|
||||
liftL :: forall (f :: k -> k -> *) x y.
|
||||
liftL :: forall k (f :: k -> k -> *) x y.
|
||||
f x y -> ListTr f x y
|
||||
liftL f = ConsTr f NilTr
|
||||
{-# INLINE [1] liftL #-}
|
||||
|
||||
foldNatL :: forall (f :: k -> k -> *) c a b.
|
||||
foldNatL :: forall k (f :: k -> k -> *) c a b.
|
||||
Category c
|
||||
=> (forall x y. f x y -> c x y)
|
||||
-> ListTr f a b
|
||||
@ -172,7 +173,7 @@ foldNatL fun (ConsTr bc ab) = fun bc . foldNatFree2 fun ab
|
||||
|
||||
-- | 'foldr' of a 'ListTr'
|
||||
--
|
||||
foldrL :: forall (f :: k -> k -> *) c a b d.
|
||||
foldrL :: forall k (f :: k -> k -> *) c a b d.
|
||||
(forall x y z. f y z -> c x y -> c x z)
|
||||
-> c a b
|
||||
-> ListTr f b d
|
||||
@ -185,7 +186,7 @@ foldrL nat ab (ConsTr xd bx) = nat xd (foldrL nat ab bx)
|
||||
--
|
||||
-- TODO: make it strict, like 'foldl''.
|
||||
--
|
||||
foldlL :: forall (f :: k -> k -> *) c a b d.
|
||||
foldlL :: forall k (f :: k -> k -> *) c a b d.
|
||||
(forall x y z. c y z -> f x y -> c x z)
|
||||
-> c b d
|
||||
-> ListTr f a b
|
||||
@ -294,7 +295,7 @@ pattern NilQ <- (unconsQ -> EmptyL) where
|
||||
{-# complete NilQ, ConsQ #-}
|
||||
#endif
|
||||
|
||||
composeQ :: forall (f :: k -> k -> *) x y z.
|
||||
composeQ :: forall k (f :: k -> k -> *) x y z.
|
||||
Queue f y z
|
||||
-> Queue f x y
|
||||
-> Queue f x z
|
||||
@ -306,7 +307,7 @@ nilQ :: Queue (f :: k -> k -> *) a a
|
||||
nilQ = Queue NilTr NilTr NilTr
|
||||
{-# INLINE [1] nilQ #-}
|
||||
|
||||
consQ :: forall (f :: k -> k -> *) a b c.
|
||||
consQ :: forall k (f :: k -> k -> *) a b c.
|
||||
f b c
|
||||
-> Queue f a b
|
||||
-> Queue f a c
|
||||
@ -326,7 +327,7 @@ unconsQ (Queue (ConsTr tr f) r s) = tr :< exec f r s
|
||||
unconsQ _ = error "Queue.uncons: invariant violation"
|
||||
{-# INLINE unconsQ #-}
|
||||
|
||||
snocQ :: forall (f :: k -> k -> *) a b c.
|
||||
snocQ :: forall k (f :: k -> k -> *) a b c.
|
||||
Queue f b c
|
||||
-> f a b
|
||||
-> Queue f a c
|
||||
@ -335,7 +336,7 @@ snocQ (Queue f r s) g = exec f (ConsTr (Op g) r) s
|
||||
|
||||
-- | 'foldr' of a 'Queue'
|
||||
--
|
||||
foldrQ :: forall (f :: k -> k -> *) c a b d.
|
||||
foldrQ :: forall k (f :: k -> k -> *) c a b d.
|
||||
(forall x y z. f y z -> c x y -> c x z)
|
||||
-> c a b
|
||||
-> Queue f b d
|
||||
@ -367,7 +368,7 @@ foldrQ nat ab (ConsQ xd bx) = nat xd (foldrQ nat ab bx)
|
||||
|
||||
#-}
|
||||
|
||||
liftQ :: forall (f :: k -> k -> *) a b.
|
||||
liftQ :: forall k (f :: k -> k -> *) a b.
|
||||
f a b -> Queue f a b
|
||||
liftQ = \fab -> ConsQ fab NilQ
|
||||
{-# INLINE [1] liftQ #-}
|
||||
@ -376,7 +377,7 @@ liftQ = \fab -> ConsQ fab NilQ
|
||||
--
|
||||
-- /complexity/ @O\(n\)@
|
||||
--
|
||||
foldNatQ :: forall (f :: k -> k -> *) c a b.
|
||||
foldNatQ :: forall k (f :: k -> k -> *) c a b.
|
||||
Category c
|
||||
=> (forall x y. f x y -> c x y)
|
||||
-> Queue f a b
|
||||
@ -407,7 +408,7 @@ foldNatQ nat = foldrQ (\f c -> nat f . c) id
|
||||
--
|
||||
-- TODO: make it strict, like 'foldl''.
|
||||
--
|
||||
foldlQ :: forall (f :: k -> k -> *) c a b d.
|
||||
foldlQ :: forall k (f :: k -> k -> *) c a b d.
|
||||
(forall x y z. c y z -> f x y -> c x z)
|
||||
-> c b d
|
||||
-> Queue f a b
|
||||
@ -433,7 +434,8 @@ zipWithQ fn queueA queueB = case (queueA, queueB) of
|
||||
-- categories), thus one can hoist the transitions using a natural
|
||||
-- transformation. This in analogy to @'map' :: (a -> b) -> [a] -> [b]@.
|
||||
--
|
||||
hoistQ :: forall (f :: k -> k -> *)
|
||||
hoistQ :: forall k
|
||||
(f :: k -> k -> *)
|
||||
(g :: k -> k -> *)
|
||||
a b.
|
||||
(forall x y. f x y -> g x y)
|
||||
|
Loading…
Reference in New Issue
Block a user