60 lines
2 KiB
Haskell
60 lines
2 KiB
Haskell
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
module Zenith.Utils where
|
|
|
|
import qualified Data.ByteString as BS
|
|
import qualified Data.ByteString.Char8 as C
|
|
import Data.Char
|
|
import Data.Functor (void)
|
|
import Data.Maybe
|
|
import qualified Data.Text as T
|
|
import qualified Data.Text.Encoding as E
|
|
import qualified Data.Text.IO as TIO
|
|
import System.Process (createProcess_, shell)
|
|
import Text.Read (readMaybe)
|
|
import Text.Regex.Posix
|
|
import ZcashHaskell.Orchard (isValidUnifiedAddress)
|
|
import ZcashHaskell.Sapling (isValidShieldedAddress)
|
|
import Zenith.Types
|
|
( AddressGroup(..)
|
|
, AddressSource(..)
|
|
, ZcashAddress(..)
|
|
, ZcashPool(..)
|
|
)
|
|
|
|
-- | Helper function to display small amounts of ZEC
|
|
displayZec :: Integer -> String
|
|
displayZec s
|
|
| s < 100 = show s ++ " zats "
|
|
| s < 100000 = show (fromIntegral s / 100) ++ " μZEC "
|
|
| s < 100000000 = show (fromIntegral s / 100000) ++ " mZEC "
|
|
| otherwise = show (fromIntegral s / 100000000) ++ " ZEC "
|
|
|
|
-- | Helper function to extract addresses from AddressGroups
|
|
getAddresses :: AddressGroup -> [ZcashAddress]
|
|
getAddresses ag = agtransparent ag <> agsapling ag <> agunified ag
|
|
|
|
-- | Helper function to validate potential Zcash addresses
|
|
validateAddress :: T.Text -> Maybe ZcashPool
|
|
validateAddress txt --(tReg || sReg && isJust chk) || (uReg && isJust chk)
|
|
| tReg = Just Transparent
|
|
| sReg && chkS = Just Sapling
|
|
| uReg && chk = Just Orchard
|
|
| otherwise = Nothing
|
|
where
|
|
transparentRegex = "^t1[a-zA-Z0-9]{33}$" :: String
|
|
shieldedRegex = "^zs[a-zA-Z0-9]{76}$" :: String
|
|
unifiedRegex = "^u[a-zA-Z0-9]" :: String
|
|
tReg = T.unpack txt =~ transparentRegex :: Bool
|
|
sReg = T.unpack txt =~ shieldedRegex :: Bool
|
|
uReg = T.unpack txt =~ unifiedRegex :: Bool
|
|
chk = isJust $ isValidUnifiedAddress $ E.encodeUtf8 txt
|
|
chkS = isValidShieldedAddress $ E.encodeUtf8 txt
|
|
|
|
-- | Copy an address to the clipboard
|
|
copyAddress :: ZcashAddress -> IO ()
|
|
copyAddress a =
|
|
void $
|
|
createProcess_ "toClipboard" $
|
|
shell $ "echo " ++ T.unpack (addy a) ++ " | xclip -r -selection clipboard"
|