This commit is contained in:
Benjamin Summers 2019-07-12 12:18:14 -07:00
parent 31d8e217c2
commit 2d2029106b
13 changed files with 43 additions and 53 deletions

View File

@ -1,5 +1,5 @@
module Noun.Conversions
( Cord(..), Knot(..), Term(..), Tank(..), Tang, Plum(..)
( Cord(..), Knot(..), Term(..), Tank(..), Tang, Plum(..), Nullable
) where
import ClassyPrelude hiding (hash)
@ -125,14 +125,9 @@ instance FromNoun a => FromNoun [a] where
-- Tape ------------------------------------------------------------------------
-- TODO XX are these instances correct?
newtype Tape = Tape [Char]
deriving newtype (Eq, Ord, Show)
instance FromNoun Tape where
parseNoun = undefined
instance ToNoun Tape where
toNoun = undefined
deriving newtype (Eq, Ord, Show, FromNoun, ToNoun)
-- Pretty Printing -------------------------------------------------------------

View File

@ -23,10 +23,11 @@ data Noun
= NCell Int Word Noun Noun
| NAtom Int Atom
{-# COMPLETE Cell, Atom #-}
pattern Cell x y <- NCell _ _ x y where Cell = mkCell
pattern Atom a <- NAtom _ a where Atom = mkAtom
{-# COMPLETE Cell, Atom #-}
--------------------------------------------------------------------------------

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wwarn #-}
module Urbit.Ames where
import ClassyPrelude
@ -41,12 +43,12 @@ data NetworkMode
= LocalOnlyNetworking
| GlobalNetworking
--
ioStart :: Ames -> NetworkMode -> Int -> Noun -> IO Ames
ioStart ames isLocal defaultPort (Cell _ _) = undefined
ioStart ames isLocal defaultPort (Atom who) = do
let port = if who < 256
then computePort isLocal who
else defaultPort
let _port = if who < 256
then computePort isLocal who
else defaultPort
-- TODO: set up another thread to own the recv socket, which makes the Ovums
-- which get put into the computeQueue, like in _ames_recv_cb.

View File

@ -7,7 +7,7 @@ import Control.Lens
import Noun (FromNoun, ToNoun)
import Data.Bits (shiftL, shiftR)
import Data.Time.Clock (DiffTime, UTCTime, picosecondsToDiffTime)
import Data.Time.Clock (DiffTime, UTCTime)
import Data.Time.Clock (picosecondsToDiffTime, diffTimeToPicoseconds)
import Data.Time.Clock.System (SystemTime(..), getSystemTime)
import Data.Time.Clock.System (utcToSystemTime, systemToUTCTime)

View File

@ -4,8 +4,6 @@ import ClassyPrelude
import Data.IP
import Data.Void
import Noun
import Noun.TH
import Control.Lens
import qualified Urbit.Time as Time

View File

@ -4,7 +4,6 @@ module Vere.Http where
import ClassyPrelude
import Noun
import Noun.TH
import qualified Data.CaseInsensitive as CI
import qualified Network.HTTP.Types as HT

View File

@ -6,13 +6,13 @@
module Vere.Http.Client where
import ClassyPrelude
import Vere.Http
import Noun
import Noun.TH
import Vere.Http
import qualified Data.CaseInsensitive as CI
import qualified Network.HTTP.Types as HT
import qualified Network.HTTP.Client as H
import qualified Network.HTTP.Client as H
import qualified Network.HTTP.Types as HT
-- Types -----------------------------------------------------------------------

View File

@ -3,10 +3,10 @@
module Vere.Http.Server where
import ClassyPrelude
import Vere.Http
import Noun
import Noun.TH
import Control.Lens
import Noun
import Vere.Http
import Control.Concurrent (ThreadId, killThread, forkIO)
@ -16,6 +16,8 @@ import qualified Network.Wai as W
import qualified Network.Wai.Handler.Warp as W
import qualified Network.Wai.Handler.WarpTLS as W
-- Types -----------------------------------------------------------------------
type ServerId = Word
type ConnectionId = Word
type RequestId = Word
@ -60,8 +62,6 @@ data ClientResponse
data MimeData = MimeData Text ByteString
--
data Ev
data State = State
@ -69,6 +69,8 @@ data State = State
, sChan :: MVar Ev
}
--------------------------------------------------------------------------------
init :: IO State
init =
-- When we initialize things, we send an event into arvo

View File

@ -16,11 +16,10 @@ module Vere.Log ( open
import ClassyPrelude hiding (init)
import Control.Lens hiding ((<|))
import Noun
import Data.Void
import Database.LMDB.Raw
import Foreign.Ptr
import Foreign.Marshal.Alloc
import Foreign.Ptr
import Noun
import Vere.Pier.Types
import Control.Concurrent (runInBoundThread)
@ -28,9 +27,7 @@ import Control.Lens ((^.))
import Foreign.Storable (peek, poke, sizeOf)
import qualified Data.ByteString.Unsafe as BU
import qualified Data.ByteString as B
import qualified Data.Vector as V
import qualified Data.Vector.Mutable as MV
-- Open/Close an Event Log -----------------------------------------------------

View File

@ -2,14 +2,12 @@ module Vere.Pier where
import ClassyPrelude
import Noun
import Vere.Pier.Types
import qualified Vere.Log as Log
import qualified Vere.Persist as Persist
import qualified Vere.Serf as Serf
import qualified Vere.Log as Log
import qualified Vere.Serf as Serf
import Vere.Serf (Serf, EventId)
import Vere.Serf (EventId, Serf)
--------------------------------------------------------------------------------

View File

@ -1,14 +1,10 @@
module Vere.Pier.Types where
import ClassyPrelude
import Data.Void
import Noun
import Noun.TH
import Database.LMDB.Raw
import Urbit.Time
import RIO (decodeUtf8Lenient)
import qualified Vere.Ames as Ames
import qualified Vere.Http.Client as Client
import qualified Vere.Http.Server as Server
@ -81,6 +77,16 @@ data Blit
| Url Text
deriving (Eq, Ord, Show)
data Varience = Gold | Iron | Lead
type Perform = Eff -> IO ()
data Ovum = Ovum Path Event
deriving (Eq, Ord, Show)
newtype Mug = Mug Word32
deriving newtype (Eq, Ord, Show, ToNoun, FromNoun)
deriveNoun ''Blit
deriveNoun ''Eff
deriveNoun ''Event
@ -88,16 +94,7 @@ deriveNoun ''PutDel
deriveNoun ''EffBs
deriveNoun ''RecEx
deriveNoun ''NewtEx
data Varience = Gold | Iron | Lead
type Perform = Eff -> IO ()
data Ovum = Ovum Path Event
deriving (Eq, Ord, Show, Generic, ToNoun)
newtype Mug = Mug Word32
deriving newtype (Eq, Ord, Show, ToNoun, FromNoun)
deriveNoun ''Ovum
newtype Jam = Jam Atom

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wwarn #-}
module Vere.Serf where
import ClassyPrelude
@ -17,7 +19,6 @@ import System.Exit (ExitCode)
import qualified Data.ByteString.Unsafe as BS
import qualified Urbit.Time as Time
import qualified Vere.Log as Log
--------------------------------------------------------------------------------
@ -268,7 +269,7 @@ workerThread w getEvent (evendId, mug) = async $ forever do
currentDate <- Time.now
let mat = jam (undefined (mug, currentDate, ovum))
let _mat = jam (undefined (mug, currentDate, ovum))
undefined

View File

@ -8,7 +8,7 @@ library:
- -fwarn-incomplete-patterns
- -fwarn-unused-binds
- -fwarn-unused-imports
# -Werror
- -Werror
- -O2
dependencies: