[commit: packages/containers] changelog-foldtree, cleaned_bugfix394, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-184-generic, revert-408-bugfix_394: Remove unnecessary (Sized *) constraints. (5f519e6)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:37:43 UTC 2017


Repository : ssh://git@git.haskell.org/containers

On branches: changelog-foldtree,cleaned_bugfix394,master,merge-doc-target,merge-fixes-5.9,merge-restrict-fix-5.8,revert-184-generic,revert-408-bugfix_394
Link       : http://git.haskell.org/packages/containers.git/commitdiff/5f519e641aa7099c0dc6b12d3df08920e8496d04

>---------------------------------------------------------------

commit 5f519e641aa7099c0dc6b12d3df08920e8496d04
Author: Milan Straka <fox at ucw.cz>
Date:   Sat Jan 10 14:29:34 2015 +0100

    Remove unnecessary (Sized *) constraints.


>---------------------------------------------------------------

5f519e641aa7099c0dc6b12d3df08920e8496d04
 Data/Sequence.hs | 8 ++++----
 1 file changed, 4 insertions(+), 4 deletions(-)

diff --git a/Data/Sequence.hs b/Data/Sequence.hs
index b62b16a..491dd6d 100644
--- a/Data/Sequence.hs
+++ b/Data/Sequence.hs
@@ -640,13 +640,13 @@ deep            :: Sized a => Digit a -> FingerTree (Node a) -> Digit a -> Finge
 deep pr m sf    =  Deep (size pr + size m + size sf) pr m sf
 
 {-# INLINE pullL #-}
-pullL :: Sized a => Int -> FingerTree (Node a) -> Digit a -> FingerTree a
+pullL :: Int -> FingerTree (Node a) -> Digit a -> FingerTree a
 pullL s m sf = case viewLTree m of
     Nothing2        -> digitToTree' s sf
     Just2 pr m'     -> Deep s (nodeToDigit pr) m' sf
 
 {-# INLINE pullR #-}
-pullR :: Sized a => Int -> Digit a -> FingerTree (Node a) -> FingerTree a
+pullR :: Int -> Digit a -> FingerTree (Node a) -> FingerTree a
 pullR s pr m = case viewRTree m of
     Nothing2        -> digitToTree' s pr
     Just2 m' sf     -> Deep s pr m' (nodeToDigit sf)
@@ -1840,7 +1840,7 @@ initsNode (Node3 s a b c) = Node3 s (One a) (Two a b) (Three a b c)
 {-# SPECIALIZE tailsTree :: (FingerTree (Node a) -> Node b) -> FingerTree (Node a) -> FingerTree (Node b) #-}
 -- | Given a function to apply to tails of a tree, applies that function
 -- to every tail of the specified tree.
-tailsTree :: (Sized a, Sized b) => (FingerTree a -> b) -> FingerTree a -> FingerTree b
+tailsTree :: Sized a => (FingerTree a -> b) -> FingerTree a -> FingerTree b
 tailsTree _ Empty = Empty
 tailsTree f (Single x) = Single (f (Single x))
 tailsTree f (Deep n pr m sf) =
@@ -1855,7 +1855,7 @@ tailsTree f (Deep n pr m sf) =
 {-# SPECIALIZE initsTree :: (FingerTree (Node a) -> Node b) -> FingerTree (Node a) -> FingerTree (Node b) #-}
 -- | Given a function to apply to inits of a tree, applies that function
 -- to every init of the specified tree.
-initsTree :: (Sized a, Sized b) => (FingerTree a -> b) -> FingerTree a -> FingerTree b
+initsTree :: Sized a => (FingerTree a -> b) -> FingerTree a -> FingerTree b
 initsTree _ Empty = Empty
 initsTree f (Single x) = Single (f (Single x))
 initsTree f (Deep n pr m sf) =



More information about the ghc-commits mailing list