aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorCypher <cypher@server.ky>2022-05-03 15:05:40 -0500
committerCypher <cypher@server.ky>2022-05-03 15:05:40 -0500
commit1a10c09d6150dbc9e8a1718b710252cb7b38b776 (patch)
tree34139f56373ad9e93d267543166c0c3da0f434d0
parent0732fbc8925efb9753b543d721ea845b9b4f338f (diff)
downloadssb-haskell-1a10c09d6150dbc9e8a1718b710252cb7b38b776.tar.xz
use stack lts-18.8
Update text handling to keep uptodate with changes with string conversion, using 'encodeUtf' and 'decodeUtf' where necessary. One update uses an odd encoding to and from JSON, which must be looked at later.
-rw-r--r--src/Ssb/Aux.hs7
-rw-r--r--src/Ssb/Feed.hs14
-rw-r--r--src/Ssb/Identity.hs9
-rw-r--r--src/Ssb/Peer.hs2
-rw-r--r--src/Ssb/Peer/RPC.hs2
-rw-r--r--src/Ssb/Peer/RPC/Room.hs3
-rw-r--r--src/Ssb/Peer/RPC/WhoAmI.hs2
-rw-r--r--src/Ssb/Pub.hs2
-rw-r--r--stack.yaml8
-rw-r--r--stack.yaml.lock8
10 files changed, 33 insertions, 24 deletions
diff --git a/src/Ssb/Aux.hs b/src/Ssb/Aux.hs
index 4be61b9..39a09b8 100644
--- a/src/Ssb/Aux.hs
+++ b/src/Ssb/Aux.hs
@@ -3,7 +3,8 @@ module Ssb.Aux where
import Protolude
import Data.Aeson as Aeson
-import Data.ByteString.Lazy as BS (toStrict)
+import Data.ByteString.Lazy as BS (toStrict)
+import Data.ByteString.Char8 as BS (pack, unpack)
import Data.Default
import Data.Serialize as Serialize
import Data.Either.Combinators ( mapLeft
@@ -59,9 +60,9 @@ command cmd input output = do
hSetBinaryMode hErr False
let loop = do
v <- atomically $ takeTMVar input
- hPutStr hIn (toS v :: [Char])
+ hPutStr hIn (BS.unpack v :: [Char])
hFlush hIn
v' <- hGetLine hOut
- atomically $ putTMVar output (toS v')
+ atomically $ putTMVar output (BS.pack v')
loop
loop
diff --git a/src/Ssb/Feed.hs b/src/Ssb/Feed.hs
index f4e96c2..ebdd2f4 100644
--- a/src/Ssb/Feed.hs
+++ b/src/Ssb/Feed.hs
@@ -72,7 +72,7 @@ extractMessageID (MessageID buf) = buf
-- Format of '%[base64 messageId].sha256', the '.sha256' is appended for
-- forward compatibility, and is currently assumed.
formatMessageID :: MessageID -> Text
-formatMessageID (MessageID buf) = "%" <> toS (Base64.encode buf) <> ".sha256"
+formatMessageID (MessageID buf) = "%" <> decodeUtf8 (Base64.encode buf) <> ".sha256"
-- | TODO: make safe
parseMessageID :: Text -> Either Text MessageID
@@ -80,7 +80,7 @@ parseMessageID arg = decode $ T.dropEnd constLen $ T.drop 1 arg
where
constLen = T.length ".sha256"
decode :: Text -> Either Text MessageID
- decode = mapRight MessageID . mapLeft toS . Base64.decode . toS
+ decode = mapRight MessageID . mapLeft toS . Base64.decode . encodeUtf8
instance FromJSON MessageID where
parseJSON = Aeson.withText "MessageID" $ \v -> case parseMessageID v of
@@ -115,14 +115,14 @@ extractSignature :: Signature -> ByteString
extractSignature (Signature buf) = buf
formatSignature :: Signature -> Text
-formatSignature (Signature buf) = toS (Base64.encode buf) <> ".sig.ed25519"
+formatSignature (Signature buf) = decodeUtf8 (Base64.encode buf) <> ".sig.ed25519"
parseSignature :: Text -> Either Text Signature
parseSignature txt = decode $ T.dropEnd constLen txt
where
constLen = T.length ".sig.ed25519"
decode :: Text -> Either Text Signature
- decode = mapRight Signature . mapLeft toS . Base64.decode . toS
+ decode = mapRight Signature . mapLeft toS . Base64.decode . encodeUtf8
instance FromJSON Signature where
parseJSON = Aeson.withText "Signature" $ \v -> case parseSignature v of
@@ -206,7 +206,7 @@ withSignature signature buf = (dropEnd (BS.length endTxt) buf) <> sigTxt
sigTxt =
",\n \"signature\": "
<> "\""
- <> toS (formatSignature signature)
+ <> encodeUtf8 (formatSignature signature)
<> "\""
<> endTxt
endTxt = "\n}"
@@ -332,9 +332,9 @@ encodeForSigning contentOrder arg = do
then
return (error "external V8 byte string encoder not initialized")
else do
- atomically $ putTMVar v8Input (cmd <> toS arg)
+ atomically $ putTMVar v8Input (cmd <> arg)
ret <- atomically $ takeTMVar v8Output
- let ret' = Base64.decode (toS ret)
+ let ret' = Base64.decode ret
return $ mapLeft toS ret'
where
cmd = if contentOrder
diff --git a/src/Ssb/Identity.hs b/src/Ssb/Identity.hs
index e3fa4dc..f599669 100644
--- a/src/Ssb/Identity.hs
+++ b/src/Ssb/Identity.hs
@@ -9,6 +9,7 @@ import qualified Crypto.Saltine.Class as Nacl
import Data.Serialize ( Serialize )
import Data.Either.Combinators ( mapLeft )
+import qualified Data.ByteString as S
import qualified Data.Text as T
newtype PrivateKey = PrivateKey ByteString
@@ -21,13 +22,13 @@ instance Serialize PrivateKey
formatPrivateKey :: PrivateKey -> Text
formatPrivateKey (PrivateKey buf) = "@" <> pubKey <> ".ed25519"
- where pubKey = toS $ Base64.encode buf
+ where pubKey = decodeUtf8 $ Base64.encode buf
parsePrivateKey :: Text -> Either Text PrivateKey
parsePrivateKey arg = decode $ T.dropEnd constLen $ T.drop 1 arg
where
constLen = T.length ".ed25519"
- decode = fmap PrivateKey . mapLeft toS . Base64.decode . toS
+ decode = fmap PrivateKey . mapLeft toS . Base64.decode . encodeUtf8
instance FromJSON PrivateKey where
parseJSON = withText "PrivateKey" $ \v -> case parsePrivateKey v of
@@ -47,13 +48,13 @@ instance Serialize PublicKey
formatPublicKey :: PublicKey -> Text
formatPublicKey (PublicKey buf) = "@" <> pubKey <> ".ed25519"
- where pubKey = toS $ Base64.encode buf
+ where pubKey = decodeUtf8 $ Base64.encode buf
parsePublicKey :: Text -> Either Text PublicKey
parsePublicKey arg = decode $ T.dropEnd constLen $ T.drop 1 arg
where
constLen = T.length ".ed25519"
- decode = fmap PublicKey . mapLeft toS . Base64.decode . toS
+ decode = fmap PublicKey . mapLeft toS . Base64.decode . encodeUtf8
instance FromJSON PublicKey where
parseJSON = withText "PublicKey" $ \v -> case parsePublicKey v of
diff --git a/src/Ssb/Peer.hs b/src/Ssb/Peer.hs
index 75078ff..41a49cb 100644
--- a/src/Ssb/Peer.hs
+++ b/src/Ssb/Peer.hs
@@ -45,7 +45,7 @@ parseMultiAddress txt = do
{ protocol = protocol
, host = address
, port = port
- , key = PublicKey $ Base64.decodeLenient $ toS key
+ , key = PublicKey $ Base64.decodeLenient $ encodeUtf8 key
}
where
split c arg = (identity *** Text.drop 1) $ Text.breakOn c arg
diff --git a/src/Ssb/Peer/RPC.hs b/src/Ssb/Peer/RPC.hs
index 3286a33..1336b5e 100644
--- a/src/Ssb/Peer/RPC.hs
+++ b/src/Ssb/Peer/RPC.hs
@@ -3,7 +3,7 @@
module Ssb.Peer.RPC where
-import Protolude
+import Protolude hiding (Handler)
import Control.Concurrent.STM
import Control.Monad.Fail
diff --git a/src/Ssb/Peer/RPC/Room.hs b/src/Ssb/Peer/RPC/Room.hs
index 1f53cf0..7be7d2c 100644
--- a/src/Ssb/Peer/RPC/Room.hs
+++ b/src/Ssb/Peer/RPC/Room.hs
@@ -280,7 +280,8 @@ instance RPC.Handler Room where
-- should decode request
serve h (RPC.Endpoint ["tunnel", "connect"] RPC.Duplex) args stream = do
let args' =
- decodeJSON (toS $ Aeson.encode args) :: Either
+ -- TODO: why encode to JSON then decode from JSON redundantly?
+ decodeJSON (encodeJSON args) :: Either
Text
[ConnectRequest]
case args' of
diff --git a/src/Ssb/Peer/RPC/WhoAmI.hs b/src/Ssb/Peer/RPC/WhoAmI.hs
index be979fc..c92c56c 100644
--- a/src/Ssb/Peer/RPC/WhoAmI.hs
+++ b/src/Ssb/Peer/RPC/WhoAmI.hs
@@ -7,7 +7,7 @@
module Ssb.Peer.RPC.WhoAmI where
-import Protolude hiding ( Identity )
+import Protolude hiding ( Handler, Identity )
import Data.Aeson as Aeson (FromJSON,ToJSON)
import qualified Ssb.Identity as Ssb
diff --git a/src/Ssb/Pub.hs b/src/Ssb/Pub.hs
index 9ed5410..16e9e2e 100644
--- a/src/Ssb/Pub.hs
+++ b/src/Ssb/Pub.hs
@@ -33,7 +33,7 @@ parsePub txt = do
return PubAddress
{ host = address
, port = port
- , key = PublicKey $ Base64.decodeLenient $ toS key
+ , key = PublicKey $ Base64.decodeLenient $ encodeUtf8 key
}
where
split c arg = (identity *** Text.drop 1) $ Text.breakOn c arg
diff --git a/stack.yaml b/stack.yaml
index 7e7ab39..7da6e61 100644
--- a/stack.yaml
+++ b/stack.yaml
@@ -17,7 +17,7 @@
#
# resolver: ./custom-snapshot.yaml
# resolver: https://example.com/snapshots/2018-01-01.yaml
-resolver: lts-14.27
+resolver: lts-18.8
# User packages to be built.
# Various formats can be used as shown in the example below.
@@ -34,10 +34,16 @@ resolver: lts-14.27
# - wai
packages:
- .
+
# Dependency packages to be pulled from upstream that are not in the resolver
# using the same syntax as the packages field.
# (e.g., acme-missiles-0.3)
extra-deps: []
+# - protolude-0.3.0@sha256:8361b811b420585b122a7ba715aa5923834db6e8c36309bf267df2dbf66b95ef,2693
+
+# Protolude requires some newer than otherwise allowe dependencies.
+#allow-newer: true
+
# Override default flag values for local packages and extra-deps
# flags: {}
diff --git a/stack.yaml.lock b/stack.yaml.lock
index e24dcac..4728c3a 100644
--- a/stack.yaml.lock
+++ b/stack.yaml.lock
@@ -6,7 +6,7 @@
packages: []
snapshots:
- completed:
- size: 524996
- url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/14/27.yaml
- sha256: 7ea31a280c56bf36ff591a7397cc384d0dff622e7f9e4225b47d8980f019a0f0
- original: lts-14.27
+ size: 587126
+ url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/18/8.yaml
+ sha256: 93a107557e8691ed5ca17beaee41e68222b142c48868fc8c04a4181fb233477d
+ original: lts-18.8