-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathUnsafe.hs
84 lines (69 loc) · 2.88 KB
/
Unsafe.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
-- | Examples about how to work with encoded data.
-- This topic is (an interesting) work-in-progress.
--
-- Modifying encoded data would typically corrupt the encoding.
-- Current approach is to use 'Data.TypedEncoding.Unsafe.Unsafe' wrapping class that exposes
-- Functor and (limited) Applicative and Monad instances.
module Examples.TypedEncoding.Unsafe where
import qualified Data.Text as T
import Data.Semigroup ((<>))
import Data.TypedEncoding
import qualified Data.TypedEncoding.Unsafe as Unsafe
import qualified Data.TypedEncoding.Instances.Restriction.ASCII()
-- $setup
-- >>> :set -XOverloadedStrings -XMultiParamTypeClasses -XDataKinds
-- | Starting example
exAsciiTE :: Either EncodeEx (Enc '["r-ASCII"] () T.Text)
exAsciiTE = encodeFAll . toEncoding () $ "HELLO"
-- | with either removed
exAsciiT :: Enc '["r-ASCII"] () T.Text
Right exAsciiT = exAsciiTE
-- * Safe and Slow approach
-- |
-- 'recreateFAll' is the way to recover encoding in a safe way
--
-- >>> let payload = getPayload exAsciiT
-- >>> let newPayload = payload <> " some extra stuff"
-- >>> recreateFAll . toEncoding () $ newPayload :: Either RecreateEx (Enc '["r-ASCII"] () T.Text)
-- Right (UnsafeMkEnc Proxy () "HELLO some extra stuff")
--
-- Alternatively, 'UncheckedEnc' type can be used in recreation, see 'Examples.TypedEncoding.Overview'
--
modifiedAsciiT :: Either RecreateEx (Enc '["r-ASCII"] () T.Text)
modifiedAsciiT = recreateFAll . toEncoding () . ( <> " some extra stuff") . getPayload $ exAsciiT
-- * Unsafe but fast
-- |
-- The issue with 'recreateFAll' is that it may be expensive.
--
-- This apprach uses 'Data.TypedEncoding.Unsafe.Unsafe' to perform (in general risky) operation on
-- the internal payload.
--
-- >>> exAsciiTE
-- Right (UnsafeMkEnc Proxy () "HELLO")
-- >>> exAsciiTE >>= pure . Unsafe.withUnsafe (fmap T.toLower)
-- Right (UnsafeMkEnc Proxy () "hello")
--
-- Example uses of 'T.toLower' within encoded data
-- this operation is safe for ASCII restriction
-- but @Enc '["r-ASCII"] () T.Text@ does not expose it
-- We use Functor instance of Unsafe wrapper type to accomplish this
toLowerAscii :: Either EncodeEx (Enc '["r-ASCII"] () T.Text)
toLowerAscii = Unsafe.withUnsafe (fmap T.toLower) <$> exAsciiTE
-- |
-- Similar example uses applicative instance of 'Unsafe.Unsafe'
--
-- >>> let Right hELLO = exAsciiTE
-- >>> let Right hello = toLowerAscii
-- >>> displ $ Unsafe.runUnsafe ((<>) <$> Unsafe.Unsafe hELLO <*> Unsafe.Unsafe hello)
-- "Enc '[r-ASCII] () (Text HELLOhello)"
appendAscii :: Either EncodeEx (Enc '["r-ASCII"] () T.Text)
appendAscii = do
hELLO <- exAsciiTE
hello <- toLowerAscii
pure $ Unsafe.runUnsafe ((<>) <$> Unsafe.Unsafe hELLO <*> Unsafe.Unsafe hello)