Stop using Vervis.Import and NoImplicitPrelude, switch to plain regular imports
This commit is contained in:
parent
7686f3777e
commit
4b20ed23b6
162 changed files with 156 additions and 702 deletions
|
@ -45,9 +45,6 @@
|
||||||
|
|
||||||
module DevelMain where
|
module DevelMain where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
import Vervis.Application (getApplicationRepl, shutdownApp)
|
|
||||||
|
|
||||||
import Control.Exception (finally)
|
import Control.Exception (finally)
|
||||||
import Control.Monad ((>=>))
|
import Control.Monad ((>=>))
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
|
@ -56,6 +53,8 @@ import Foreign.Store
|
||||||
import Network.Wai.Handler.Warp
|
import Network.Wai.Handler.Warp
|
||||||
import GHC.Word
|
import GHC.Word
|
||||||
|
|
||||||
|
import Vervis.Application (getApplicationRepl, shutdownApp)
|
||||||
|
|
||||||
-- | Start or restart the server.
|
-- | Start or restart the server.
|
||||||
-- newStore is from foreign-store.
|
-- newStore is from foreign-store.
|
||||||
-- A Store holds onto some data across ghci reloads
|
-- A Store holds onto some data across ghci reloads
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- This file is part of Vervis.
|
{- This file is part of Vervis.
|
||||||
-
|
-
|
||||||
- Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
|
- Written in 2016, 2019 by fr33domlover <fr33domlover@riseup.net>.
|
||||||
-
|
-
|
||||||
- ♡ Copying is an act of love. Please copy, reuse and share.
|
- ♡ Copying is an act of love. Please copy, reuse and share.
|
||||||
-
|
-
|
||||||
|
@ -13,10 +13,7 @@
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE PackageImports #-}
|
import Vervis.Application (develMain)
|
||||||
|
|
||||||
import "vervis" Vervis.Application (develMain)
|
|
||||||
import Prelude (IO)
|
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = develMain
|
main = develMain
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- This file is part of Vervis.
|
{- This file is part of Vervis.
|
||||||
-
|
-
|
||||||
- Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
|
- Written in 2016, 2019 by fr33domlover <fr33domlover@riseup.net>.
|
||||||
-
|
-
|
||||||
- ♡ Copying is an act of love. Please copy, reuse and share.
|
- ♡ Copying is an act of love. Please copy, reuse and share.
|
||||||
-
|
-
|
||||||
|
@ -13,7 +13,6 @@
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
import Prelude (IO)
|
|
||||||
import Vervis.Application (appMain)
|
import Vervis.Application (appMain)
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
|
|
|
@ -21,8 +21,6 @@ module Control.Applicative.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
|
|
||||||
-- | Apply action between zero and @n@ times, inclusive, and list the results.
|
-- | Apply action between zero and @n@ times, inclusive, and list the results.
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Control.Concurrent.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Monad.IO.Class
|
import Control.Monad.IO.Class
|
||||||
|
|
|
@ -38,8 +38,6 @@ module Control.Concurrent.ResultShare
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
import Control.Concurrent.STM.TVar
|
import Control.Concurrent.STM.TVar
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
|
|
|
@ -18,8 +18,6 @@ module Control.Monad.Trans.Except.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Monad.Trans.Except
|
import Control.Monad.Trans.Except
|
||||||
|
|
||||||
fromMaybeE :: Monad m => Maybe a -> e -> ExceptT e m a
|
fromMaybeE :: Monad m => Maybe a -> e -> ExceptT e m a
|
||||||
|
|
|
@ -34,8 +34,6 @@ module Crypto.PubKey.Encoding
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Data.ASN1.BinaryEncoding
|
import Data.ASN1.BinaryEncoding
|
||||||
|
|
|
@ -24,8 +24,6 @@ module Crypto.PublicVerifKey
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Crypto.Error
|
import Crypto.Error
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Darcs.Local.Repository
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Darcs.Util.Hash
|
import Darcs.Util.Hash
|
||||||
import System.Directory (createDirectory)
|
import System.Directory (createDirectory)
|
||||||
import System.Exit (ExitCode (..))
|
import System.Exit (ExitCode (..))
|
||||||
|
|
|
@ -22,8 +22,6 @@ module Data.Aeson.Encode.Pretty.ToEncoding
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Aeson (ToJSON, Value, encode, decode)
|
import Data.Aeson (ToJSON, Value, encode, decode)
|
||||||
import Data.ByteString.Lazy (ByteString)
|
import Data.ByteString.Lazy (ByteString)
|
||||||
import Data.Maybe (fromJust)
|
import Data.Maybe (fromJust)
|
||||||
|
|
|
@ -25,8 +25,6 @@ module Data.Aeson.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
import Data.Aeson.Types (Parser)
|
import Data.Aeson.Types (Parser)
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Data.Attoparsec.ByteString.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Codec.Compression.Zlib.Internal
|
import Codec.Compression.Zlib.Internal
|
||||||
import Data.Attoparsec.ByteString
|
import Data.Attoparsec.ByteString
|
||||||
import System.IO
|
import System.IO
|
||||||
|
|
|
@ -26,8 +26,6 @@ module Data.Binary.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Monad.Logger
|
import Control.Monad.Logger
|
||||||
import Data.Binary.Get
|
import Data.Binary.Get
|
||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
|
|
|
@ -20,8 +20,6 @@ module Data.ByteString.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
|
|
||||||
import qualified Data.ByteString as B
|
import qualified Data.ByteString as B
|
||||||
|
|
|
@ -29,8 +29,6 @@ module Data.CaseInsensitive.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.CaseInsensitive
|
import Data.CaseInsensitive
|
||||||
import Data.Hashable (Hashable)
|
import Data.Hashable (Hashable)
|
||||||
import Data.String (IsString)
|
import Data.String (IsString)
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Data.Char.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Char
|
import Data.Char
|
||||||
|
|
||||||
isAsciiLetter :: Char -> Bool
|
isAsciiLetter :: Char -> Bool
|
||||||
|
|
|
@ -22,8 +22,6 @@ module Data.Either.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
import Control.Monad.IO.Class
|
import Control.Monad.IO.Class
|
||||||
|
|
|
@ -38,8 +38,6 @@ module Data.EventTime.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Text (Text, snoc)
|
import Data.Text (Text, snoc)
|
||||||
import Text.Blaze (ToMarkup (..))
|
import Text.Blaze (ToMarkup (..))
|
||||||
|
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Data.Functor.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
-- | Flipped 'fmap'.
|
-- | Flipped 'fmap'.
|
||||||
fwith :: Functor f => f a -> (a -> b) -> f b
|
fwith :: Functor f => f a -> (a -> b) -> f b
|
||||||
fwith = flip fmap
|
fwith = flip fmap
|
||||||
|
|
|
@ -27,8 +27,6 @@ module Data.Git.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Monad (when)
|
import Control.Monad (when)
|
||||||
import Data.Byteable (toBytes)
|
import Data.Byteable (toBytes)
|
||||||
import Data.Git
|
import Data.Git
|
||||||
|
|
|
@ -20,8 +20,6 @@ module Data.Graph.DirectedAcyclic.View.Tree
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Arrow ((***))
|
import Control.Arrow ((***))
|
||||||
import Data.Function (on)
|
import Data.Function (on)
|
||||||
import Data.Hashable (Hashable)
|
import Data.Hashable (Hashable)
|
||||||
|
|
|
@ -45,8 +45,6 @@ module Data.Graph.Inductive.Query.Cycle
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Graph.Inductive.Graph
|
import Data.Graph.Inductive.Graph
|
||||||
import Data.Maybe (isNothing)
|
import Data.Maybe (isNothing)
|
||||||
|
|
||||||
|
|
|
@ -39,8 +39,6 @@ module Data.Graph.Inductive.Query.Layer
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Graph.Inductive.Basic (gsel)
|
import Data.Graph.Inductive.Basic (gsel)
|
||||||
import Data.Graph.Inductive.Graph
|
import Data.Graph.Inductive.Graph
|
||||||
import Data.Graph.Inductive.Internal.Queue
|
import Data.Graph.Inductive.Internal.Queue
|
||||||
|
|
|
@ -26,8 +26,6 @@ module Data.Graph.Inductive.Query.Path
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Graph.Inductive.Graph
|
import Data.Graph.Inductive.Graph
|
||||||
import Data.Graph.Inductive.Internal.Queue
|
import Data.Graph.Inductive.Internal.Queue
|
||||||
|
|
||||||
|
|
|
@ -18,8 +18,6 @@ module Data.Graph.Inductive.Query.TransRed
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Foldable (foldl')
|
import Data.Foldable (foldl')
|
||||||
import Data.Graph.Inductive.Graph
|
import Data.Graph.Inductive.Graph
|
||||||
import Data.Graph.Inductive.Query.DFS (dfs)
|
import Data.Graph.Inductive.Query.DFS (dfs)
|
||||||
|
|
|
@ -18,8 +18,6 @@ module Data.Hourglass.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Hourglass
|
import Data.Hourglass
|
||||||
import Time.System
|
import Time.System
|
||||||
|
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Data.Int.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Int (Int64)
|
import Data.Int (Int64)
|
||||||
import Data.List.NonEmpty (NonEmpty (..), (<|))
|
import Data.List.NonEmpty (NonEmpty (..), (<|))
|
||||||
|
|
||||||
|
|
|
@ -21,8 +21,6 @@ module Data.KeyFile
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
import System.Directory
|
import System.Directory
|
||||||
|
|
|
@ -25,8 +25,6 @@ module Data.List.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Function (on)
|
import Data.Function (on)
|
||||||
import Data.List.NonEmpty (NonEmpty (..), (<|), toList)
|
import Data.List.NonEmpty (NonEmpty (..), (<|), toList)
|
||||||
|
|
||||||
|
|
|
@ -21,8 +21,6 @@ module Data.List.NonEmpty.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Function
|
import Data.Function
|
||||||
import Data.List.NonEmpty (NonEmpty (..))
|
import Data.List.NonEmpty (NonEmpty (..))
|
||||||
|
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Data.Maybe.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
partitionMaybes :: [(Maybe a, b)] -> ([(a, b)], [b])
|
partitionMaybes :: [(Maybe a, b)] -> ([(a, b)], [b])
|
||||||
partitionMaybes = foldr f ([], [])
|
partitionMaybes = foldr f ([], [])
|
||||||
where
|
where
|
||||||
|
|
|
@ -27,8 +27,6 @@ module Data.MediaType
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
|
|
||||||
data MediaType
|
data MediaType
|
||||||
|
|
|
@ -48,8 +48,6 @@ module Data.Paginate.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Default.Class
|
import Data.Default.Class
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Ratio
|
import Data.Ratio
|
||||||
|
|
|
@ -18,8 +18,6 @@ module Data.Time.Clock.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Time.Clock
|
import Data.Time.Clock
|
||||||
|
|
||||||
import Data.EventTime.Local
|
import Data.EventTime.Local
|
||||||
|
|
|
@ -18,8 +18,6 @@ module Data.Tree.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.List (sortOn)
|
import Data.List (sortOn)
|
||||||
import Data.Tree
|
import Data.Tree
|
||||||
|
|
||||||
|
|
|
@ -21,8 +21,6 @@ module Data.Tuple.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
fst3 :: (a, b, c) -> a
|
fst3 :: (a, b, c) -> a
|
||||||
fst3 (x, _, _) = x
|
fst3 (x, _, _) = x
|
||||||
|
|
||||||
|
|
|
@ -18,8 +18,6 @@ module Database.Esqueleto.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.CaseInsensitive (CI)
|
import Data.CaseInsensitive (CI)
|
||||||
import Database.Esqueleto
|
import Database.Esqueleto
|
||||||
|
|
||||||
|
|
|
@ -18,8 +18,6 @@ module Database.Persist.Class.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Data.Bifunctor
|
import Data.Bifunctor
|
||||||
import Data.CaseInsensitive (CI)
|
import Data.CaseInsensitive (CI)
|
||||||
|
|
|
@ -28,8 +28,6 @@ module Database.Persist.JSON
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
import Data.Aeson.Text
|
import Data.Aeson.Text
|
||||||
import Data.Text.Lazy.Encoding
|
import Data.Text.Lazy.Encoding
|
||||||
|
|
|
@ -22,8 +22,6 @@ module Database.Persist.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
|
|
|
@ -21,8 +21,6 @@ module Database.Persist.Local.Class.PersistEntityHierarchy
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Database.Persist
|
import Database.Persist
|
||||||
import Database.Persist.Graph.Class
|
import Database.Persist.Graph.Class
|
||||||
|
|
||||||
|
|
|
@ -18,8 +18,6 @@ module Database.Persist.Sql.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.CaseInsensitive (CI)
|
import Data.CaseInsensitive (CI)
|
||||||
import Database.Persist.Sql
|
import Database.Persist.Sql
|
||||||
|
|
||||||
|
|
|
@ -21,8 +21,6 @@ module Diagrams.IntransitiveDAG
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Arrow ((&&&))
|
import Control.Arrow ((&&&))
|
||||||
import Data.Graph.Inductive.Graph
|
import Data.Graph.Inductive.Graph
|
||||||
import Data.Graph.Inductive.Query.Layer (rlayerWith)
|
import Data.Graph.Inductive.Query.Layer (rlayerWith)
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Formatting.CaseInsensitive
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.CaseInsensitive
|
import Data.CaseInsensitive
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Data.Text.Lazy.Builder (fromText)
|
import Data.Text.Lazy.Builder (fromText)
|
||||||
|
|
|
@ -20,8 +20,6 @@ module GitPackProto
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Applicative ((<|>))
|
import Control.Applicative ((<|>))
|
||||||
import Data.Attoparsec.Text
|
import Data.Attoparsec.Text
|
||||||
import Data.ByteString (ByteString, unsnoc)
|
import Data.ByteString (ByteString, unsnoc)
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Language.Haskell.TH.Quote.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Language.Haskell.TH.Quote (QuasiQuoter (..))
|
import Language.Haskell.TH.Quote (QuasiQuoter (..))
|
||||||
import Language.Haskell.TH.Syntax (Q, Exp, Dec)
|
import Language.Haskell.TH.Syntax (Q, Exp, Dec)
|
||||||
|
|
||||||
|
|
|
@ -38,8 +38,6 @@ module Network.FedURI
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Monad ((<=<))
|
import Control.Monad ((<=<))
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
import Data.Bifunctor (bimap, first)
|
import Data.Bifunctor (bimap, first)
|
||||||
|
|
|
@ -38,8 +38,6 @@ module Network.HTTP.Client.Conduit.ActivityPub
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Exception (throwIO, bracket)
|
import Control.Exception (throwIO, bracket)
|
||||||
import Control.Monad.IO.Unlift (MonadIO, liftIO, MonadUnliftIO, withRunInIO)
|
import Control.Monad.IO.Unlift (MonadIO, liftIO, MonadUnliftIO, withRunInIO)
|
||||||
import Data.Aeson (FromJSON, Result (..), fromJSON, json')
|
import Data.Aeson (FromJSON, Result (..), fromJSON, json')
|
||||||
|
|
|
@ -37,8 +37,6 @@ module Network.HTTP.Digest
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Crypto.Hash
|
import Crypto.Hash
|
||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
import Network.HTTP.Types.Header
|
import Network.HTTP.Types.Header
|
||||||
|
|
|
@ -18,8 +18,6 @@ module Network.SSH.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.ByteString.Char8 (ByteString, pack)
|
import Data.ByteString.Char8 (ByteString, pack)
|
||||||
import Network.SSH
|
import Network.SSH
|
||||||
|
|
||||||
|
|
|
@ -18,8 +18,6 @@ module Text.Blaze.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.CaseInsensitive (CI)
|
import Data.CaseInsensitive (CI)
|
||||||
import Text.Blaze
|
import Text.Blaze
|
||||||
|
|
||||||
|
|
|
@ -36,8 +36,6 @@ module Text.Display
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
|
|
||||||
class Display a where
|
class Display a where
|
||||||
|
|
|
@ -18,8 +18,6 @@ module Text.Email.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Text.Email.Validate
|
import Text.Email.Validate
|
||||||
|
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
|
|
|
@ -24,8 +24,6 @@ module Text.FilePath.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Arrow ((***))
|
import Control.Arrow ((***))
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
|
|
|
@ -31,8 +31,6 @@ module Text.Jasmine.Local
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import qualified Data.ByteString.Lazy as BL (ByteString, empty)
|
import qualified Data.ByteString.Lazy as BL (ByteString, empty)
|
||||||
|
|
||||||
discardm :: BL.ByteString -> Either String BL.ByteString
|
discardm :: BL.ByteString -> Either String BL.ByteString
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Vervis.API
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Control.Concurrent.MVar
|
import Control.Concurrent.MVar
|
||||||
import Control.Concurrent.STM.TVar
|
import Control.Concurrent.STM.TVar
|
||||||
|
|
|
@ -59,8 +59,6 @@ module Vervis.Access
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Applicative ((<|>))
|
import Control.Applicative ((<|>))
|
||||||
import Control.Monad.IO.Class
|
import Control.Monad.IO.Class
|
||||||
import Control.Monad.Trans.Maybe
|
import Control.Monad.Trans.Maybe
|
||||||
|
|
|
@ -33,8 +33,6 @@ module Vervis.ActivityPub
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Exception hiding (try)
|
import Control.Exception hiding (try)
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Monad.IO.Class
|
import Control.Monad.IO.Class
|
||||||
|
|
|
@ -1,224 +0,0 @@
|
||||||
{- This file is part of Vervis.
|
|
||||||
-
|
|
||||||
- Written in 2018 by fr33domlover <fr33domlover@riseup.net>.
|
|
||||||
-
|
|
||||||
- ♡ Copying is an act of love. Please copy, reuse and share.
|
|
||||||
-
|
|
||||||
- The author(s) have dedicated all copyright and related and neighboring
|
|
||||||
- rights to this software to the public domain worldwide. This software is
|
|
||||||
- distributed without any warranty.
|
|
||||||
-
|
|
||||||
- You should have received a copy of the CC0 Public Domain Dedication along
|
|
||||||
- with this software. If not, see
|
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
|
||||||
-}
|
|
||||||
|
|
||||||
module Vervis.ActivityStreams
|
|
||||||
( Actor (..)
|
|
||||||
, ActivityStreams2 (..)
|
|
||||||
, provideAS2
|
|
||||||
, makeActor
|
|
||||||
)
|
|
||||||
where
|
|
||||||
|
|
||||||
import Control.Monad.Trans.Writer
|
|
||||||
import Data.Aeson (pairs)
|
|
||||||
import Data.Monoid
|
|
||||||
|
|
||||||
import Vervis.Import
|
|
||||||
import Vervis.Model.Ident
|
|
||||||
|
|
||||||
-- AS2 is divided into core and extensions-for-common-social-web-use-cases, I'm
|
|
||||||
-- starting with the core, looking at the AS2 vocab spec
|
|
||||||
|
|
||||||
{-
|
|
||||||
data Object = Object
|
|
||||||
{ objectAttachment ::
|
|
||||||
, objectAttributedTo ::
|
|
||||||
, objectAudience ::
|
|
||||||
, objectContent ::
|
|
||||||
, objectContext ::
|
|
||||||
, objectName ::
|
|
||||||
, objectEndTime ::
|
|
||||||
, objectGenerator ::
|
|
||||||
, objectIcon ::
|
|
||||||
, objectImage ::
|
|
||||||
, objectInReplyTo ::
|
|
||||||
, objectLocation ::
|
|
||||||
, objectPreview ::
|
|
||||||
, objectPublished ::
|
|
||||||
, objectReplies ::
|
|
||||||
, objectStartTime ::
|
|
||||||
, objectSummary ::
|
|
||||||
, objectTag ::
|
|
||||||
, objectUpdated ::
|
|
||||||
, objectUrl ::
|
|
||||||
, objectTo ::
|
|
||||||
, objectBto ::
|
|
||||||
, objectCc ::
|
|
||||||
, objectBcc ::
|
|
||||||
, objectMediaType ::
|
|
||||||
, objectDuration ::
|
|
||||||
}
|
|
||||||
|
|
||||||
data Link = Link
|
|
||||||
{ linkHref ::
|
|
||||||
, linkRel ::
|
|
||||||
, linkMediaType ::
|
|
||||||
, linkName ::
|
|
||||||
, linkHrefLang ::
|
|
||||||
, linkHeight ::
|
|
||||||
, linkWidth ::
|
|
||||||
, linkPreview ::
|
|
||||||
}
|
|
||||||
|
|
||||||
data Activity = Activity
|
|
||||||
{ activityAsObject :: Object
|
|
||||||
, activityActor ::
|
|
||||||
, activityObject ::
|
|
||||||
, activityTarget ::
|
|
||||||
, activityResult ::
|
|
||||||
, activityOrigin ::
|
|
||||||
, activityInstrument ::
|
|
||||||
}
|
|
||||||
|
|
||||||
data IntransitiveActivity = IntransitiveActivity
|
|
||||||
{ iactivityAsObject :: Object
|
|
||||||
, iactivityActor ::
|
|
||||||
, iactivityTarget ::
|
|
||||||
, iactivityResult ::
|
|
||||||
, iactivityOrigin ::
|
|
||||||
, iactivityInstrument ::
|
|
||||||
}
|
|
||||||
|
|
||||||
data Collection = Collection
|
|
||||||
{ collectionAsObject :: Object
|
|
||||||
, collectionTotalItems ::
|
|
||||||
, collectionCurrent ::
|
|
||||||
, collectionFirst ::
|
|
||||||
, collectionLast ::
|
|
||||||
, collectionItems ::
|
|
||||||
}
|
|
||||||
|
|
||||||
data OrderedCollection = OrderedCollection
|
|
||||||
{ ocollectionAsCollection :: Collection
|
|
||||||
}
|
|
||||||
|
|
||||||
data CollectionPage = CollectionPage
|
|
||||||
{ collectionPageAsCollection :: Collection
|
|
||||||
, collectionPagePartOf ::
|
|
||||||
, collectionPageNext ::
|
|
||||||
, collectionPagePrev ::
|
|
||||||
}
|
|
||||||
|
|
||||||
data OrderedCollectionPage = OrderedCollectionPage
|
|
||||||
{ orderedCollectionPageAsCollectionPage :: CollectionPage
|
|
||||||
, orederdCollectionPageStartIndex ::
|
|
||||||
}
|
|
||||||
|
|
||||||
-- Now come the extended types
|
|
||||||
|
|
||||||
-- Activity types - I'm skipping them for now
|
|
||||||
|
|
||||||
-- Actor types
|
|
||||||
|
|
||||||
data Application = Application
|
|
||||||
{ applicationAsObject :: Object
|
|
||||||
}
|
|
||||||
|
|
||||||
data Group = Group
|
|
||||||
{ groupAsObject :: Object
|
|
||||||
}
|
|
||||||
|
|
||||||
data Organization = Organization
|
|
||||||
{ organizationAsObject :: Object
|
|
||||||
}
|
|
||||||
|
|
||||||
data Person = Person
|
|
||||||
{ personAsObject :: Object
|
|
||||||
}
|
|
||||||
|
|
||||||
data Service = Service
|
|
||||||
{ serviceAsObject :: Object
|
|
||||||
}
|
|
||||||
-}
|
|
||||||
|
|
||||||
-- Actor objects in AP
|
|
||||||
|
|
||||||
data Actor = Actor
|
|
||||||
{ -- Requirements
|
|
||||||
actorId :: Text
|
|
||||||
, actorType :: Text
|
|
||||||
-- Must
|
|
||||||
, actorInbox :: Text
|
|
||||||
, actorOutbox :: Text
|
|
||||||
-- Should
|
|
||||||
--, actorFollowing
|
|
||||||
--, actorFollowers
|
|
||||||
-- May
|
|
||||||
--, actorLiked
|
|
||||||
--, actorStreams
|
|
||||||
--, actorPreferredUsername
|
|
||||||
--, actorEndpoints
|
|
||||||
}
|
|
||||||
|
|
||||||
fields a =
|
|
||||||
[ "@context" .= ("https://www.w3.org/ns/activitystreams" :: Text)
|
|
||||||
, "id" .= actorId a
|
|
||||||
, "type" .= actorType a
|
|
||||||
, "inbox" .= actorInbox a
|
|
||||||
, "outbox" .= actorOutbox a
|
|
||||||
]
|
|
||||||
|
|
||||||
instance ToJSON Actor where
|
|
||||||
toJSON = object . fields
|
|
||||||
toEncoding = pairs . mconcat . fields
|
|
||||||
|
|
||||||
-- NEXT:
|
|
||||||
--
|
|
||||||
-- * Figure out how to detect the client wanting AS2 / AP
|
|
||||||
-- * Send minimal simple actor per user
|
|
||||||
|
|
||||||
typeActivityStreams2 :: ContentType
|
|
||||||
typeActivityStreams2 = "application/activity+json"
|
|
||||||
|
|
||||||
typeActivityStreams2LD :: ContentType
|
|
||||||
typeActivityStreams2LD =
|
|
||||||
"application/ld+json; profile=\"https://www.w3.org/ns/activitystreams\""
|
|
||||||
|
|
||||||
data ActivityStreams2 = ActivityPubActor Actor
|
|
||||||
|
|
||||||
instance ToContent ActivityStreams2 where
|
|
||||||
toContent (ActivityPubActor a) = toContent $ toEncoding a
|
|
||||||
|
|
||||||
{-
|
|
||||||
instance ToTypedContent ActivityStreams2 where
|
|
||||||
toTypedContent = TypedContent typeActivityStreams2 . toContent
|
|
||||||
|
|
||||||
instance HasContentType ActivityStreams2 where
|
|
||||||
getContentType _ = typeActivityStreams2
|
|
||||||
|
|
||||||
data ActivityStreams2LD = ActivityStreams2LD ActivityStreams2
|
|
||||||
|
|
||||||
instance ToContent ActivityStreams2LD where
|
|
||||||
toContent (ActivityStreams2LD a) = toContent a
|
|
||||||
|
|
||||||
instance ToTypedContent ActivityStreams2LD where
|
|
||||||
toTypedContent = TypedContent typeActivityStreams2LD . toContent
|
|
||||||
|
|
||||||
instance HasContentType ActivityStreams2LD where
|
|
||||||
getContentType _ = typeActivityStreams2LD
|
|
||||||
-}
|
|
||||||
|
|
||||||
provideAS2 :: Monad m => ActivityStreams2 -> Writer (Endo [ProvidedRep m]) ()
|
|
||||||
provideAS2 as2 = do
|
|
||||||
provideRepType typeActivityStreams2 $ return as2
|
|
||||||
provideRepType typeActivityStreams2LD $ return as2
|
|
||||||
|
|
||||||
makeActor ur shr =
|
|
||||||
Actor
|
|
||||||
{ actorId = ur $ SharerR shr
|
|
||||||
, actorType = "Person"
|
|
||||||
, actorInbox = ur $ SharerR shr
|
|
||||||
, actorOutbox = ur $ error "We don't have outboxes yet"
|
|
||||||
}
|
|
|
@ -23,8 +23,6 @@ module Vervis.ActorKey
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Concurrent (threadDelay)
|
import Control.Concurrent (threadDelay)
|
||||||
import Control.Concurrent.STM (TVar, modifyTVar')
|
import Control.Concurrent.STM (TVar, modifyTVar')
|
||||||
import Control.Monad (forever)
|
import Control.Monad (forever)
|
||||||
|
|
|
@ -30,16 +30,19 @@ module Vervis.Application
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
|
import Control.Concurrent.Chan
|
||||||
|
import Control.Concurrent.STM.TVar
|
||||||
|
import Control.Monad
|
||||||
import Control.Monad.Logger (liftLoc, runLoggingT, logInfo, logError)
|
import Control.Monad.Logger (liftLoc, runLoggingT, logInfo, logError)
|
||||||
import Database.Persist.Postgresql (createPostgresqlPool, pgConnStr,
|
import Control.Monad.Trans.Reader
|
||||||
pgPoolSize, runSqlPool)
|
import Data.Default.Class
|
||||||
|
import Database.Persist.Postgresql
|
||||||
import Graphics.SVGFonts.Fonts (lin2)
|
import Graphics.SVGFonts.Fonts (lin2)
|
||||||
import Graphics.SVGFonts.ReadFont (loadFont)
|
import Graphics.SVGFonts.ReadFont (loadFont)
|
||||||
import Vervis.Import
|
|
||||||
import Language.Haskell.TH.Syntax (qLocation)
|
import Language.Haskell.TH.Syntax (qLocation)
|
||||||
import Network.HTTP.Client (newManager)
|
import Network.HTTP.Client (newManager)
|
||||||
import Network.HTTP.Client.TLS (tlsManagerSettings)
|
import Network.HTTP.Client.TLS (tlsManagerSettings)
|
||||||
import Network.Wai (Middleware)
|
import Network.Wai
|
||||||
import Network.Wai.Handler.Warp (Settings, defaultSettings,
|
import Network.Wai.Handler.Warp (Settings, defaultSettings,
|
||||||
defaultShouldDisplayException,
|
defaultShouldDisplayException,
|
||||||
runSettings, setHost,
|
runSettings, setHost,
|
||||||
|
@ -48,15 +51,20 @@ import Network.Wai.Middleware.RequestLogger (Destination (Logger),
|
||||||
IPAddrSource (..),
|
IPAddrSource (..),
|
||||||
OutputFormat (..), destination,
|
OutputFormat (..), destination,
|
||||||
mkRequestLogger, outputFormat)
|
mkRequestLogger, outputFormat)
|
||||||
import System.Log.FastLogger (defaultBufSize, newStdoutLoggerSet,
|
import System.Log.FastLogger
|
||||||
toLogStr)
|
import Yesod.Auth
|
||||||
import Yesod.Default.Main (LogFunc)
|
import Yesod.Core
|
||||||
import Yesod.Mail.Send (runMailer)
|
import Yesod.Core.Dispatch
|
||||||
|
import Yesod.Core.Types hiding (Logger)
|
||||||
|
import Yesod.Default.Config2
|
||||||
|
import Yesod.Persist.Core
|
||||||
|
import Yesod.Static
|
||||||
|
|
||||||
import qualified Data.Text as T (unpack)
|
import qualified Data.Text as T (unpack)
|
||||||
import qualified Data.HashMap.Strict as M (empty)
|
import qualified Data.HashMap.Strict as M (empty)
|
||||||
|
|
||||||
import Database.Persist.Schema.PostgreSQL (schemaBackend)
|
import Database.Persist.Schema.PostgreSQL (schemaBackend)
|
||||||
|
import Yesod.Mail.Send (runMailer)
|
||||||
|
|
||||||
import Control.Concurrent.ResultShare
|
import Control.Concurrent.ResultShare
|
||||||
import Data.KeyFile
|
import Data.KeyFile
|
||||||
|
@ -67,6 +75,7 @@ import Web.Hashids.Local
|
||||||
|
|
||||||
import Vervis.ActorKey (generateActorKey, actorKeyRotator)
|
import Vervis.ActorKey (generateActorKey, actorKeyRotator)
|
||||||
import Vervis.Federation
|
import Vervis.Federation
|
||||||
|
import Vervis.Foundation
|
||||||
import Vervis.KeyFile (isInitialSetup)
|
import Vervis.KeyFile (isInitialSetup)
|
||||||
import Vervis.RemoteActorStore
|
import Vervis.RemoteActorStore
|
||||||
|
|
||||||
|
@ -88,6 +97,7 @@ import Vervis.Handler.Wiki
|
||||||
import Vervis.Handler.Workflow
|
import Vervis.Handler.Workflow
|
||||||
|
|
||||||
import Vervis.Migration (migrateDB)
|
import Vervis.Migration (migrateDB)
|
||||||
|
import Vervis.Settings
|
||||||
import Vervis.Ssh (runSsh)
|
import Vervis.Ssh (runSsh)
|
||||||
|
|
||||||
-- This line actually creates our YesodDispatch instance. It is the second half
|
-- This line actually creates our YesodDispatch instance. It is the second half
|
||||||
|
|
|
@ -18,8 +18,6 @@ module Vervis.Avatar
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Monad.IO.Class (liftIO)
|
import Control.Monad.IO.Class (liftIO)
|
||||||
import Data.Default.Class (def)
|
import Data.Default.Class (def)
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
|
|
|
@ -24,8 +24,6 @@ module Vervis.BinaryBody
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Monad.IO.Class (liftIO)
|
import Control.Monad.IO.Class (liftIO)
|
||||||
import Control.Monad.Logger (MonadLogger)
|
import Control.Monad.Logger (MonadLogger)
|
||||||
import Data.Binary.Get (Get)
|
import Data.Binary.Get (Get)
|
||||||
|
|
|
@ -18,8 +18,6 @@ module Vervis.ChangeFeed
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Monoid ((<>))
|
import Data.Monoid ((<>))
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Yesod.Core (Route)
|
import Yesod.Core (Route)
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Vervis.Changes
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Data.Time.Clock (UTCTime)
|
import Data.Time.Clock (UTCTime)
|
||||||
|
|
||||||
|
|
|
@ -34,8 +34,6 @@ module Vervis.Colour
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Colour.SRGB (Colour, sRGB24)
|
import Data.Colour.SRGB (Colour, sRGB24)
|
||||||
import Data.Word (Word8)
|
import Data.Word (Word8)
|
||||||
|
|
||||||
|
|
|
@ -20,8 +20,6 @@ module Vervis.Content
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
import Data.Monoid ((<>))
|
import Data.Monoid ((<>))
|
||||||
import Network.Git.Put (serializeService)
|
import Network.Git.Put (serializeService)
|
||||||
|
|
|
@ -20,8 +20,6 @@ module Vervis.Discussion
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Arrow (second)
|
import Control.Arrow (second)
|
||||||
import Data.Graph.Inductive.Graph (mkGraph, lab')
|
import Data.Graph.Inductive.Graph (mkGraph, lab')
|
||||||
import Data.Graph.Inductive.PatriciaTree (Gr)
|
import Data.Graph.Inductive.PatriciaTree (Gr)
|
||||||
|
|
|
@ -23,8 +23,6 @@ module Vervis.Federation
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Control.Concurrent.MVar
|
import Control.Concurrent.MVar
|
||||||
import Control.Concurrent.STM.TVar
|
import Control.Concurrent.STM.TVar
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Vervis.Federation.Discussion
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
--import Control.Applicative
|
--import Control.Applicative
|
||||||
--import Control.Concurrent.MVar
|
--import Control.Concurrent.MVar
|
||||||
--import Control.Concurrent.STM.TVar
|
--import Control.Concurrent.STM.TVar
|
||||||
|
|
|
@ -20,8 +20,6 @@ module Vervis.Field.Key
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
import Data.ByteString.Base64 (decode)
|
import Data.ByteString.Base64 (decode)
|
||||||
import Data.Char (isDigit)
|
import Data.Char (isDigit)
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- This file is part of Vervis.
|
{- This file is part of Vervis.
|
||||||
-
|
-
|
||||||
- Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
|
- Written in 2016, 2019 by fr33domlover <fr33domlover@riseup.net>.
|
||||||
-
|
-
|
||||||
- ♡ Copying is an act of love. Please copy, reuse and share.
|
- ♡ Copying is an act of love. Please copy, reuse and share.
|
||||||
-
|
-
|
||||||
|
@ -18,13 +18,20 @@ module Vervis.Field.Person
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Vervis.Import hiding ((==.))
|
|
||||||
|
|
||||||
import Data.Char (isDigit)
|
import Data.Char (isDigit)
|
||||||
|
import Data.Text (Text)
|
||||||
import Database.Esqueleto
|
import Database.Esqueleto
|
||||||
|
import Yesod.Form.Fields
|
||||||
|
import Yesod.Form.Functions
|
||||||
|
import Yesod.Form.Types
|
||||||
|
|
||||||
|
import qualified Data.Text as T
|
||||||
|
|
||||||
import Data.Char.Local (isAsciiLetter)
|
import Data.Char.Local (isAsciiLetter)
|
||||||
|
|
||||||
|
import Vervis.Foundation
|
||||||
import Vervis.Model.Ident (text2shr)
|
import Vervis.Model.Ident (text2shr)
|
||||||
|
import Vervis.Settings
|
||||||
|
|
||||||
checkPassLength :: Field Handler Text -> Field Handler Text
|
checkPassLength :: Field Handler Text -> Field Handler Text
|
||||||
checkPassLength =
|
checkPassLength =
|
||||||
|
@ -36,7 +43,7 @@ checkPassLength =
|
||||||
\alternative, such as a client TLS certificate, that can work \
|
\alternative, such as a client TLS certificate, that can work \
|
||||||
\somewhat like SSH and GPG keys."
|
\somewhat like SSH and GPG keys."
|
||||||
minlen = 8
|
minlen = 8
|
||||||
in checkBool ((>= minlen) . length) msg
|
in checkBool ((>= minlen) . T.length) msg
|
||||||
|
|
||||||
passConfirmField :: Field Handler Text
|
passConfirmField :: Field Handler Text
|
||||||
passConfirmField = Field
|
passConfirmField = Field
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- This file is part of Vervis.
|
{- This file is part of Vervis.
|
||||||
-
|
-
|
||||||
- Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
|
- Written in 2016, 2019 by fr33domlover <fr33domlover@riseup.net>.
|
||||||
-
|
-
|
||||||
- ♡ Copying is an act of love. Please copy, reuse and share.
|
- ♡ Copying is an act of love. Please copy, reuse and share.
|
||||||
-
|
-
|
||||||
|
@ -18,20 +18,26 @@ module Vervis.Field.Project
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Vervis.Import hiding ((==.))
|
|
||||||
|
|
||||||
import Data.Char (isDigit)
|
import Data.Char (isDigit)
|
||||||
import Data.Char.Local (isAsciiLetter)
|
import Data.Char.Local (isAsciiLetter)
|
||||||
import Data.Text (split)
|
import Data.Text (Text)
|
||||||
import Database.Esqueleto
|
import Database.Esqueleto
|
||||||
|
import Yesod.Form.Fields
|
||||||
|
import Yesod.Form.Functions
|
||||||
|
import Yesod.Form.Types
|
||||||
|
import Yesod.Persist.Core
|
||||||
|
|
||||||
|
import qualified Data.Text as T
|
||||||
|
|
||||||
|
import Vervis.Foundation
|
||||||
|
import Vervis.Model
|
||||||
import Vervis.Model.Ident (PrjIdent, prj2text, text2prj)
|
import Vervis.Model.Ident (PrjIdent, prj2text, text2prj)
|
||||||
|
|
||||||
checkTemplate :: Field Handler Text -> Field Handler Text
|
checkTemplate :: Field Handler Text -> Field Handler Text
|
||||||
checkTemplate =
|
checkTemplate =
|
||||||
let charOk c = isAsciiLetter c || isDigit c
|
let charOk c = isAsciiLetter c || isDigit c
|
||||||
wordOk w = (not . null) w && all charOk w
|
wordOk w = (not . T.null) w && T.all charOk w
|
||||||
identOk t = (not . null) t && all wordOk (split (== '-') t)
|
identOk t = (not . T.null) t && all wordOk (T.split (== '-') t)
|
||||||
msg :: Text
|
msg :: Text
|
||||||
msg = "The project identifier must be a sequence of one or more words \
|
msg = "The project identifier must be a sequence of one or more words \
|
||||||
\separated by hyphens (‘-’), and each such word may contain \
|
\separated by hyphens (‘-’), and each such word may contain \
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- This file is part of Vervis.
|
{- This file is part of Vervis.
|
||||||
-
|
-
|
||||||
- Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
|
- Written in 2016, 2019 by fr33domlover <fr33domlover@riseup.net>.
|
||||||
-
|
-
|
||||||
- ♡ Copying is an act of love. Please copy, reuse and share.
|
- ♡ Copying is an act of love. Please copy, reuse and share.
|
||||||
-
|
-
|
||||||
|
@ -22,22 +22,28 @@ module Vervis.Field.Repo
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Vervis.Import hiding ((==.), on, isNothing)
|
import Data.Bifunctor
|
||||||
|
|
||||||
import Data.Char (isDigit)
|
import Data.Char (isDigit)
|
||||||
import Data.Char.Local (isAsciiLetter)
|
import Data.Char.Local (isAsciiLetter)
|
||||||
import Data.Text (split)
|
import Data.Text (Text)
|
||||||
import Database.Esqueleto
|
import Database.Esqueleto
|
||||||
|
import Yesod.Form.Fields
|
||||||
|
import Yesod.Form.Functions
|
||||||
|
import Yesod.Form.Types
|
||||||
|
import Yesod.Persist.Core
|
||||||
|
|
||||||
|
import qualified Data.Text as T
|
||||||
import qualified Database.Persist as P ((==.))
|
import qualified Database.Persist as P ((==.))
|
||||||
|
|
||||||
|
import Vervis.Foundation
|
||||||
|
import Vervis.Model
|
||||||
import Vervis.Model.Ident (shr2text, text2rp, prj2text)
|
import Vervis.Model.Ident (shr2text, text2rp, prj2text)
|
||||||
|
|
||||||
checkIdentTemplate :: Field Handler Text -> Field Handler Text
|
checkIdentTemplate :: Field Handler Text -> Field Handler Text
|
||||||
checkIdentTemplate =
|
checkIdentTemplate =
|
||||||
let charOk c = isAsciiLetter c || isDigit c
|
let charOk c = isAsciiLetter c || isDigit c
|
||||||
wordOk w = (not . null) w && all charOk w
|
wordOk w = (not . T.null) w && T.all charOk w
|
||||||
identOk t = (not . null) t && all wordOk (split (== '-') t)
|
identOk t = (not . T.null) t && all wordOk (T.split (== '-') t)
|
||||||
msg :: Text
|
msg :: Text
|
||||||
msg = "The repo identifier must be a sequence of one or more words \
|
msg = "The repo identifier must be a sequence of one or more words \
|
||||||
\separated by hyphens (‘-’), and each such word may contain \
|
\separated by hyphens (‘-’), and each such word may contain \
|
||||||
|
@ -73,7 +79,7 @@ selectCollabFromAll rid = selectField $ do
|
||||||
collab ?. RepoCollabPerson ==. just (person ^. PersonId)
|
collab ?. RepoCollabPerson ==. just (person ^. PersonId)
|
||||||
where_ $ isNothing $ collab ?. RepoCollabId
|
where_ $ isNothing $ collab ?. RepoCollabId
|
||||||
return (sharer ^. SharerIdent, person ^. PersonId)
|
return (sharer ^. SharerIdent, person ^. PersonId)
|
||||||
optionsPairs $ map (shr2text . unValue *** unValue) l
|
optionsPairs $ map (bimap (shr2text . unValue) unValue) l
|
||||||
|
|
||||||
-- | Select a new collaborator for a repo, from the list of collaborators of
|
-- | Select a new collaborator for a repo, from the list of collaborators of
|
||||||
-- the project it belongs to. It can be any collaborator of the project, who
|
-- the project it belongs to. It can be any collaborator of the project, who
|
||||||
|
@ -95,7 +101,7 @@ selectCollabFromProject jid rid = selectField $ do
|
||||||
pcollab ^. ProjectCollabPerson ==. person ^. PersonId
|
pcollab ^. ProjectCollabPerson ==. person ^. PersonId
|
||||||
where_ $ isNothing $ rcollab ?. RepoCollabId
|
where_ $ isNothing $ rcollab ?. RepoCollabId
|
||||||
return (sharer ^. SharerIdent, person ^. PersonId)
|
return (sharer ^. SharerIdent, person ^. PersonId)
|
||||||
optionsPairs $ map (shr2text . unValue *** unValue) l
|
optionsPairs $ map (bimap (shr2text . unValue) unValue) l
|
||||||
|
|
||||||
-- | Select a project for a new repository to belong to. It can be any project
|
-- | Select a project for a new repository to belong to. It can be any project
|
||||||
-- of the same sharer who's sharing the repo.
|
-- of the same sharer who's sharing the repo.
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Vervis.Field.Role
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Database.Esqueleto
|
import Database.Esqueleto
|
||||||
import Yesod.Form.Fields (textField, selectField, optionsEnum)
|
import Yesod.Form.Fields (textField, selectField, optionsEnum)
|
||||||
|
|
|
@ -23,8 +23,6 @@ module Vervis.Field.Sharer
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Monad (void)
|
import Control.Monad (void)
|
||||||
import Control.Monad.Trans.Maybe
|
import Control.Monad.Trans.Maybe
|
||||||
import Data.Char (isDigit)
|
import Data.Char (isDigit)
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Vervis.Field.Ticket
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Arrow ((***))
|
import Control.Arrow ((***))
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Database.Esqueleto hiding ((%))
|
import Database.Esqueleto hiding ((%))
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- This file is part of Vervis.
|
{- This file is part of Vervis.
|
||||||
-
|
-
|
||||||
- Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
|
- Written in 2016, 2019 by fr33domlover <fr33domlover@riseup.net>.
|
||||||
-
|
-
|
||||||
- ♡ Copying is an act of love. Please copy, reuse and share.
|
- ♡ Copying is an act of love. Please copy, reuse and share.
|
||||||
-
|
-
|
||||||
|
@ -21,20 +21,26 @@ module Vervis.Field.Workflow
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Vervis.Import hiding ((==.))
|
|
||||||
|
|
||||||
import Data.Char (isDigit, isAlphaNum)
|
import Data.Char (isDigit, isAlphaNum)
|
||||||
import Data.Char.Local (isAsciiLetter)
|
import Data.Char.Local (isAsciiLetter)
|
||||||
import Data.Text (split)
|
import Data.Text (Text)
|
||||||
import Database.Esqueleto
|
import Database.Esqueleto
|
||||||
|
import Yesod.Form.Fields
|
||||||
|
import Yesod.Form.Functions
|
||||||
|
import Yesod.Form.Types
|
||||||
|
import Yesod.Persist.Core
|
||||||
|
|
||||||
|
import qualified Data.Text as T
|
||||||
|
|
||||||
|
import Vervis.Foundation
|
||||||
|
import Vervis.Model
|
||||||
import Vervis.Model.Ident
|
import Vervis.Model.Ident
|
||||||
|
|
||||||
checkTemplate :: Field Handler Text -> Field Handler Text
|
checkTemplate :: Field Handler Text -> Field Handler Text
|
||||||
checkTemplate =
|
checkTemplate =
|
||||||
let charOk c = isAsciiLetter c || isDigit c
|
let charOk c = isAsciiLetter c || isDigit c
|
||||||
wordOk w = (not . null) w && all charOk w
|
wordOk w = (not . T.null) w && T.all charOk w
|
||||||
identOk t = (not . null) t && all wordOk (split (== '-') t)
|
identOk t = (not . T.null) t && all wordOk (T.split (== '-') t)
|
||||||
msg :: Text
|
msg :: Text
|
||||||
msg = "The identifier must be a sequence of one or more words \
|
msg = "The identifier must be a sequence of one or more words \
|
||||||
\separated by hyphens (‘-’), and each such word may contain \
|
\separated by hyphens (‘-’), and each such word may contain \
|
||||||
|
@ -101,7 +107,7 @@ newEnumIdentField wid = checkEnmUniqueCI wid enumIdentField
|
||||||
checkCtorName :: Field Handler Text -> Field Handler Text
|
checkCtorName :: Field Handler Text -> Field Handler Text
|
||||||
checkCtorName =
|
checkCtorName =
|
||||||
let charOk c = isAlphaNum c || c == ' '
|
let charOk c = isAlphaNum c || c == ' '
|
||||||
nameOk t = (not . null) t && all charOk t
|
nameOk t = (not . T.null) t && T.all charOk t
|
||||||
msg :: Text
|
msg :: Text
|
||||||
msg = "The name may contain only letters, digits and spaces."
|
msg = "The name may contain only letters, digits and spaces."
|
||||||
in checkBool nameOk msg
|
in checkBool nameOk msg
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Vervis.Form.Discussion
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Yesod.Form
|
import Yesod.Form
|
||||||
|
|
||||||
|
|
|
@ -21,8 +21,6 @@ module Vervis.Form.Group
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Yesod.Form.Fields (textField, selectFieldList)
|
import Yesod.Form.Fields (textField, selectFieldList)
|
||||||
import Yesod.Form.Functions (aopt, areq, renderDivs)
|
import Yesod.Form.Functions (aopt, areq, renderDivs)
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- This file is part of Vervis.
|
{- This file is part of Vervis.
|
||||||
-
|
-
|
||||||
- Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
|
- Written in 2016, 2019 by fr33domlover <fr33domlover@riseup.net>.
|
||||||
-
|
-
|
||||||
- ♡ Copying is an act of love. Please copy, reuse and share.
|
- ♡ Copying is an act of love. Please copy, reuse and share.
|
||||||
-
|
-
|
||||||
|
@ -18,10 +18,14 @@ module Vervis.Form.Key
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Vervis.Import
|
import Yesod.Form.Fields
|
||||||
|
import Yesod.Form.Functions
|
||||||
|
import Yesod.Form.Types
|
||||||
|
|
||||||
import Vervis.Field.Key
|
import Vervis.Field.Key
|
||||||
import Vervis.Model.Ident (text2ky)
|
import Vervis.Foundation
|
||||||
|
import Vervis.Model
|
||||||
|
import Vervis.Model.Ident
|
||||||
|
|
||||||
newKeyAForm :: PersonId -> AForm Handler SshKey
|
newKeyAForm :: PersonId -> AForm Handler SshKey
|
||||||
newKeyAForm pid = SshKey
|
newKeyAForm pid = SshKey
|
||||||
|
|
|
@ -1,43 +0,0 @@
|
||||||
{- This file is part of Vervis.
|
|
||||||
-
|
|
||||||
- Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
|
|
||||||
-
|
|
||||||
- ♡ Copying is an act of love. Please copy, reuse and share.
|
|
||||||
-
|
|
||||||
- The author(s) have dedicated all copyright and related and neighboring
|
|
||||||
- rights to this software to the public domain worldwide. This software is
|
|
||||||
- distributed without any warranty.
|
|
||||||
-
|
|
||||||
- You should have received a copy of the CC0 Public Domain Dedication along
|
|
||||||
- with this software. If not, see
|
|
||||||
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
|
||||||
-}
|
|
||||||
|
|
||||||
module Vervis.Form.Person
|
|
||||||
( -- NewPerson (..)
|
|
||||||
-- , newPersonForm
|
|
||||||
)
|
|
||||||
where
|
|
||||||
|
|
||||||
import Vervis.Import
|
|
||||||
|
|
||||||
import Vervis.Field.Person
|
|
||||||
import Vervis.Field.Sharer
|
|
||||||
import Vervis.Model.Ident (ShrIdent)
|
|
||||||
|
|
||||||
data NewPerson = NewPerson
|
|
||||||
{ npLogin :: ShrIdent
|
|
||||||
, npPass :: Text
|
|
||||||
, npName :: Maybe Text
|
|
||||||
, npEmail :: Maybe Text
|
|
||||||
}
|
|
||||||
|
|
||||||
newPersonAForm :: AForm Handler NewPerson
|
|
||||||
newPersonAForm = NewPerson
|
|
||||||
<$> areq newSharerIdentField "Username*" Nothing
|
|
||||||
<*> areq passField "Password*" Nothing
|
|
||||||
<*> aopt textField "Full name" Nothing
|
|
||||||
<*> aopt emailField "E-mail" Nothing
|
|
||||||
|
|
||||||
newPersonForm :: Form NewPerson
|
|
||||||
newPersonForm = renderDivs newPersonAForm
|
|
|
@ -22,13 +22,20 @@ module Vervis.Form.Project
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Vervis.Import hiding (on, isNothing)
|
import Data.Bifunctor
|
||||||
|
import Data.Maybe
|
||||||
|
import Data.Text (Text)
|
||||||
import Database.Esqueleto hiding ((==.))
|
import Database.Esqueleto hiding ((==.))
|
||||||
|
import Database.Persist ((==.))
|
||||||
|
import Yesod.Form.Fields
|
||||||
|
import Yesod.Form.Functions
|
||||||
|
import Yesod.Form.Types
|
||||||
|
import Yesod.Persist.Core
|
||||||
|
|
||||||
import qualified Database.Esqueleto as E
|
import qualified Database.Esqueleto as E
|
||||||
|
|
||||||
import Vervis.Field.Project
|
import Vervis.Field.Project
|
||||||
|
import Vervis.Foundation
|
||||||
import Vervis.Model
|
import Vervis.Model
|
||||||
import Vervis.Model.Ident
|
import Vervis.Model.Ident
|
||||||
import Vervis.Model.Repo
|
import Vervis.Model.Repo
|
||||||
|
@ -93,9 +100,9 @@ newProjectCollabAForm sid jid = NewProjectCollab
|
||||||
on $
|
on $
|
||||||
collab ?. ProjectCollabProject E.==. just (val jid) &&.
|
collab ?. ProjectCollabProject E.==. just (val jid) &&.
|
||||||
collab ?. ProjectCollabPerson E.==. just (person ^. PersonId)
|
collab ?. ProjectCollabPerson E.==. just (person ^. PersonId)
|
||||||
where_ $ isNothing $ collab ?. ProjectCollabId
|
where_ $ E.isNothing $ collab ?. ProjectCollabId
|
||||||
return (sharer ^. SharerIdent, person ^. PersonId)
|
return (sharer ^. SharerIdent, person ^. PersonId)
|
||||||
optionsPairs $ map (shr2text . unValue *** unValue) l
|
optionsPairs $ map (bimap (shr2text . unValue) unValue) l
|
||||||
selectRole =
|
selectRole =
|
||||||
selectField $
|
selectField $
|
||||||
optionsPersistKey [RoleSharer ==. sid] [] $
|
optionsPersistKey [RoleSharer ==. sid] [] $
|
||||||
|
|
|
@ -22,14 +22,14 @@ module Vervis.Form.Repo
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
--import Prelude
|
import Data.Text (Text)
|
||||||
|
import Database.Persist
|
||||||
|
import Yesod.Form.Fields
|
||||||
|
import Yesod.Form.Functions
|
||||||
|
import Yesod.Form.Types
|
||||||
|
|
||||||
import Database.Esqueleto hiding ((==.))
|
|
||||||
|
|
||||||
import qualified Database.Esqueleto as E ((==.))
|
|
||||||
|
|
||||||
import Vervis.Import hiding (isNothing, on)
|
|
||||||
import Vervis.Field.Repo
|
import Vervis.Field.Repo
|
||||||
|
import Vervis.Foundation
|
||||||
import Vervis.Model
|
import Vervis.Model
|
||||||
import Vervis.Model.Ident
|
import Vervis.Model.Ident
|
||||||
import Vervis.Model.Repo
|
import Vervis.Model.Repo
|
||||||
|
|
|
@ -20,8 +20,6 @@ module Vervis.Form.Role
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Yesod.Form.Fields (textField)
|
import Yesod.Form.Fields (textField)
|
||||||
import Yesod.Form.Functions (areq, renderDivs)
|
import Yesod.Form.Functions (areq, renderDivs)
|
||||||
|
|
|
@ -24,8 +24,6 @@ module Vervis.Form.Ticket
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Applicative (liftA2, liftA3)
|
import Control.Applicative (liftA2, liftA3)
|
||||||
import Control.Monad.IO.Class (liftIO)
|
import Control.Monad.IO.Class (liftIO)
|
||||||
import Control.Monad.Trans.Class (lift)
|
import Control.Monad.Trans.Class (lift)
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- This file is part of Vervis.
|
{- This file is part of Vervis.
|
||||||
-
|
-
|
||||||
- Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
|
- Written in 2016, 2019 by fr33domlover <fr33domlover@riseup.net>.
|
||||||
-
|
-
|
||||||
- ♡ Copying is an act of love. Please copy, reuse and share.
|
- ♡ Copying is an act of love. Please copy, reuse and share.
|
||||||
-
|
-
|
||||||
|
@ -25,13 +25,13 @@ module Vervis.Form.Workflow
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Vervis.Import hiding (on, isNothing)
|
import Data.Text (Text)
|
||||||
|
import Yesod.Form.Fields
|
||||||
import Database.Esqueleto hiding ((==.))
|
import Yesod.Form.Functions
|
||||||
|
import Yesod.Form.Types
|
||||||
import qualified Database.Esqueleto as E ((==.))
|
|
||||||
|
|
||||||
import Vervis.Field.Workflow
|
import Vervis.Field.Workflow
|
||||||
|
import Vervis.Foundation
|
||||||
import Vervis.Model
|
import Vervis.Model
|
||||||
import Vervis.Model.Ident
|
import Vervis.Model.Ident
|
||||||
import Vervis.Model.Workflow
|
import Vervis.Model.Workflow
|
||||||
|
|
|
@ -25,8 +25,6 @@ module Vervis.Formatting
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.CaseInsensitive
|
import Data.CaseInsensitive
|
||||||
import Data.Text.Lazy.Builder (fromText)
|
import Data.Text.Lazy.Builder (fromText)
|
||||||
import Formatting
|
import Formatting
|
||||||
|
|
|
@ -15,12 +15,10 @@
|
||||||
|
|
||||||
module Vervis.Foundation where
|
module Vervis.Foundation where
|
||||||
|
|
||||||
import Prelude (init, last)
|
import Control.Concurrent.Chan
|
||||||
|
|
||||||
import Control.Concurrent.MVar (MVar, newEmptyMVar)
|
|
||||||
import Control.Concurrent.STM.TVar
|
import Control.Concurrent.STM.TVar
|
||||||
|
import Control.Monad
|
||||||
import Control.Monad.Logger.CallStack (logWarn)
|
import Control.Monad.Logger.CallStack (logWarn)
|
||||||
import Control.Monad.STM (atomically)
|
|
||||||
import Control.Monad.Trans.Except
|
import Control.Monad.Trans.Except
|
||||||
import Control.Monad.Trans.Maybe
|
import Control.Monad.Trans.Maybe
|
||||||
import Crypto.Error (CryptoFailable (..))
|
import Crypto.Error (CryptoFailable (..))
|
||||||
|
@ -29,32 +27,41 @@ import Data.Char
|
||||||
import Data.Either (isRight)
|
import Data.Either (isRight)
|
||||||
import Data.HashMap.Strict (HashMap)
|
import Data.HashMap.Strict (HashMap)
|
||||||
import Data.List.NonEmpty (NonEmpty (..))
|
import Data.List.NonEmpty (NonEmpty (..))
|
||||||
import Data.Maybe (fromJust)
|
import Data.Text (Text)
|
||||||
import Data.PEM (pemContent)
|
import Data.Text.Encoding
|
||||||
import Data.Text.Encoding (decodeUtf8')
|
import Data.Time.Calendar
|
||||||
|
import Data.Time.Clock
|
||||||
import Data.Time.Interval (TimeInterval, fromTimeUnit, toTimeUnit)
|
import Data.Time.Interval (TimeInterval, fromTimeUnit, toTimeUnit)
|
||||||
import Data.Time.Units (Second, Minute, Day)
|
import Data.Traversable
|
||||||
|
import Data.Vector (Vector)
|
||||||
import Database.Persist.Postgresql
|
import Database.Persist.Postgresql
|
||||||
import Database.Persist.Sql (ConnectionPool, runSqlPool)
|
import Database.Persist.Sql (ConnectionPool, runSqlPool)
|
||||||
import Graphics.SVGFonts.ReadFont (PreparedFont)
|
import Graphics.SVGFonts.ReadFont (PreparedFont)
|
||||||
import Network.HTTP.Client (Manager, HasHttpManager (..))
|
import Network.HTTP.Client (Manager, HasHttpManager (..))
|
||||||
import Network.HTTP.Types.Header (hHost)
|
import Network.HTTP.Types.Header
|
||||||
import Network.URI (URI, uriAuthority, uriFragment, uriRegName, parseURI)
|
import Network.URI (URI, uriAuthority, uriFragment, uriRegName, parseURI)
|
||||||
import Network.Wai
|
import Network.Wai
|
||||||
import Text.Shakespeare.Text (textFile)
|
import Text.Shakespeare.Text (textFile)
|
||||||
import Text.Hamlet (hamletFile)
|
import Text.Hamlet (hamletFile)
|
||||||
--import Text.Jasmine (minifym)
|
--import Text.Jasmine (minifym)
|
||||||
import UnliftIO.MVar (withMVar)
|
|
||||||
import Web.Hashids
|
import Web.Hashids
|
||||||
|
import Yesod.Auth
|
||||||
import Yesod.Auth.Account
|
import Yesod.Auth.Account
|
||||||
import Yesod.Auth.Account.Message (AccountMsg (MsgUsernameExists))
|
import Yesod.Auth.Account.Message (AccountMsg (MsgUsernameExists))
|
||||||
import Yesod.Auth.Message (AuthMessage (IdentifierNotFound))
|
import Yesod.Auth.Message (AuthMessage (IdentifierNotFound))
|
||||||
import Yesod.Core.Types (Logger)
|
import Yesod.Core hiding (logWarn)
|
||||||
|
import Yesod.Core.Types
|
||||||
import Yesod.Default.Util (addStaticContentExternal)
|
import Yesod.Default.Util (addStaticContentExternal)
|
||||||
|
import Yesod.Form.Fields
|
||||||
|
import Yesod.Form.Functions
|
||||||
|
import Yesod.Form.Types
|
||||||
|
import Yesod.Persist.Core
|
||||||
|
import Yesod.Static
|
||||||
|
|
||||||
import qualified Data.ByteString.Char8 as BC (unpack)
|
import qualified Data.ByteString.Char8 as BC (unpack)
|
||||||
import qualified Data.ByteString.Lazy as BL (ByteString)
|
import qualified Data.ByteString.Lazy as BL (ByteString)
|
||||||
import qualified Data.HashMap.Strict as M (lookup, insert)
|
import qualified Data.HashMap.Strict as M (lookup, insert)
|
||||||
|
import qualified Data.Time.Units as U
|
||||||
import qualified Database.Esqueleto as E
|
import qualified Database.Esqueleto as E
|
||||||
import qualified Yesod.Core.Unsafe as Unsafe
|
import qualified Yesod.Core.Unsafe as Unsafe
|
||||||
--import qualified Data.CaseInsensitive as CI
|
--import qualified Data.CaseInsensitive as CI
|
||||||
|
@ -84,11 +91,13 @@ import Yesod.Paginate.Local
|
||||||
|
|
||||||
import Vervis.Access
|
import Vervis.Access
|
||||||
import Vervis.ActorKey
|
import Vervis.ActorKey
|
||||||
import Vervis.Import.NoFoundation hiding (Handler, Day, last, init, logWarn)
|
import Vervis.Model
|
||||||
import Vervis.Model.Group
|
import Vervis.Model.Group
|
||||||
import Vervis.Model.Ident
|
import Vervis.Model.Ident
|
||||||
import Vervis.Model.Role
|
import Vervis.Model.Role
|
||||||
import Vervis.RemoteActorStore
|
import Vervis.RemoteActorStore
|
||||||
|
import Vervis.Settings
|
||||||
|
import Vervis.Style
|
||||||
import Vervis.Widget (breadcrumbsW, revisionW)
|
import Vervis.Widget (breadcrumbsW, revisionW)
|
||||||
|
|
||||||
data ActivityReport = ActivityReport
|
data ActivityReport = ActivityReport
|
||||||
|
@ -167,7 +176,8 @@ instance Yesod App where
|
||||||
makeSessionBackend app =
|
makeSessionBackend app =
|
||||||
-- sslOnlySessions $
|
-- sslOnlySessions $
|
||||||
let s = appSettings app
|
let s = appSettings app
|
||||||
t = fromIntegral (toTimeUnit $ appClientSessionTimeout s :: Minute)
|
t = fromIntegral
|
||||||
|
(toTimeUnit $ appClientSessionTimeout s :: U.Minute)
|
||||||
k = appClientSessionKeyFile s
|
k = appClientSessionKeyFile s
|
||||||
in Just <$> defaultClientSessionBackend t k
|
in Just <$> defaultClientSessionBackend t k
|
||||||
|
|
||||||
|
@ -629,8 +639,8 @@ instance YesodAuthVerify App where
|
||||||
|
|
||||||
instance YesodAuthAccount AccountPersistDB' App where
|
instance YesodAuthAccount AccountPersistDB' App where
|
||||||
requireEmailVerification = appEmailVerification . appSettings
|
requireEmailVerification = appEmailVerification . appSettings
|
||||||
emailVerifyKeyDuration _ = Just $ fromTimeUnit (1 :: Day)
|
emailVerifyKeyDuration _ = Just $ fromTimeUnit (1 :: U.Day)
|
||||||
passphraseResetKeyDuration _ = Just $ fromTimeUnit (1 :: Day)
|
passphraseResetKeyDuration _ = Just $ fromTimeUnit (1 :: U.Day)
|
||||||
allowLoginByEmailAddress _ = True
|
allowLoginByEmailAddress _ = True
|
||||||
runAccountDB = unAccountPersistDB'
|
runAccountDB = unAccountPersistDB'
|
||||||
|
|
||||||
|
|
|
@ -22,8 +22,6 @@ module Vervis.Git
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Arrow ((***))
|
import Control.Arrow ((***))
|
||||||
import Control.Monad (join)
|
import Control.Monad (join)
|
||||||
import Control.Monad.Trans.Class (lift)
|
import Control.Monad.Trans.Class (lift)
|
||||||
|
|
|
@ -33,8 +33,6 @@ module Vervis.GraphProxy
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
|
|
||||||
import Vervis.Model
|
import Vervis.Model
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- This file is part of Vervis.
|
{- This file is part of Vervis.
|
||||||
-
|
-
|
||||||
- Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
|
- Written in 2016, 2019 by fr33domlover <fr33domlover@riseup.net>.
|
||||||
-
|
-
|
||||||
- ♡ Copying is an act of love. Please copy, reuse and share.
|
- ♡ Copying is an act of love. Please copy, reuse and share.
|
||||||
-
|
-
|
||||||
|
@ -20,8 +20,10 @@ module Vervis.Handler.Common
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Data.FileEmbed (embedFile)
|
import Data.FileEmbed
|
||||||
import Vervis.Import
|
import Yesod.Core
|
||||||
|
|
||||||
|
import Vervis.Foundation
|
||||||
|
|
||||||
-- These handlers embed files in the executable at compile time to avoid a
|
-- These handlers embed files in the executable at compile time to avoid a
|
||||||
-- runtime dependency, and for efficiency.
|
-- runtime dependency, and for efficiency.
|
||||||
|
|
|
@ -23,8 +23,6 @@ module Vervis.Handler.Discussion
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Monad.IO.Class (liftIO)
|
import Control.Monad.IO.Class (liftIO)
|
||||||
import Control.Monad.Trans.Except
|
import Control.Monad.Trans.Except
|
||||||
|
|
|
@ -19,8 +19,6 @@ module Vervis.Handler.Git
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Monad (unless)
|
import Control.Monad (unless)
|
||||||
import Control.Monad.IO.Class (liftIO)
|
import Control.Monad.IO.Class (liftIO)
|
||||||
import Data.Binary.Put
|
import Data.Binary.Put
|
||||||
|
|
|
@ -27,8 +27,6 @@ module Vervis.Handler.Group
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Monad.IO.Class (liftIO)
|
import Control.Monad.IO.Class (liftIO)
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
import Data.Time.Clock (getCurrentTime)
|
import Data.Time.Clock (getCurrentTime)
|
||||||
|
|
|
@ -18,22 +18,29 @@ module Vervis.Handler.Home
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Vervis.Import hiding (on)
|
|
||||||
|
|
||||||
import Database.Esqueleto hiding ((==.))
|
import Database.Esqueleto hiding ((==.))
|
||||||
import Yesod.Auth.Account (newAccountR)
|
import Yesod.Auth.Account (newAccountR)
|
||||||
import Data.Time.Clock (diffUTCTime)
|
import Data.Time.Clock
|
||||||
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
|
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
|
||||||
|
import Data.Traversable
|
||||||
|
import Database.Persist
|
||||||
import Time.Types (Elapsed (..), Seconds (..))
|
import Time.Types (Elapsed (..), Seconds (..))
|
||||||
|
import Yesod.Auth
|
||||||
|
import Yesod.Core
|
||||||
|
import Yesod.Persist.Core
|
||||||
|
|
||||||
import qualified Database.Esqueleto as E ((==.))
|
import qualified Database.Esqueleto as E ((==.))
|
||||||
|
|
||||||
|
import Data.EventTime.Local
|
||||||
|
|
||||||
import Vervis.Darcs
|
import Vervis.Darcs
|
||||||
|
import Vervis.Foundation
|
||||||
|
import Vervis.Model
|
||||||
import Vervis.Model.Ident
|
import Vervis.Model.Ident
|
||||||
import Vervis.Model.Repo
|
import Vervis.Model.Repo
|
||||||
import Vervis.Path
|
import Vervis.Path
|
||||||
|
import Vervis.Settings
|
||||||
|
|
||||||
import Data.EventTime.Local
|
|
||||||
import qualified Vervis.Git as G
|
import qualified Vervis.Git as G
|
||||||
import qualified Vervis.Darcs as D
|
import qualified Vervis.Darcs as D
|
||||||
|
|
||||||
|
|
|
@ -30,8 +30,6 @@ module Vervis.Handler.Inbox
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Control.Applicative ((<|>))
|
import Control.Applicative ((<|>))
|
||||||
import Control.Concurrent.STM.TVar (readTVarIO, modifyTVar')
|
import Control.Concurrent.STM.TVar (readTVarIO, modifyTVar')
|
||||||
import Control.Exception hiding (Handler)
|
import Control.Exception hiding (Handler)
|
||||||
|
|
|
@ -23,8 +23,6 @@ module Vervis.Handler.Key
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
import Data.ByteString.Base64 (encode)
|
import Data.ByteString.Base64 (encode)
|
||||||
import Data.Monoid ((<>))
|
import Data.Monoid ((<>))
|
||||||
import Data.Text (Text, intercalate)
|
import Data.Text (Text, intercalate)
|
||||||
|
|
|
@ -20,16 +20,12 @@ module Vervis.Handler.Person
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Vervis.Import hiding ((==.))
|
|
||||||
--import Prelude
|
|
||||||
|
|
||||||
import Data.List.NonEmpty (NonEmpty (..))
|
|
||||||
import Database.Esqueleto hiding (isNothing, count)
|
import Database.Esqueleto hiding (isNothing, count)
|
||||||
import Vervis.Form.Person
|
|
||||||
--import Model
|
|
||||||
import Text.Blaze.Html (toHtml)
|
import Text.Blaze.Html (toHtml)
|
||||||
|
import Yesod.Core
|
||||||
import Yesod.Auth.Account (newAccountR, resendVerifyEmailWidget, username)
|
import Yesod.Auth.Account (newAccountR, resendVerifyEmailWidget, username)
|
||||||
import Yesod.Auth.Account.Message (AccountMsg (MsgEmailUnverified))
|
import Yesod.Auth.Account.Message (AccountMsg (MsgEmailUnverified))
|
||||||
|
import Yesod.Persist.Core
|
||||||
|
|
||||||
import qualified Data.Text as T (unpack)
|
import qualified Data.Text as T (unpack)
|
||||||
|
|
||||||
|
@ -41,10 +37,12 @@ import Network.FedURI
|
||||||
import Web.ActivityPub
|
import Web.ActivityPub
|
||||||
import Yesod.FedURI
|
import Yesod.FedURI
|
||||||
|
|
||||||
--import Vervis.ActivityStreams
|
|
||||||
import Vervis.ActorKey
|
import Vervis.ActorKey
|
||||||
|
import Vervis.Foundation
|
||||||
|
import Vervis.Model
|
||||||
import Vervis.Model.Ident
|
import Vervis.Model.Ident
|
||||||
import Vervis.Secure
|
import Vervis.Secure
|
||||||
|
import Vervis.Settings
|
||||||
import Vervis.Widget (avatarW)
|
import Vervis.Widget (avatarW)
|
||||||
|
|
||||||
-- | Account verification email resend form
|
-- | Account verification email resend form
|
||||||
|
|
Some files were not shown because too many files have changed in this diff Show more
Loading…
Reference in a new issue