Skip to content

Commit

Permalink
add TimeFormatter, prepare Futr data structure
Browse files Browse the repository at this point in the history
  • Loading branch information
prolic committed Sep 16, 2024
1 parent a8ae984 commit 9e9cb4e
Show file tree
Hide file tree
Showing 7 changed files with 72 additions and 27 deletions.
2 changes: 1 addition & 1 deletion futr.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -40,11 +40,11 @@ executable futr
Nostr.Encryption.Internal
Nostr.Event
Nostr.Keys
Nostr.Kind
Nostr.Profile
Nostr.Relay
Nostr.Types
Presentation.KeyMgmt
TimeFormatter

default-language: Haskell2010
extra-libraries: secp256k1
Expand Down
19 changes: 17 additions & 2 deletions src/Futr.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,10 @@

module Futr where

import Data.Int (Int64)

Check warning on line 9 in src/Futr.hs

View workflow job for this annotation

GitHub Actions / 9.4.8 on ubuntu-latest

The import of ‘Data.Int’ is redundant
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.Text (pack, unpack)
import Data.Text (Text, pack, unpack)
import Effectful
import Effectful.Dispatch.Dynamic (EffectHandler, interpret)
import Effectful.State.Static.Shared (State, get, modify)
Expand All @@ -16,7 +18,8 @@ import EffectfulQML
import Graphics.QML hiding (fireSignal, runEngineLoop)
import Text.Read (readMaybe)

import Nostr.Keys (KeyPair, secKeyToKeyPair)
import Nostr.Keys (KeyPair, PubKeyXO, secKeyToKeyPair)
import Nostr.Types (Event, EventId, RelayURI)
import Presentation.KeyMgmt qualified as PKeyMgmt

data AppScreen
Expand All @@ -25,15 +28,27 @@ data AppScreen
| Home
deriving (Eq, Read, Show)

data ChatMessage = ChatMessage
{ chatMessageId :: EventId
, content :: Text
, author :: PubKeyXO
, createdAt :: Text
, seenOn :: [RelayURI]
}

data Futr = Futr
{ keyPair :: Maybe KeyPair
, currentScreen :: AppScreen
, events :: Map EventId (Event, [RelayURI])
, chats :: Map PubKeyXO [ChatMessage]
}

initialState :: Futr
initialState = Futr
{ keyPair = Nothing
, currentScreen = KeyMgmt
, events = Map.empty
, chats = Map.empty
}

-- | Key Management Effect for creating QML context.
Expand Down
12 changes: 6 additions & 6 deletions src/Nostr/Event.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ import Nostr.Types

signEvent :: UnsignedEvent -> KeyPair -> Maybe Event
signEvent u kp =
Event eid (pubKey' u) (created_at' u) (kind' u) (tags' u) (content' u) <$> schnorrSign kp (getEventId eid)
Event eid (pubKey' u) (createdAt' u) (kind' u) (tags' u) (content' u) <$> schnorrSign kp (getEventId eid)
where
eid = EventId { getEventId = SHA256.hash $ toStrict $ encode u }

Expand All @@ -38,7 +38,7 @@ textNote :: Text -> PubKeyXO -> Int64 -> UnsignedEvent
textNote note xo t =
UnsignedEvent
{ pubKey' = xo
, created_at' = t
, createdAt' = t
, kind' = ShortTextNote
, tags' = []
, content' = note
Expand All @@ -48,7 +48,7 @@ setMetadata :: Profile -> PubKeyXO -> Int64 -> UnsignedEvent
setMetadata profile xo t =
UnsignedEvent
{ pubKey' = xo
, created_at' = t
, createdAt' = t
, kind' = Metadata
, tags' = []
, content' = LazyText.toStrict . toLazyText . encodeToTextBuilder . toJSON $ profile
Expand All @@ -65,7 +65,7 @@ replyNote :: Event -> Text -> PubKeyXO -> Int64 -> UnsignedEvent
replyNote event note xo t =
UnsignedEvent
{ pubKey' = xo
, created_at' = t
, createdAt' = t
, kind' = ShortTextNote
, tags' = [ETag (eventId event) Nothing (Just Reply)]
, content' = note
Expand All @@ -75,7 +75,7 @@ setContacts :: [(PubKeyXO, Maybe DisplayName)] -> PubKeyXO -> Int64 -> UnsignedE
setContacts contacts xo t =
UnsignedEvent
{ pubKey' = xo
, created_at' = t
, createdAt' = t
, kind' = FollowList
, tags' = map (\c -> PTag (fst c) (Just (RelayURI emptyURI)) (snd c)) contacts
, content' = ""
Expand All @@ -85,7 +85,7 @@ deleteEvents :: [EventId] -> Text -> PubKeyXO -> Int64 -> UnsignedEvent
deleteEvents eids reason xo t =
UnsignedEvent
{ pubKey' = xo
, created_at' = t
, createdAt' = t
, kind' = EventDeletion
, tags' = toDelete
, content' = reason
Expand Down
15 changes: 8 additions & 7 deletions src/Nostr/Profile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,12 +26,13 @@ instance FromJSON Nip05Response where
parseJSON = withObject "Nip05Response" $ \v -> Nip05Response <$> v .:? "names"

verifyNip05 :: Profile -> PubKeyXO -> IO Bool
verifyNip05 (Profile _ _ _ _ (Just nip05) _) pubkey = do
let (localPart, domain) = parseNip05 nip05
let opts = defaults & param "name" .~ [localPart]
result <- try (getWith opts ("https://" ++ unpack domain ++ "/.well-known/nostr.json")) :: IO (Either SomeException (Response ByteString))
return $ either (const False) (checkResponse localPart (pack $ show pubkey) . (^. responseBody)) result
verifyNip05 _ _ = return False
verifyNip05 p pubkey = case nip05 p of
Just n -> do
let (localPart, domain) = parseNip05 n
let opts = defaults & param "name" .~ [localPart]
result <- try (getWith opts ("https://" ++ unpack domain ++ "/.well-known/nostr.json")) :: IO (Either SomeException (Response ByteString))
return $ either (const False) (checkResponse localPart (pack $ show pubkey) . (^. responseBody)) result
Nothing -> return False

checkResponse :: Text -> Text -> ByteString -> Bool
checkResponse localPart pubkey body =
Expand All @@ -43,6 +44,6 @@ checkResponse localPart pubkey body =
_ -> False

parseNip05 :: Text -> (Text, Text)
parseNip05 nip05 = case splitOn "@" nip05 of
parseNip05 n = case splitOn "@" n of
[localPart, domain] -> (localPart, domain)
_ -> ("", "")
22 changes: 14 additions & 8 deletions src/Nostr/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -108,7 +108,7 @@ data Tag
data Event = Event
{ eventId :: EventId
, pubKey :: PubKeyXO
, created_at :: Int64
, createdAt :: Int64
, kind :: Kind
, tags :: [Tag]
, content :: Text
Expand All @@ -118,7 +118,7 @@ data Event = Event

data UnsignedEvent = UnsignedEvent
{ pubKey' :: PubKeyXO
, created_at' :: Int64
, createdAt' :: Int64
, kind' :: Kind
, tags' :: [Tag]
, content' :: Text
Expand All @@ -136,8 +136,14 @@ type Picture = Text
type Banner = Text
type Nip05 = Text

data Profile = Profile Name (Maybe DisplayName) (Maybe About) (Maybe Picture) (Maybe Nip05) (Maybe Banner)
deriving (Eq, Show)
data Profile = Profile
{ name :: Maybe Text
, displayName :: Maybe Text
, about :: Maybe Text
, picture :: Maybe Text
, nip05 :: Maybe Text
, banner :: Maybe Text
} deriving (Eq, Show)

-- Helper functions

Expand Down Expand Up @@ -185,7 +191,7 @@ instance FromJSON Event where
parseJSON = withObject "event data" $ \e -> Event
<$> e .: "id"
<*> e .: "pubkey"
<*> e .: "created_at"
<*> e .: "createdAt"
<*> e .: "kind"
<*> e .: "tags"
<*> e .: "content"
Expand All @@ -195,7 +201,7 @@ instance ToJSON Event where
toJSON Event {..} = object
[ "id" .= show eventId
, "pubkey" .= show pubKey
, "created_at" .= created_at
, "createdAt" .= createdAt
, "kind" .= kind
, "tags" .= tags
, "content" .= content
Expand All @@ -206,7 +212,7 @@ instance ToJSON UnsignedEvent where
toJSON (UnsignedEvent {..}) = Array $ fromList
[ Number 0
, String $ pack $ show pubKey'
, Number $ fromIntegral $ created_at'
, Number $ fromIntegral $ createdAt'
, toJSON kind'
, toJSON tags'
, toJSON content'
Expand Down Expand Up @@ -405,7 +411,7 @@ instance ToJSON Filter where
]

instance Default Profile where
def = Profile "" Nothing Nothing Nothing Nothing Nothing
def = Profile Nothing Nothing Nothing Nothing Nothing Nothing

instance ToJSON Profile where
toJSON (Profile name displayName about picture nip05 banner) = object
Expand Down
6 changes: 3 additions & 3 deletions src/Presentation/KeyMgmt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ import EffectfulQML
import Graphics.QML hiding (fireSignal, runEngineLoop)
import Nostr.Keys
import Nostr.Relay (defaultRelays)
import Nostr.Types
import Nostr.Types hiding (displayName, picture)
import System.FilePath (takeFileName, (</>))
import Text.Read (readMaybe)

Expand Down Expand Up @@ -243,8 +243,8 @@ tryImportSecretKeyAndPersist input = do
return Nothing

isNpubDirectory :: (FileSystem :> es) => FilePath -> FilePath -> Eff es Bool
isNpubDirectory storageDir name = do
let fullPath = storageDir </> name
isNpubDirectory storageDir dirName = do
let fullPath = storageDir </> dirName
isDir <- doesDirectoryExist fullPath
let fileName = takeFileName fullPath
return $ isDir && "npub" `isPrefixOf` pack fileName
Expand Down
23 changes: 23 additions & 0 deletions src/TimeFormatter.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
module TimeFormatter (formatDateTime) where

import Data.Int (Int64)
import Data.Text (Text)
import Data.Text qualified as T
import Data.Time (UTCTime, formatTime, defaultTimeLocale)
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)

data Language = English | Spanish | German

-- Convert Int64 (Unix timestamp) to UTCTime
int64ToUTCTime :: Int64 -> UTCTime
int64ToUTCTime = posixSecondsToUTCTime . fromIntegral

-- Format UTCTime to Text based on the provided format
formatUTCTime :: String -> UTCTime -> Text
formatUTCTime format utcTime = T.pack $ formatTime defaultTimeLocale format utcTime

-- Helper function to format time
formatDateTime :: Language -> Int64 -> Text
formatDateTime English = formatUTCTime "%H:%M:%S %Y-%m-%d" . int64ToUTCTime
formatDateTime German = formatUTCTime "%H:%M:%S %d.%m.%Y" . int64ToUTCTime
formatDateTime Spanish = formatUTCTime "%H:%M:%S %d/%m/%Y" . int64ToUTCTime

0 comments on commit 9e9cb4e

Please sign in to comment.