mirror of
https://github.com/tfausak/witch.git
synced 2024-11-22 14:58:13 +03:00
Add ISO-8859-1 encoding
This commit is contained in:
parent
186e722687
commit
2e097296d6
@ -4,5 +4,8 @@ module Witch.Encoding where
|
||||
|
||||
import qualified Data.Tagged as Tagged
|
||||
|
||||
-- | <https://en.wikipedia.org/wiki/ISO/IEC_8859-1>
|
||||
type ISO_8859_1 = Tagged.Tagged "ISO-8859-1"
|
||||
|
||||
-- | <https://en.wikipedia.org/wiki/UTF-8>
|
||||
type UTF_8 = Tagged.Tagged "UTF-8"
|
||||
|
@ -1226,6 +1226,56 @@ instance From.From (Tagged.Tagged t a) a
|
||||
-- | Uses @coerce@. Essentially the same as 'Tagged.retag'.
|
||||
instance From.From (Tagged.Tagged t a) (Tagged.Tagged u a)
|
||||
|
||||
-- ISO-8859-1
|
||||
|
||||
-- | Uses 'Text.decodeLatin1'.
|
||||
instance From.From (Encoding.ISO_8859_1 ByteString.ByteString) Text.Text where
|
||||
from = Text.decodeLatin1 . From.from
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance From.From (Encoding.ISO_8859_1 ByteString.ByteString) LazyText.Text where
|
||||
from = Utility.via @Text.Text
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance From.From (Encoding.ISO_8859_1 ByteString.ByteString) String where
|
||||
from = Utility.via @Text.Text
|
||||
|
||||
-- | Uses 'LazyText.decodeLatin1'.
|
||||
instance From.From (Encoding.ISO_8859_1 LazyByteString.ByteString) LazyText.Text where
|
||||
from = LazyText.decodeLatin1 . From.from
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance From.From (Encoding.ISO_8859_1 LazyByteString.ByteString) Text.Text where
|
||||
from = Utility.via @LazyText.Text
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance From.From (Encoding.ISO_8859_1 LazyByteString.ByteString) String where
|
||||
from = Utility.via @LazyText.Text
|
||||
|
||||
-- | Uses 'Text.encodeUtf8'.
|
||||
instance From.From Text.Text (Encoding.ISO_8859_1 ByteString.ByteString) where
|
||||
from = From.from . Text.encodeUtf8
|
||||
|
||||
-- | Converts via 'ByteString.ByteString'.
|
||||
instance From.From Text.Text (Encoding.ISO_8859_1 LazyByteString.ByteString) where
|
||||
from = fmap From.from . Utility.into @(Encoding.ISO_8859_1 ByteString.ByteString)
|
||||
|
||||
-- | Uses 'LazyText.encodeUtf8'.
|
||||
instance From.From LazyText.Text (Encoding.ISO_8859_1 LazyByteString.ByteString) where
|
||||
from = From.from . LazyText.encodeUtf8
|
||||
|
||||
-- | Converts via 'LazyByteString.ByteString'.
|
||||
instance From.From LazyText.Text (Encoding.ISO_8859_1 ByteString.ByteString) where
|
||||
from = fmap From.from . Utility.into @(Encoding.ISO_8859_1 LazyByteString.ByteString)
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance From.From String (Encoding.ISO_8859_1 ByteString.ByteString) where
|
||||
from = Utility.via @Text.Text
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance From.From String (Encoding.ISO_8859_1 LazyByteString.ByteString) where
|
||||
from = Utility.via @LazyText.Text
|
||||
|
||||
-- UTF-8
|
||||
|
||||
-- | Uses 'Text.decodeUtf8''.
|
||||
|
@ -2010,6 +2010,66 @@ spec = describe "Witch" $ do
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged False) `shouldBe` Tagged.Tagged False
|
||||
|
||||
describe "From (ISO_8859_1 ByteString) Text" $ do
|
||||
let f = Witch.from @(Encoding.ISO_8859_1 ByteString.ByteString) @Text.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x61])) `shouldBe` Text.pack "a"
|
||||
|
||||
describe "From (ISO_8859_1 ByteString) LazyText" $ do
|
||||
let f = Witch.from @(Encoding.ISO_8859_1 ByteString.ByteString) @LazyText.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x61])) `shouldBe` LazyText.pack "a"
|
||||
|
||||
describe "From (ISO_8859_1 ByteString) String" $ do
|
||||
let f = Witch.from @(Encoding.ISO_8859_1 ByteString.ByteString) @String
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x61])) `shouldBe` "a"
|
||||
|
||||
describe "From (ISO_8859_1 LazyByteString) LazyText" $ do
|
||||
let f = Witch.from @(Encoding.ISO_8859_1 LazyByteString.ByteString) @LazyText.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61])) `shouldBe` LazyText.pack "a"
|
||||
|
||||
describe "From (ISO_8859_1 LazyByteString) Text" $ do
|
||||
let f = Witch.from @(Encoding.ISO_8859_1 LazyByteString.ByteString) @Text.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61])) `shouldBe` Text.pack "a"
|
||||
|
||||
describe "From (ISO_8859_1 LazyByteString) String" $ do
|
||||
let f = Witch.from @(Encoding.ISO_8859_1 LazyByteString.ByteString) @String
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61])) `shouldBe` "a"
|
||||
|
||||
describe "From Text (ISO_8859_1 ByteString)" $ do
|
||||
let f = Witch.from @Text.Text @(Encoding.ISO_8859_1 ByteString.ByteString)
|
||||
it "works" $ do
|
||||
f (Text.pack "a") `shouldBe` Tagged.Tagged (ByteString.pack [0x61])
|
||||
|
||||
describe "From Text (ISO_8859_1 LazyByteString)" $ do
|
||||
let f = Witch.from @Text.Text @(Encoding.ISO_8859_1 LazyByteString.ByteString)
|
||||
it "works" $ do
|
||||
f (Text.pack "a") `shouldBe` Tagged.Tagged (LazyByteString.pack [0x61])
|
||||
|
||||
describe "From LazyText (ISO_8859_1 LazyByteString)" $ do
|
||||
let f = Witch.from @LazyText.Text @(Encoding.ISO_8859_1 LazyByteString.ByteString)
|
||||
it "works" $ do
|
||||
f (LazyText.pack "a") `shouldBe` Tagged.Tagged (LazyByteString.pack [0x61])
|
||||
|
||||
describe "From LazyText (ISO_8859_1 ByteString)" $ do
|
||||
let f = Witch.from @LazyText.Text @(Encoding.ISO_8859_1 ByteString.ByteString)
|
||||
it "works" $ do
|
||||
f (LazyText.pack "a") `shouldBe` Tagged.Tagged (ByteString.pack [0x61])
|
||||
|
||||
describe "From String (ISO_8859_1 ByteString)" $ do
|
||||
let f = Witch.from @String @(Encoding.ISO_8859_1 ByteString.ByteString)
|
||||
it "works" $ do
|
||||
f "a" `shouldBe` Tagged.Tagged (ByteString.pack [0x61])
|
||||
|
||||
describe "From String (ISO_8859_1 LazyByteString)" $ do
|
||||
let f = Witch.from @String @(Encoding.ISO_8859_1 LazyByteString.ByteString)
|
||||
it "works" $ do
|
||||
f "a" `shouldBe` Tagged.Tagged (LazyByteString.pack [0x61])
|
||||
|
||||
describe "TryFrom (UTF_8 ByteString) Text" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_8 ByteString.ByteString) @Text.Text
|
||||
it "works" $ do
|
||||
|
Loading…
Reference in New Issue
Block a user