[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: Add IsString instance (7615e42)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:38:19 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/7615e4238cd7968d4abc27539974afe9b0b5024b

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

commit 7615e4238cd7968d4abc27539974afe9b0b5024b
Author: David Feuer <David.Feuer at gmail.com>
Date:   Sun Mar 15 21:27:31 2015 -0400

    Add IsString instance
    
    Add `instance IsString (Seq Char)` when compiling with GHC.


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

7615e4238cd7968d4abc27539974afe9b0b5024b
 Data/Sequence.hs | 10 +++++++++-
 1 file changed, 9 insertions(+), 1 deletion(-)

diff --git a/Data/Sequence.hs b/Data/Sequence.hs
index db333c3..c06931b 100644
--- a/Data/Sequence.hs
+++ b/Data/Sequence.hs
@@ -1,6 +1,8 @@
 {-# LANGUAGE CPP #-}
 #if __GLASGOW_HASKELL__
-{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE StandaloneDeriving #-}
+{-# LANGUAGE FlexibleInstances #-}
 #endif
 #if __GLASGOW_HASKELL__ >= 703
 {-# LANGUAGE Trustworthy #-}
@@ -182,6 +184,7 @@ import GHC.Exts (build)
 import Text.Read (Lexeme(Ident), lexP, parens, prec,
     readPrec, readListPrec, readListPrecDefault)
 import Data.Data
+import Data.String (IsString(..))
 #endif
 
 -- Array stuff, with GHC.Arr on GHC
@@ -2137,6 +2140,11 @@ instance GHC.Exts.IsList (Seq a) where
     toList = toList
 #endif
 
+#ifdef __GLASGOW_HASKELL__
+instance IsString (Seq Char) where
+    fromString = fromList
+#endif
+
 ------------------------------------------------------------------------
 -- Reverse
 ------------------------------------------------------------------------



More information about the ghc-commits mailing list