mirror of
https://github.com/ilyakooo0/urbit.git
synced 2024-11-14 15:04:14 +03:00
Got docs to build.
This commit is contained in:
parent
06934959ca
commit
f0892436ff
@ -60,14 +60,14 @@ import Data.Conduit
|
|||||||
import Data.Conduit.List hiding (catMaybes, map, replicate, take)
|
import Data.Conduit.List hiding (catMaybes, map, replicate, take)
|
||||||
import Data.RAcquire
|
import Data.RAcquire
|
||||||
import Network.HTTP.Client.TLS
|
import Network.HTTP.Client.TLS
|
||||||
import Noun hiding (Parser)
|
|
||||||
import Noun.Atom
|
|
||||||
import Noun.Conversions (cordToUW)
|
|
||||||
import RIO.Directory
|
import RIO.Directory
|
||||||
|
import Ur.Noun hiding (Parser)
|
||||||
|
import Ur.Noun.Atom
|
||||||
|
import Ur.Noun.Conversions (cordToUW)
|
||||||
|
import Vere.Dawn
|
||||||
import Vere.Pier
|
import Vere.Pier
|
||||||
import Vere.Pier.Types
|
import Vere.Pier.Types
|
||||||
import Vere.Serf
|
import Vere.Serf
|
||||||
import Vere.Dawn
|
|
||||||
|
|
||||||
import Control.Concurrent (myThreadId, runInBoundThread)
|
import Control.Concurrent (myThreadId, runInBoundThread)
|
||||||
import Control.Exception (AsyncException(UserInterrupt))
|
import Control.Exception (AsyncException(UserInterrupt))
|
||||||
|
@ -2,7 +2,7 @@ module TryJamPill where
|
|||||||
|
|
||||||
import ClassyPrelude
|
import ClassyPrelude
|
||||||
import Control.Lens
|
import Control.Lens
|
||||||
import Noun
|
import Ur.Noun
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
|
@ -1,70 +0,0 @@
|
|||||||
let Persist = { collect-fx : Bool }
|
|
||||||
|
|
||||||
let FakeMode = < Dry | Wet : Persist >
|
|
||||||
|
|
||||||
let Mode = < Online : Persist | Local : Persist | Fake : FakeMode >
|
|
||||||
|
|
||||||
let Verbose = < Quiet | Normal | Verbose >
|
|
||||||
|
|
||||||
let King = { mode : Mode, log : Verbose }
|
|
||||||
|
|
||||||
let Serf =
|
|
||||||
{ debug-ram :
|
|
||||||
Bool
|
|
||||||
, debug-cpu :
|
|
||||||
Bool
|
|
||||||
, check-corrupt :
|
|
||||||
Bool
|
|
||||||
, check-fatal :
|
|
||||||
Bool
|
|
||||||
, verbose :
|
|
||||||
Bool
|
|
||||||
, dry-run :
|
|
||||||
Bool
|
|
||||||
, quiet :
|
|
||||||
Bool
|
|
||||||
, hashless :
|
|
||||||
Bool
|
|
||||||
, trace :
|
|
||||||
Bool
|
|
||||||
}
|
|
||||||
|
|
||||||
let Ship = { addr : Text, serf : Serf, ames-port : Optional Natural }
|
|
||||||
|
|
||||||
let Config = { king : King, ships : List Ship }
|
|
||||||
|
|
||||||
let KingDefault =
|
|
||||||
{ mode = Mode.Online { collect-fx = False }, log = Verbose.Normal } : King
|
|
||||||
|
|
||||||
let SerfDefault =
|
|
||||||
{ debug-ram =
|
|
||||||
False
|
|
||||||
, debug-cpu =
|
|
||||||
False
|
|
||||||
, check-corrupt =
|
|
||||||
False
|
|
||||||
, check-fatal =
|
|
||||||
False
|
|
||||||
, verbose =
|
|
||||||
False
|
|
||||||
, dry-run =
|
|
||||||
False
|
|
||||||
, quiet =
|
|
||||||
False
|
|
||||||
, hashless =
|
|
||||||
False
|
|
||||||
, trace =
|
|
||||||
False
|
|
||||||
}
|
|
||||||
: Serf
|
|
||||||
|
|
||||||
let ShipDefault =
|
|
||||||
λ(addr : Text)
|
|
||||||
→ { addr = addr, serf = SerfDefault, ames-port = None Natural }
|
|
||||||
|
|
||||||
let ConfigDefault = { king = KingDefault, ships = [] : List Ship } : Config
|
|
||||||
|
|
||||||
let ConfigExample =
|
|
||||||
{ king = KingDefault, ships = [ ShipDefault "zod" ] } : Config
|
|
||||||
|
|
||||||
in ConfigExample
|
|
@ -8,6 +8,6 @@ module Arvo
|
|||||||
import Arvo.Common
|
import Arvo.Common
|
||||||
import Arvo.Effect
|
import Arvo.Effect
|
||||||
import Arvo.Event
|
import Arvo.Event
|
||||||
import Noun.Conversions (Lenient)
|
import Ur.Noun.Conversions (Lenient)
|
||||||
|
|
||||||
type FX = [Lenient Ef]
|
type FX = [Lenient Ef]
|
||||||
|
@ -1,6 +1,6 @@
|
|||||||
module Arvo.Event where
|
module Arvo.Event where
|
||||||
|
|
||||||
import Noun.Tree (HoonMap, HoonSet)
|
import Ur.Noun.Tree (HoonMap, HoonSet)
|
||||||
import UrbitPrelude hiding (Term)
|
import UrbitPrelude hiding (Term)
|
||||||
|
|
||||||
import Arvo.Common (KingId(..), ServId(..))
|
import Arvo.Common (KingId(..), ServId(..))
|
||||||
|
@ -1,5 +0,0 @@
|
|||||||
module Azimuth.Azimuth where
|
|
||||||
|
|
||||||
import Network.Ethereum.Contract.TH
|
|
||||||
|
|
||||||
[abiFrom|lib/Azimuth/azimuth.json|]
|
|
@ -117,7 +117,7 @@ serveTerminal env api word =
|
|||||||
$ NounServ.wsConn "NOUNSERV (wsServ) " inp out wsc
|
$ NounServ.wsConn "NOUNSERV (wsServ) " inp out wsc
|
||||||
|
|
||||||
-- If `wai` kills this thread for any reason, the TBMChans
|
-- If `wai` kills this thread for any reason, the TBMChans
|
||||||
-- *need* to be closed. If they are not closed, the
|
-- need to be closed. If they are not closed, the
|
||||||
-- terminal will not know that they disconnected.
|
-- terminal will not know that they disconnected.
|
||||||
finally doit $ atomically $ do
|
finally doit $ atomically $ do
|
||||||
closeTBMChan inp
|
closeTBMChan inp
|
||||||
|
@ -1,92 +0,0 @@
|
|||||||
module KingApp
|
|
||||||
( App
|
|
||||||
, runApp
|
|
||||||
, runPierApp
|
|
||||||
, HasAppName(..)
|
|
||||||
) where
|
|
||||||
|
|
||||||
import Config
|
|
||||||
import RIO.Directory
|
|
||||||
import UrbitPrelude
|
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
|
||||||
|
|
||||||
class HasAppName env where
|
|
||||||
appNameL :: Lens' env Utf8Builder
|
|
||||||
|
|
||||||
data App = App
|
|
||||||
{ _appLogFunc :: !LogFunc
|
|
||||||
, _appName :: !Utf8Builder
|
|
||||||
}
|
|
||||||
|
|
||||||
makeLenses ''App
|
|
||||||
|
|
||||||
instance HasLogFunc App where
|
|
||||||
logFuncL = appLogFunc
|
|
||||||
|
|
||||||
instance HasAppName App where
|
|
||||||
appNameL = appName
|
|
||||||
|
|
||||||
withLogFileHandle :: (Handle -> IO a) -> IO a
|
|
||||||
withLogFileHandle act = do
|
|
||||||
home <- getHomeDirectory
|
|
||||||
let logDir = home <> "/log"
|
|
||||||
createDirectoryIfMissing True logDir
|
|
||||||
withTempFile logDir "king-" $ \_tmpFile handle -> do
|
|
||||||
hSetBuffering handle LineBuffering
|
|
||||||
act handle
|
|
||||||
|
|
||||||
runApp :: RIO App a -> IO a
|
|
||||||
runApp inner = do
|
|
||||||
withLogFileHandle $ \logFile -> do
|
|
||||||
logOptions <- logOptionsHandle stderr True
|
|
||||||
<&> setLogUseTime True
|
|
||||||
<&> setLogUseLoc False
|
|
||||||
|
|
||||||
withLogFunc logOptions $ \logFunc ->
|
|
||||||
go $ App { _appLogFunc = logFunc
|
|
||||||
, _appName = "Vere"
|
|
||||||
}
|
|
||||||
where
|
|
||||||
go app = runRIO app inner
|
|
||||||
|
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
|
||||||
|
|
||||||
-- A PierApp is like an App, except that it also provides a PierConfig
|
|
||||||
data PierApp = PierApp
|
|
||||||
{ _shipAppLogFunc :: !LogFunc
|
|
||||||
, _shipAppName :: !Utf8Builder
|
|
||||||
, _shipAppPierConfig :: !PierConfig
|
|
||||||
, _shipAppNetworkConfig :: !NetworkConfig
|
|
||||||
}
|
|
||||||
|
|
||||||
makeLenses ''PierApp
|
|
||||||
|
|
||||||
instance HasLogFunc PierApp where
|
|
||||||
logFuncL = shipAppLogFunc
|
|
||||||
|
|
||||||
instance HasAppName PierApp where
|
|
||||||
appNameL = shipAppName
|
|
||||||
|
|
||||||
instance HasPierConfig PierApp where
|
|
||||||
pierConfigL = shipAppPierConfig
|
|
||||||
|
|
||||||
instance HasNetworkConfig PierApp where
|
|
||||||
networkConfigL = shipAppNetworkConfig
|
|
||||||
|
|
||||||
runPierApp :: PierConfig -> NetworkConfig -> RIO PierApp a -> IO a
|
|
||||||
runPierApp pierConfig networkConfig inner = do
|
|
||||||
withLogFileHandle $ \logFile -> do
|
|
||||||
logOptions <- logOptionsHandle stderr True
|
|
||||||
<&> setLogUseTime True
|
|
||||||
<&> setLogUseLoc False
|
|
||||||
|
|
||||||
withLogFunc logOptions $ \logFunc ->
|
|
||||||
go $ PierApp { _shipAppLogFunc = logFunc
|
|
||||||
, _shipAppName = "Vere"
|
|
||||||
, _shipAppPierConfig = pierConfig
|
|
||||||
, _shipAppNetworkConfig = networkConfig
|
|
||||||
}
|
|
||||||
where
|
|
||||||
go app = runRIO app inner
|
|
@ -1 +0,0 @@
|
|||||||
module Noun.Lens where
|
|
@ -1,14 +1,14 @@
|
|||||||
module Noun
|
module Ur.Noun
|
||||||
( module Noun.Atom
|
( module Ur.Noun.Atom
|
||||||
, module Data.Word
|
, module Data.Word
|
||||||
, module Noun.Conversions
|
, module Ur.Noun.Conversions
|
||||||
, module Noun.Convert
|
, module Ur.Noun.Convert
|
||||||
, module Noun.Core
|
, module Ur.Noun.Core
|
||||||
, module Noun.Cue
|
, module Ur.Noun.Cue
|
||||||
, module Noun.Jam
|
, module Ur.Noun.Jam
|
||||||
, module Noun.Tank
|
, module Ur.Noun.Tank
|
||||||
, module Noun.TH
|
, module Ur.Noun.TH
|
||||||
, module Noun.Tree
|
, module Ur.Noun.Tree
|
||||||
, _Cue
|
, _Cue
|
||||||
, LoadErr(..)
|
, LoadErr(..)
|
||||||
, loadFile
|
, loadFile
|
||||||
@ -18,15 +18,15 @@ import ClassyPrelude
|
|||||||
import Control.Lens
|
import Control.Lens
|
||||||
|
|
||||||
import Data.Word
|
import Data.Word
|
||||||
import Noun.Atom
|
import Ur.Noun.Atom
|
||||||
import Noun.Tree
|
import Ur.Noun.Tree
|
||||||
import Noun.Conversions
|
import Ur.Noun.Conversions
|
||||||
import Noun.Convert
|
import Ur.Noun.Convert
|
||||||
import Noun.Core
|
import Ur.Noun.Core
|
||||||
import Noun.Cue
|
import Ur.Noun.Cue
|
||||||
import Noun.Jam
|
import Ur.Noun.Jam
|
||||||
import Noun.Tank
|
import Ur.Noun.Tank
|
||||||
import Noun.TH
|
import Ur.Noun.TH
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
@ -5,7 +5,7 @@
|
|||||||
|
|
||||||
{-# OPTIONS_GHC -Werror #-}
|
{-# OPTIONS_GHC -Werror #-}
|
||||||
|
|
||||||
module Noun.Atom
|
module Ur.Noun.Atom
|
||||||
( Atom(..)
|
( Atom(..)
|
||||||
, atomBitWidth#, wordBitWidth#, wordBitWidth
|
, atomBitWidth#, wordBitWidth#, wordBitWidth
|
||||||
, takeBitsWord, bitWidth
|
, takeBitsWord, bitWidth
|
@ -1,6 +1,6 @@
|
|||||||
{-# OPTIONS_GHC -Wwarn #-}
|
{-# OPTIONS_GHC -Wwarn #-}
|
||||||
|
|
||||||
module Noun.Conversions
|
module Ur.Noun.Conversions
|
||||||
( Nullable(..), Jammed(..), AtomCell(..)
|
( Nullable(..), Jammed(..), AtomCell(..)
|
||||||
, Word128, Word256, Word512
|
, Word128, Word256, Word512
|
||||||
, Bytes(..), Octs(..), File(..)
|
, Bytes(..), Octs(..), File(..)
|
||||||
@ -14,29 +14,29 @@ module Noun.Conversions
|
|||||||
|
|
||||||
import ClassyPrelude hiding (hash)
|
import ClassyPrelude hiding (hash)
|
||||||
|
|
||||||
import Control.Lens hiding (Index, Each, (<.>))
|
import Control.Lens hiding (Each, Index, (<.>))
|
||||||
import Data.Void
|
import Data.Void
|
||||||
import Data.Word
|
import Data.Word
|
||||||
import Noun.Atom
|
|
||||||
import Noun.Convert
|
|
||||||
import Noun.Core
|
|
||||||
import Noun.TH
|
|
||||||
import Text.Regex.TDFA
|
import Text.Regex.TDFA
|
||||||
import Text.Regex.TDFA.Text ()
|
import Text.Regex.TDFA.Text ()
|
||||||
|
import Ur.Noun.Atom
|
||||||
|
import Ur.Noun.Convert
|
||||||
|
import Ur.Noun.Core
|
||||||
|
import Ur.Noun.TH
|
||||||
|
|
||||||
import Data.LargeWord (LargeKey, Word128, Word256)
|
import Data.LargeWord (LargeKey, Word128, Word256)
|
||||||
import GHC.Exts (chr#, isTrue#, leWord#, word2Int#)
|
import GHC.Exts (chr#, isTrue#, leWord#, word2Int#)
|
||||||
import GHC.Natural (Natural)
|
import GHC.Natural (Natural)
|
||||||
import GHC.Types (Char(C#))
|
import GHC.Types (Char(C#))
|
||||||
import GHC.Word (Word32(W32#))
|
import GHC.Word (Word32(W32#))
|
||||||
import Noun.Cue (cue)
|
|
||||||
import Noun.Jam (jam)
|
|
||||||
import Prelude ((!!))
|
import Prelude ((!!))
|
||||||
import RIO (decodeUtf8Lenient)
|
import RIO (decodeUtf8Lenient)
|
||||||
|
import RIO.FilePath (joinPath, splitDirectories, takeBaseName,
|
||||||
|
takeDirectory, takeExtension, (<.>), (</>))
|
||||||
import System.IO.Unsafe (unsafePerformIO)
|
import System.IO.Unsafe (unsafePerformIO)
|
||||||
import Text.Show.Pretty (ppShow)
|
import Text.Show.Pretty (ppShow)
|
||||||
import RIO.FilePath ((</>), (<.>), joinPath, splitDirectories,
|
import Ur.Noun.Cue (cue)
|
||||||
takeBaseName, takeDirectory, takeExtension)
|
import Ur.Noun.Jam (jam)
|
||||||
|
|
||||||
import qualified Data.Char as C
|
import qualified Data.Char as C
|
||||||
import qualified Data.Text.Encoding as T
|
import qualified Data.Text.Encoding as T
|
@ -1,4 +1,4 @@
|
|||||||
module Noun.Convert
|
module Ur.Noun.Convert
|
||||||
( ToNoun(toNoun)
|
( ToNoun(toNoun)
|
||||||
, FromNoun(parseNoun), fromNoun, fromNounErr, fromNounExn
|
, FromNoun(parseNoun), fromNoun, fromNounErr, fromNounExn
|
||||||
, Parser(..)
|
, Parser(..)
|
||||||
@ -8,7 +8,8 @@ module Noun.Convert
|
|||||||
) where
|
) where
|
||||||
|
|
||||||
import ClassyPrelude hiding (hash)
|
import ClassyPrelude hiding (hash)
|
||||||
import Noun.Core
|
|
||||||
|
import Ur.Noun.Core
|
||||||
|
|
||||||
import qualified Control.Monad.Fail as Fail
|
import qualified Control.Monad.Fail as Fail
|
||||||
|
|
@ -2,7 +2,7 @@
|
|||||||
{-# LANGUAGE Strict #-}
|
{-# LANGUAGE Strict #-}
|
||||||
{-# LANGUAGE StrictData #-}
|
{-# LANGUAGE StrictData #-}
|
||||||
|
|
||||||
module Noun.Core
|
module Ur.Noun.Core
|
||||||
( Noun, nounSize
|
( Noun, nounSize
|
||||||
, pattern Cell, pattern Atom
|
, pattern Cell, pattern Atom
|
||||||
, pattern C, pattern A
|
, pattern C, pattern A
|
||||||
@ -11,7 +11,7 @@ module Noun.Core
|
|||||||
|
|
||||||
import ClassyPrelude hiding (hash)
|
import ClassyPrelude hiding (hash)
|
||||||
|
|
||||||
import Noun.Atom
|
import Ur.Noun.Atom
|
||||||
|
|
||||||
import Control.Lens (view, from, (&), (^.))
|
import Control.Lens (view, from, (&), (^.))
|
||||||
import Data.Bits (xor)
|
import Data.Bits (xor)
|
@ -1,11 +1,11 @@
|
|||||||
{-# OPTIONS_GHC -O2 #-}
|
{-# OPTIONS_GHC -O2 #-}
|
||||||
|
|
||||||
module Noun.Cue (cue, cueExn, cueBS, cueBSExn, DecodeErr) where
|
module Ur.Noun.Cue (cue, cueExn, cueBS, cueBSExn, DecodeErr) where
|
||||||
|
|
||||||
import ClassyPrelude
|
import ClassyPrelude
|
||||||
|
|
||||||
import Noun.Atom
|
import Ur.Noun.Atom
|
||||||
import Noun.Core
|
import Ur.Noun.Core
|
||||||
|
|
||||||
import Control.Lens (from, view, (&), (^.))
|
import Control.Lens (from, view, (&), (^.))
|
||||||
import Data.Bits (shiftL, shiftR, (.&.), (.|.))
|
import Data.Bits (shiftL, shiftR, (.&.), (.|.))
|
@ -1,11 +1,11 @@
|
|||||||
{-# OPTIONS_GHC -O2 #-}
|
{-# OPTIONS_GHC -O2 #-}
|
||||||
|
|
||||||
module Noun.Jam (jam, jamBS) where
|
module Ur.Noun.Jam (jam, jamBS) where
|
||||||
|
|
||||||
import ClassyPrelude hiding (hash)
|
import ClassyPrelude hiding (hash)
|
||||||
|
|
||||||
import Noun.Atom
|
import Ur.Noun.Atom
|
||||||
import Noun.Core
|
import Ur.Noun.Core
|
||||||
|
|
||||||
import Control.Lens (from, view)
|
import Control.Lens (from, view)
|
||||||
import Data.Bits (clearBit, setBit, shiftL, shiftR, (.|.))
|
import Data.Bits (clearBit, setBit, shiftL, shiftR, (.|.))
|
1
pkg/hs/king/lib/Ur/Noun/Lens.hs
Normal file
1
pkg/hs/king/lib/Ur/Noun/Lens.hs
Normal file
@ -0,0 +1 @@
|
|||||||
|
module Ur.Noun.Lens where
|
@ -1,10 +1,12 @@
|
|||||||
module Noun.Rip where
|
module Ur.Noun.Rip where
|
||||||
|
|
||||||
import ClassyPrelude
|
import ClassyPrelude
|
||||||
import Noun.Atom
|
|
||||||
import Data.Bits
|
import Data.Bits
|
||||||
import Control.Lens (view, (&), from)
|
import Ur.Noun.Atom
|
||||||
import qualified Data.Vector.Primitive as VP
|
|
||||||
|
import Control.Lens (from, view, (&))
|
||||||
|
|
||||||
|
import qualified Data.Vector.Primitive as VP
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
@ -2,14 +2,14 @@
|
|||||||
Generate FromNoun and ToNoun instances.
|
Generate FromNoun and ToNoun instances.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Noun.TH (deriveNoun, deriveToNoun, deriveFromNoun) where
|
module Ur.Noun.TH (deriveNoun, deriveToNoun, deriveFromNoun) where
|
||||||
|
|
||||||
import ClassyPrelude hiding (fromList)
|
import ClassyPrelude hiding (fromList)
|
||||||
import Language.Haskell.TH
|
import Language.Haskell.TH
|
||||||
import Language.Haskell.TH.Syntax
|
import Language.Haskell.TH.Syntax
|
||||||
import Noun.Convert
|
import Ur.Noun.Convert
|
||||||
|
|
||||||
import Noun.Core (textToUtf8Atom)
|
import Ur.Noun.Core (textToUtf8Atom)
|
||||||
|
|
||||||
import qualified Data.Char as C
|
import qualified Data.Char as C
|
||||||
|
|
@ -1,8 +1,8 @@
|
|||||||
module Noun.Tank where
|
module Ur.Noun.Tank where
|
||||||
|
|
||||||
import ClassyPrelude
|
import ClassyPrelude
|
||||||
import Noun.Conversions
|
import Ur.Noun.Conversions
|
||||||
import Noun.TH
|
import Ur.Noun.TH
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
@ -1,6 +1,6 @@
|
|||||||
{-# LANGUAGE DuplicateRecordFields, DisambiguateRecordFields #-}
|
{-# LANGUAGE DuplicateRecordFields, DisambiguateRecordFields #-}
|
||||||
|
|
||||||
module Noun.Tree
|
module Ur.Noun.Tree
|
||||||
( HoonSet, setToHoonSet, setFromHoonSet
|
( HoonSet, setToHoonSet, setFromHoonSet
|
||||||
, HoonMap, mapToHoonMap, mapFromHoonMap
|
, HoonMap, mapToHoonMap, mapFromHoonMap
|
||||||
, mug
|
, mug
|
||||||
@ -9,11 +9,11 @@ module Noun.Tree
|
|||||||
import ClassyPrelude
|
import ClassyPrelude
|
||||||
import Control.Lens hiding (non)
|
import Control.Lens hiding (non)
|
||||||
|
|
||||||
import Noun.Atom
|
import Ur.Noun.Atom
|
||||||
import Noun.Conversions ()
|
import Ur.Noun.Conversions ()
|
||||||
import Noun.Convert
|
import Ur.Noun.Convert
|
||||||
import Noun.Core
|
import Ur.Noun.Core
|
||||||
import Noun.TH
|
import Ur.Noun.TH
|
||||||
|
|
||||||
import Data.Bits (shiftR, xor)
|
import Data.Bits (shiftR, xor)
|
||||||
import Data.Hash.Murmur (murmur3)
|
import Data.Hash.Murmur (murmur3)
|
@ -1,10 +0,0 @@
|
|||||||
module Urbit.CTTP where
|
|
||||||
|
|
||||||
{-
|
|
||||||
h2o_iovec_t
|
|
||||||
_cttp_vec_to_atom
|
|
||||||
u3_hhed*
|
|
||||||
type HHed = [(Text, Text)]
|
|
||||||
u3_hbod*
|
|
||||||
type HBod = [ByteString]
|
|
||||||
-}
|
|
@ -10,7 +10,7 @@ import Data.Time.Clock (DiffTime, UTCTime)
|
|||||||
import Data.Time.Clock (diffTimeToPicoseconds, picosecondsToDiffTime)
|
import Data.Time.Clock (diffTimeToPicoseconds, picosecondsToDiffTime)
|
||||||
import Data.Time.Clock.System (SystemTime(..), getSystemTime)
|
import Data.Time.Clock.System (SystemTime(..), getSystemTime)
|
||||||
import Data.Time.Clock.System (systemToUTCTime, utcToSystemTime)
|
import Data.Time.Clock.System (systemToUTCTime, utcToSystemTime)
|
||||||
import Noun (FromNoun, ToNoun)
|
import Ur.Noun (FromNoun, ToNoun)
|
||||||
|
|
||||||
|
|
||||||
-- Types -----------------------------------------------------------------------
|
-- Types -----------------------------------------------------------------------
|
||||||
|
@ -5,7 +5,7 @@ module UrbitPrelude
|
|||||||
, module Data.Acquire
|
, module Data.Acquire
|
||||||
, module Data.RAcquire
|
, module Data.RAcquire
|
||||||
, module Data.Void
|
, module Data.Void
|
||||||
, module Noun
|
, module Ur.Noun
|
||||||
, module Text.Show.Pretty
|
, module Text.Show.Pretty
|
||||||
, module Text.Printf
|
, module Text.Printf
|
||||||
, module RIO
|
, module RIO
|
||||||
@ -14,7 +14,7 @@ module UrbitPrelude
|
|||||||
) where
|
) where
|
||||||
|
|
||||||
import ClassyPrelude
|
import ClassyPrelude
|
||||||
import Noun
|
import Ur.Noun
|
||||||
|
|
||||||
import Control.Lens hiding (Index, cons, index, snoc, uncons, unsnoc, (<.>),
|
import Control.Lens hiding (Index, cons, index, snoc, uncons, unsnoc, (<.>),
|
||||||
(<|), Each)
|
(<|), Each)
|
||||||
|
@ -14,7 +14,7 @@ import Network.Ethereum.Api.Types hiding (blockNumber)
|
|||||||
import Network.Ethereum.Web3
|
import Network.Ethereum.Web3
|
||||||
import Network.HTTP.Client.TLS
|
import Network.HTTP.Client.TLS
|
||||||
|
|
||||||
import qualified Azimuth.Azimuth as AZ
|
import qualified Ur.Azimuth as AZ
|
||||||
import qualified Crypto.Hash.SHA256 as SHA256
|
import qualified Crypto.Hash.SHA256 as SHA256
|
||||||
import qualified Crypto.Hash.SHA512 as SHA512
|
import qualified Crypto.Hash.SHA512 as SHA512
|
||||||
import qualified Crypto.Sign.Ed25519 as Ed
|
import qualified Crypto.Sign.Ed25519 as Ed
|
||||||
|
@ -3,7 +3,7 @@
|
|||||||
module Vere.Http where
|
module Vere.Http where
|
||||||
|
|
||||||
import ClassyPrelude
|
import ClassyPrelude
|
||||||
import Noun
|
import Ur.Noun
|
||||||
import Arvo
|
import Arvo
|
||||||
|
|
||||||
import qualified Data.CaseInsensitive as CI
|
import qualified Data.CaseInsensitive as CI
|
||||||
|
@ -29,7 +29,7 @@ module Vere.Http.Server where
|
|||||||
import Arvo hiding (ServerId, reqBody, reqUrl, secure)
|
import Arvo hiding (ServerId, reqBody, reqUrl, secure)
|
||||||
import Config
|
import Config
|
||||||
import Data.Conduit
|
import Data.Conduit
|
||||||
import Noun
|
import Ur.Noun
|
||||||
import UrbitPrelude hiding (Builder)
|
import UrbitPrelude hiding (Builder)
|
||||||
import Vere.Pier.Types
|
import Vere.Pier.Types
|
||||||
|
|
||||||
|
@ -102,6 +102,7 @@ dependencies:
|
|||||||
- unliftio
|
- unliftio
|
||||||
- unliftio-core
|
- unliftio-core
|
||||||
- unordered-containers
|
- unordered-containers
|
||||||
|
- ur-azimuth
|
||||||
- urbit-hob
|
- urbit-hob
|
||||||
- utf8-string
|
- utf8-string
|
||||||
- vector
|
- vector
|
||||||
|
@ -5,7 +5,7 @@ import Config
|
|||||||
import Data.Conduit
|
import Data.Conduit
|
||||||
import Data.Conduit.List hiding (take)
|
import Data.Conduit.List hiding (take)
|
||||||
import Data.Ord.Unicode
|
import Data.Ord.Unicode
|
||||||
import Noun
|
import Ur.Noun
|
||||||
import Test.QuickCheck hiding ((.&.))
|
import Test.QuickCheck hiding ((.&.))
|
||||||
import Test.Tasty
|
import Test.Tasty
|
||||||
import Test.Tasty.QuickCheck
|
import Test.Tasty.QuickCheck
|
||||||
|
@ -5,7 +5,7 @@ import Data.Acquire
|
|||||||
import Data.Conduit
|
import Data.Conduit
|
||||||
import Data.Conduit.List hiding (take)
|
import Data.Conduit.List hiding (take)
|
||||||
import Data.Ord.Unicode
|
import Data.Ord.Unicode
|
||||||
import Noun
|
import Ur.Noun
|
||||||
import Test.QuickCheck hiding ((.&.))
|
import Test.QuickCheck hiding ((.&.))
|
||||||
import Test.Tasty
|
import Test.Tasty
|
||||||
import Test.Tasty.QuickCheck
|
import Test.Tasty.QuickCheck
|
||||||
|
@ -1,6 +1,6 @@
|
|||||||
module ClayTests (tests) where
|
module ClayTests (tests) where
|
||||||
|
|
||||||
import Noun.Conversions
|
import Ur.Noun.Conversions
|
||||||
import UrbitPrelude
|
import UrbitPrelude
|
||||||
|
|
||||||
import Test.QuickCheck hiding ((.&.))
|
import Test.QuickCheck hiding ((.&.))
|
||||||
|
@ -1,7 +1,7 @@
|
|||||||
module DawnTests (tests) where
|
module DawnTests (tests) where
|
||||||
|
|
||||||
import Arvo.Event
|
import Arvo.Event
|
||||||
import Noun.Conversions
|
import Ur.Noun.Conversions
|
||||||
import UrbitPrelude
|
import UrbitPrelude
|
||||||
|
|
||||||
import Test.Tasty
|
import Test.Tasty
|
||||||
|
@ -1,9 +1,9 @@
|
|||||||
module JamTests (tests) where
|
module JamTests (tests) where
|
||||||
|
|
||||||
import Arvo.Event
|
import Arvo.Event
|
||||||
import Noun.Conversions
|
import Ur.Noun.Conversions
|
||||||
import Noun.Cue
|
import Ur.Noun.Cue
|
||||||
import Noun.Jam
|
import Ur.Noun.Jam
|
||||||
import UrbitPrelude
|
import UrbitPrelude
|
||||||
|
|
||||||
import GHC.Natural (Natural(..))
|
import GHC.Natural (Natural(..))
|
||||||
|
@ -1,7 +1,7 @@
|
|||||||
module NounConversionTests (tests) where
|
module NounConversionTests (tests) where
|
||||||
|
|
||||||
import Arvo.Event
|
import Arvo.Event
|
||||||
import Noun.Conversions
|
import Ur.Noun.Conversions
|
||||||
import UrbitPrelude
|
import UrbitPrelude
|
||||||
|
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
|
@ -3,7 +3,7 @@ module SimpleNoun where
|
|||||||
import ClassyPrelude
|
import ClassyPrelude
|
||||||
import Numeric.Natural
|
import Numeric.Natural
|
||||||
|
|
||||||
import qualified Noun as N
|
import qualified Ur.Noun as N
|
||||||
|
|
||||||
type Atom = Natural
|
type Atom = Natural
|
||||||
|
|
||||||
|
@ -9,7 +9,6 @@ dependencies:
|
|||||||
- classy-prelude
|
- classy-prelude
|
||||||
- containers
|
- containers
|
||||||
- deriving-compat
|
- deriving-compat
|
||||||
- king
|
|
||||||
- lens
|
- lens
|
||||||
- megaparsec
|
- megaparsec
|
||||||
- mtl
|
- mtl
|
||||||
@ -20,6 +19,7 @@ dependencies:
|
|||||||
- transformers
|
- transformers
|
||||||
- transformers-compat
|
- transformers-compat
|
||||||
- unordered-containers
|
- unordered-containers
|
||||||
|
- king
|
||||||
|
|
||||||
default-extensions:
|
default-extensions:
|
||||||
- ApplicativeDo
|
- ApplicativeDo
|
||||||
|
@ -1,10 +1,11 @@
|
|||||||
resolver: lts-14.4
|
resolver: lts-14.4
|
||||||
|
|
||||||
packages:
|
packages:
|
||||||
- proto
|
|
||||||
- king
|
- king
|
||||||
- lmdb-static
|
- lmdb-static
|
||||||
|
- proto
|
||||||
- terminal-progress-bar
|
- terminal-progress-bar
|
||||||
|
- ur-azimuth
|
||||||
|
|
||||||
extra-deps:
|
extra-deps:
|
||||||
- flat-0.3.4@sha256:002a0e0ae656ea8cc02a772d0bcb6ea7dbd7f2e79070959cc748ad1e7138eb38
|
- flat-0.3.4@sha256:002a0e0ae656ea8cc02a772d0bcb6ea7dbd7f2e79070959cc748ad1e7138eb38
|
||||||
|
1
pkg/hs/ur-azimuth/.gitignore
vendored
Normal file
1
pkg/hs/ur-azimuth/.gitignore
vendored
Normal file
@ -0,0 +1 @@
|
|||||||
|
ur-azimuth.cabal
|
21
pkg/hs/ur-azimuth/LICENSE
Normal file
21
pkg/hs/ur-azimuth/LICENSE
Normal file
@ -0,0 +1,21 @@
|
|||||||
|
The MIT License (MIT)
|
||||||
|
|
||||||
|
Copyright (c) 2016 urbit
|
||||||
|
|
||||||
|
Permission is hereby granted, free of charge, to any person obtaining a copy
|
||||||
|
of this software and associated documentation files (the "Software"), to deal
|
||||||
|
in the Software without restriction, including without limitation the rights
|
||||||
|
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
|
||||||
|
copies of the Software, and to permit persons to whom the Software is
|
||||||
|
furnished to do so, subject to the following conditions:
|
||||||
|
|
||||||
|
The above copyright notice and this permission notice shall be included in all
|
||||||
|
copies or substantial portions of the Software.
|
||||||
|
|
||||||
|
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
|
||||||
|
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
|
||||||
|
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
|
||||||
|
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
|
||||||
|
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
|
||||||
|
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
|
||||||
|
SOFTWARE.
|
5
pkg/hs/ur-azimuth/Ur/Azimuth.hs
Normal file
5
pkg/hs/ur-azimuth/Ur/Azimuth.hs
Normal file
@ -0,0 +1,5 @@
|
|||||||
|
module Ur.Azimuth where
|
||||||
|
|
||||||
|
import Network.Ethereum.Contract.TH
|
||||||
|
|
||||||
|
[abiFrom|azimuth.json|]
|
55
pkg/hs/ur-azimuth/package.yaml
Normal file
55
pkg/hs/ur-azimuth/package.yaml
Normal file
@ -0,0 +1,55 @@
|
|||||||
|
name: ur-azimuth
|
||||||
|
version: 0.10.1
|
||||||
|
license: MIT
|
||||||
|
license-file: LICENSE
|
||||||
|
|
||||||
|
library:
|
||||||
|
source-dirs: .
|
||||||
|
|
||||||
|
dependencies:
|
||||||
|
- base
|
||||||
|
- web3
|
||||||
|
|
||||||
|
default-extensions:
|
||||||
|
- ApplicativeDo
|
||||||
|
- BangPatterns
|
||||||
|
- BlockArguments
|
||||||
|
- DataKinds
|
||||||
|
- DefaultSignatures
|
||||||
|
- DeriveAnyClass
|
||||||
|
- DeriveDataTypeable
|
||||||
|
- DeriveFoldable
|
||||||
|
- DeriveGeneric
|
||||||
|
- DeriveTraversable
|
||||||
|
- DerivingStrategies
|
||||||
|
- EmptyCase
|
||||||
|
- EmptyDataDecls
|
||||||
|
- FlexibleContexts
|
||||||
|
- FlexibleInstances
|
||||||
|
- FunctionalDependencies
|
||||||
|
- GADTs
|
||||||
|
- GeneralizedNewtypeDeriving
|
||||||
|
- LambdaCase
|
||||||
|
- MagicHash
|
||||||
|
- MultiParamTypeClasses
|
||||||
|
- NamedFieldPuns
|
||||||
|
- NoImplicitPrelude
|
||||||
|
- NumericUnderscores
|
||||||
|
- OverloadedStrings
|
||||||
|
- PackageImports
|
||||||
|
- PartialTypeSignatures
|
||||||
|
- PatternSynonyms
|
||||||
|
- QuasiQuotes
|
||||||
|
- Rank2Types
|
||||||
|
- RankNTypes
|
||||||
|
- RecordWildCards
|
||||||
|
- ScopedTypeVariables
|
||||||
|
- StandaloneDeriving
|
||||||
|
- TemplateHaskell
|
||||||
|
- TupleSections
|
||||||
|
- TypeApplications
|
||||||
|
- TypeFamilies
|
||||||
|
- TypeOperators
|
||||||
|
- UnboxedTuples
|
||||||
|
- UnicodeSyntax
|
||||||
|
- ViewPatterns
|
Loading…
Reference in New Issue
Block a user