Skip to content
Snippets Groups Projects
Commit d947bae1 authored by quasicomputational's avatar quasicomputational Committed by Herbert Valerio Riedel
Browse files

Add Lift instances for Text.

These have similar trade-offs to the existing `Data` instances:
preserving abstraction at the cost of efficiency.

Due to haskell/cabal#5623, the tests exercising this feature have to
live in their own package.
parent 7c869152
No related branches found
No related tags found
No related merge requests found
...@@ -6,6 +6,17 @@ ...@@ -6,6 +6,17 @@
#if __GLASGOW_HASKELL__ >= 708 #if __GLASGOW_HASKELL__ >= 708
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
#endif #endif
-- Using TemplateHaskell in text unconditionally is unacceptable, as
-- it's a GHC boot library. TemplateHaskellQuotes was added in 8.0, so
-- this would seem to be a problem. However, GHC's policy of only
-- needing to be able to compile itself from the last few releases
-- allows us to use full-fat TH on older versions, while using THQ for
-- GHC versions that may be used for bootstrapping.
#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE TemplateHaskellQuotes #-}
#else
{-# LANGUAGE TemplateHaskell #-}
#endif
-- | -- |
-- Module : Data.Text -- Module : Data.Text
...@@ -244,6 +255,8 @@ import GHC.Base (eqInt, neInt, gtInt, geInt, ltInt, leInt) ...@@ -244,6 +255,8 @@ import GHC.Base (eqInt, neInt, gtInt, geInt, ltInt, leInt)
#if __GLASGOW_HASKELL__ >= 708 #if __GLASGOW_HASKELL__ >= 708
import qualified GHC.Exts as Exts import qualified GHC.Exts as Exts
#endif #endif
import qualified Language.Haskell.TH.Lib as TH
import Language.Haskell.TH.Syntax (Lift, lift)
#if MIN_VERSION_base(4,7,0) #if MIN_VERSION_base(4,7,0)
import Text.Printf (PrintfArg, formatArg, formatString) import Text.Printf (PrintfArg, formatArg, formatString)
#endif #endif
...@@ -413,6 +426,13 @@ instance Data Text where ...@@ -413,6 +426,13 @@ instance Data Text where
_ -> P.error "gunfold" _ -> P.error "gunfold"
dataTypeOf _ = textDataType dataTypeOf _ = textDataType
-- | This instance has similar considerations to the 'Data' instance:
-- it preserves abstraction at the cost of inefficiency.
--
-- @since 1.2.4.0
instance Lift Text where
lift = TH.appE (TH.varE 'pack) . TH.stringE . unpack
#if MIN_VERSION_base(4,7,0) #if MIN_VERSION_base(4,7,0)
-- | Only defined for @base-4.7.0.0@ and later -- | Only defined for @base-4.7.0.0@ and later
-- --
......
...@@ -6,6 +6,17 @@ ...@@ -6,6 +6,17 @@
#if __GLASGOW_HASKELL__ >= 708 #if __GLASGOW_HASKELL__ >= 708
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
#endif #endif
-- Using TemplateHaskell in text unconditionally is unacceptable, as
-- it's a GHC boot library. TemplateHaskellQuotes was added in 8.0, so
-- this would seem to be a problem. However, GHC's policy of only
-- needing to be able to compile itself from the last few releases
-- allows us to use full-fat TH on older versions, while using THQ for
-- GHC versions that may be used for bootstrapping.
#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE TemplateHaskellQuotes #-}
#else
{-# LANGUAGE TemplateHaskell #-}
#endif
-- | -- |
-- Module : Data.Text.Lazy -- Module : Data.Text.Lazy
...@@ -239,6 +250,8 @@ import qualified GHC.Base as GHC ...@@ -239,6 +250,8 @@ import qualified GHC.Base as GHC
import qualified GHC.Exts as Exts import qualified GHC.Exts as Exts
#endif #endif
import GHC.Prim (Addr#) import GHC.Prim (Addr#)
import qualified Language.Haskell.TH.Lib as TH
import Language.Haskell.TH.Syntax (Lift, lift)
#if MIN_VERSION_base(4,7,0) #if MIN_VERSION_base(4,7,0)
import Text.Printf (PrintfArg, formatArg, formatString) import Text.Printf (PrintfArg, formatArg, formatString)
#endif #endif
...@@ -399,6 +412,13 @@ instance Data Text where ...@@ -399,6 +412,13 @@ instance Data Text where
_ -> error "Data.Text.Lazy.Text.gunfold" _ -> error "Data.Text.Lazy.Text.gunfold"
dataTypeOf _ = textDataType dataTypeOf _ = textDataType
-- | This instance has similar considerations to the 'Data' instance:
-- it preserves abstraction at the cost of inefficiency.
--
-- @since 1.2.4.0
instance Lift Text where
lift = TH.appE (TH.varE 'pack) . TH.stringE . unpack
#if MIN_VERSION_base(4,7,0) #if MIN_VERSION_base(4,7,0)
-- | Only defined for @base-4.7.0.0@ and later -- | Only defined for @base-4.7.0.0@ and later
-- --
......
...@@ -42,6 +42,7 @@ executable text-benchmarks ...@@ -42,6 +42,7 @@ executable text-benchmarks
ghc-prim, ghc-prim,
integer-gmp, integer-gmp,
stringsearch, stringsearch,
template-haskell,
transformers, transformers,
utf8-string, utf8-string,
vector vector
......
-- See http://cabal.readthedocs.io/en/latest/nix-local-build-overview.html -- See http://cabal.readthedocs.io/en/latest/nix-local-build-overview.html
packages: ., benchmarks packages: ., benchmarks, th-tests
tests: True tests: True
### next
* `Lift` instances `Data.Text.Text` and `Data.Text.Lazy.Text`.
### 1.2.3.1 ### 1.2.3.1
* Make `decodeUtf8With` fail explicitly for unsupported non-BMP * Make `decodeUtf8With` fail explicitly for unsupported non-BMP
......
...@@ -146,7 +146,8 @@ library ...@@ -146,7 +146,8 @@ library
binary, binary,
deepseq, deepseq,
ghc-prim, ghc-prim,
integer-gmp integer-gmp,
template-haskell
if flag(bytestring-builder) if flag(bytestring-builder)
build-depends: bytestring >= 0.9 && < 0.10.4, build-depends: bytestring >= 0.9 && < 0.10.4,
......
cabal-version: >= 1.8 cabal-version: >= 1.8
name: text name: text
version: 1.2.3.1 version: 1.2.4.0
homepage: https://github.com/haskell/text homepage: https://github.com/haskell/text
bug-reports: https://github.com/haskell/text/issues bug-reports: https://github.com/haskell/text/issues
...@@ -147,7 +147,8 @@ library ...@@ -147,7 +147,8 @@ library
base >= 4.2 && < 5, base >= 4.2 && < 5,
binary, binary,
deepseq >= 1.1.0.0, deepseq >= 1.1.0.0,
ghc-prim >= 0.2 ghc-prim >= 0.2,
template-haskell
if flag(bytestring-builder) if flag(bytestring-builder)
build-depends: bytestring >= 0.9 && < 0.10.4, build-depends: bytestring >= 0.9 && < 0.10.4,
...@@ -255,6 +256,7 @@ test-suite tests ...@@ -255,6 +256,7 @@ test-suite tests
ghc-prim, ghc-prim,
quickcheck-unicode >= 1.0.1.0, quickcheck-unicode >= 1.0.1.0,
random, random,
template-haskell,
test-framework >= 0.4, test-framework >= 0.4,
test-framework-hunit >= 0.2, test-framework-hunit >= 0.2,
test-framework-quickcheck2 >= 0.2 test-framework-quickcheck2 >= 0.2
......
Copyright (c) 2008-2009, Tom Harper
All rights reserved.
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions
are met:
* Redistributions of source code must retain the above copyright
notice, this list of conditions and the following disclaimer.
* Redistributions in binary form must reproduce the above
copyright notice, this list of conditions and the following
disclaimer in the documentation and/or other materials provided
with the distribution.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Lift
( tests
)
where
import qualified Data.Text as S
import qualified Data.Text.Lazy as L
import Language.Haskell.TH.Syntax (lift)
import Test.HUnit (assertBool, assertEqual, assertFailure)
import qualified Test.Framework as F
import qualified Test.Framework.Providers.HUnit as F
tests :: F.Test
tests = F.testGroup "TH lifting Text"
[ F.testCase "strict" $ assertEqual "strict"
$(lift ("foo" :: S.Text))
("foo" :: S.Text)
, F.testCase "lazy" $ assertEqual "lazy"
$(lift ("foo" :: L.Text))
("foo" :: L.Text)
]
-- | Provides a simple main function which runs all the tests
--
module Main
( main
) where
import Test.Framework (defaultMain)
import qualified Lift
main :: IO ()
main = defaultMain [Lift.tests]
cabal-version: 2.2
name: th-tests
version: 0
description:
Tests that use 'Text' functions during compile time.
.
These are in a separate package because of https://github.com/haskell/cabal/issues/5623
license: BSD-2-Clause
license-file: LICENSE
test-suite th-tests
default-language: Haskell2010
type: exitcode-stdio-1.0
hs-source-dirs:
tests/
main-is: th-tests.hs
other-modules:
Lift
build-depends:
HUnit >= 1.2,
base,
template-haskell,
text,
test-framework >= 0.4,
test-framework-hunit >= 0.2
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment