Skip to content

Commit

Permalink
updating eulerhs test file changes
Browse files Browse the repository at this point in the history
  • Loading branch information
Vijay Gupta committed Aug 25, 2023
1 parent 9bc4544 commit b9be8bf
Show file tree
Hide file tree
Showing 126 changed files with 2,021 additions and 1,062 deletions.
2 changes: 0 additions & 2 deletions cabal.project

This file was deleted.

10 changes: 4 additions & 6 deletions euler-hs.cabal
Original file line number Diff line number Diff line change
@@ -1,13 +1,11 @@
cabal-version: 3.0
name: euler-hs
version: 3.3.2.0
synopsis: The Flow framework for Euler.
description:
homepage: https://github.com/juspay/euler-hs
license:
synopsis: The Flow framework for web backends
license: Apache-2.0
author: Juspay Technologies Pvt Ltd
maintainer: euler@juspay.in
copyright: (C) Juspay Technologies Pvt Ltd 2019-2020
maintainer: opensource@juspay.in
copyright: (C) Juspay Technologies Pvt Ltd 2019-2022
category: Euler
build-type: Simple
tested-with: GHC ==8.8.4 || ==8.10.7
Expand Down
11 changes: 11 additions & 0 deletions src/EulerHS/ART/DBReplay.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,14 @@
{- |
Module : EulerHS.ART.DBReplay
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
This module contains interpreters and methods for running `Flow` scenarios.
-}

{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
Expand Down
11 changes: 11 additions & 0 deletions src/EulerHS/ART/EnvVars.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,14 @@
{- |
Module : EulerHS.ART.EnvVars
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
This module contains interpreters and methods for running `Flow` scenarios.
-}

{-# LANGUAGE ScopedTypeVariables #-}

module EulerHS.ART.EnvVars where
Expand Down
9 changes: 9 additions & 0 deletions src/EulerHS/ART/FlowUtils.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,12 @@
{- |
Module : EulerHS.ART.FlowUtils
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
-}

{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
Expand Down
9 changes: 9 additions & 0 deletions src/EulerHS/ART/ReplayFunctions.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,12 @@
{- |
Module : EulerHS.ART.ReplayFunctions
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
-}

{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE ScopedTypeVariables #-}
Expand Down
12 changes: 12 additions & 0 deletions src/EulerHS/ART/Types.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,15 @@
{- |
Module : EulerHS.ART.Types
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
This module contains types for ART recording.
Import this module qualified as import EulerHS.ART.Types as ART
-}

{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE ScopedTypeVariables #-}

Expand Down
9 changes: 9 additions & 0 deletions src/EulerHS/ART/Utils.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,12 @@
{- |
Module : EulerHS.ART.Utils
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
-}

{-# LANGUAGE ScopedTypeVariables #-}

module EulerHS.ART.Utils where
Expand Down
17 changes: 17 additions & 0 deletions src/EulerHS/Api.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,15 @@
{- |
Module : EulerHS.Api
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
This module contains the definition of the `EulerClient` type, which is a wrapper around `Servant.Client.Client` type.
It also contains the definition of the `ApiTag` type, which is used to tag API calls in the logs.
-}

{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE RankNTypes #-}
Expand All @@ -14,11 +26,16 @@ import Servant.Client.Core.RunClient (RunClient)
import qualified Servant.Client.Free as SCF
import qualified EulerHS.Options as T
import qualified EulerHS.Logger.Types as Log
import qualified Servant.Client as SC
import qualified Servant.Client.Core as SCC

newtype EulerClient a = EulerClient (Free SCF.ClientF a)
deriving newtype (Functor, Applicative, Monad, RunClient)
-- deriving stock (Show,Generic)

client :: SC.HasClient EulerClient api => Proxy api -> SC.Client EulerClient api
client api = SCC.clientIn api $ Proxy @EulerClient

data LogServantRequest
= LogServantRequest
{ url :: String
Expand Down
9 changes: 9 additions & 0 deletions src/EulerHS/ApiHelpers.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,12 @@
{- |
Module : EulerHS.ApiHelpers
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
-}

{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
module EulerHS.ApiHelpers where
Expand Down
11 changes: 10 additions & 1 deletion src/EulerHS/BinaryString.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,12 @@
{- |
Module : EulerHS.BinaryString
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
-}

module EulerHS.BinaryString
( BinaryString(..)
, LBinaryString(..)
Expand All @@ -15,7 +24,7 @@ import qualified Data.Text.Encoding as Encoding
import EulerHS.Prelude
import Text.Read (read)

-- TODO: Move to euler-db


--------------------------------------------------------------------------
-- Base64 encoding/decoding helpers
Expand Down
13 changes: 13 additions & 0 deletions src/EulerHS/CachedSqlDBQuery.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,16 @@
{- |
Module : EulerHS.CachedSqlDBQuery
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
This module contains the function to create, update, delete and find rows in the database.
This module has functions which are being used in Flows for KVDB operations.
-}

{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# OPTIONS_GHC -Wno-error=unused-top-binds #-}
Expand Down
10 changes: 10 additions & 0 deletions src/EulerHS/Common.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,13 @@
{- |
Module : EulerHS.Common
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
This module contains common types and functions used in EulerHS.
-}

{-# LANGUAGE DerivingVia #-}

module EulerHS.Common
Expand Down
6 changes: 3 additions & 3 deletions src/EulerHS/Core/Api.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,3 @@
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

{- |
Module : EulerHS.Core.Api
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
Expand All @@ -14,6 +11,9 @@ This module contains implementation of the low-level HTTP client subsystem.
This is an internal module. Import EulerHS.Types instead.
-}

{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}


module EulerHS.Core.Api where
import EulerHS.Prelude
Expand Down
9 changes: 9 additions & 0 deletions src/EulerHS/Core/KVDB/Interpreter.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,12 @@
{- |
Module : EulerHS.Core.KVDB.Interpreter
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
-}

{-# LANGUAGE AllowAmbiguousTypes #-}
module EulerHS.Core.KVDB.Interpreter
(
Expand Down
8 changes: 4 additions & 4 deletions src/EulerHS/Core/KVDB/Language.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,3 @@
{-# OPTIONS_GHC -Werror #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE MultiParamTypeClasses #-}

{- |
Module : EulerHS.Core.KVDB.Language
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
Expand All @@ -19,6 +15,10 @@ This module is internal and should not imported in the projects.
Import 'EulerHS.Language' instead.
-}

{-# OPTIONS_GHC -Werror #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE MultiParamTypeClasses #-}

module EulerHS.Core.KVDB.Language
(
-- * KVDB language
Expand Down
9 changes: 9 additions & 0 deletions src/EulerHS/Core/Language.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,12 @@
{- |
Module : EulerHS.Core.Language
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
-}

{- |
Module : EulerHS.Core.Language
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
Expand Down
9 changes: 9 additions & 0 deletions src/EulerHS/Core/Logger/Impl/TinyLogger.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,12 @@
{- |
Module : EulerHS.Core.Logger.Impl.TinyLogger
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
-}

module EulerHS.Core.Logger.Impl.TinyLogger
(
-- * TinyLogger Implementation
Expand Down
9 changes: 9 additions & 0 deletions src/EulerHS/Core/Logger/Interpreter.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,12 @@
{- |
Module : EulerHS.Core.Logger.Interpreter
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
-}

{-# LANGUAGE BangPatterns #-}

module EulerHS.Core.Logger.Interpreter
Expand Down
9 changes: 9 additions & 0 deletions src/EulerHS/Core/Logger/Language.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,12 @@
{- |
Module : EulerHS.Core.Logger.Language
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
-}

{-# LANGUAGE GADTs #-}
{-# LANGUAGE TemplateHaskell #-}

Expand Down
9 changes: 9 additions & 0 deletions src/EulerHS/Core/Masking.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,12 @@
{- |
Module : EulerHS.Core.Masking
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
-}

module EulerHS.Core.Masking where


Expand Down
9 changes: 9 additions & 0 deletions src/EulerHS/Core/PubSub/Interpreter.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,12 @@
{- |
Module : EulerHS.Core.PubSub.Interpreter
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
-}

module EulerHS.Core.PubSub.Interpreter where

import EulerHS.Prelude
Expand Down
4 changes: 2 additions & 2 deletions src/EulerHS/Core/PubSub/Language.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
{-# LANGUAGE DeriveFunctor #-}

{- |
Module : EulerHS.Core.PubSub.Language
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
Expand All @@ -14,6 +12,8 @@ This module is internal and should not imported in the projects.
Import 'EulerHS.Language' instead.
-}

{-# LANGUAGE DeriveFunctor #-}

module EulerHS.Core.PubSub.Language where

import EulerHS.Prelude
Expand Down
8 changes: 1 addition & 7 deletions src/EulerHS/Core/Runtime.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ import EulerHS.Core.Types.DB as X (withTransaction)
import qualified System.Logger as Log


-- TODO: add StaticLoggerRuntimeContext if we'll need more than a single Bool

data LoggerRuntime
= LoggerRuntime
{ _flowFormatter :: T.FlowFormatter
Expand All @@ -62,12 +62,6 @@ data CoreRuntime = CoreRuntime
{ _loggerRuntime :: LoggerRuntime
}

-- createLoggerRuntime :: LoggerConfig -> IO LoggerRuntime
-- createLoggerRuntime (MemoryLoggerConfig cfgLogLevel) =
-- MemoryLoggerRuntime cfgLogLevel <$> newMVar []
-- createLoggerRuntime cfg = do
-- counter <- initLogCounter
-- LoggerRuntime (_level cfg) (_logRawSql cfg) counter Nothing Nothing (_logMaskingConfig cfg)<$> Impl.createLogger cfg

createMemoryLoggerRuntime :: T.FlowFormatter -> T.LogLevel -> IO LoggerRuntime
createMemoryLoggerRuntime flowFormatter logLevel =
Expand Down
10 changes: 9 additions & 1 deletion src/EulerHS/Core/SqlDB/Interpreter.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,12 @@
{- |
Module : EulerHS.Core.SqlDB.Interpreter
Copyright : (C) Juspay Technologies Pvt Ltd 2019-2022
License : Apache 2.0 (see the file LICENSE)
Maintainer : opensource@juspay.in
Stability : experimental
Portability : non-portable
-}

module EulerHS.Core.SqlDB.Interpreter
(
-- * SQL DB Interpreter
Expand All @@ -11,7 +20,6 @@ import qualified EulerHS.Core.Types as T

import Control.Exception (throwIO)

-- TODO: The runner runner gets composed in in `sqlDBMethod`. Move it into the interpreter!
interpretSqlDBMethod
:: T.NativeSqlConn
-> (Text -> IO ())
Expand Down
Loading

0 comments on commit b9be8bf

Please sign in to comment.