Skip to content

Commit

Permalink
Reorder imports
Browse files Browse the repository at this point in the history
  • Loading branch information
ajeetdsouza committed Jun 13, 2019
1 parent d593f91 commit 09eee77
Show file tree
Hide file tree
Showing 3 changed files with 31 additions and 17 deletions.
18 changes: 13 additions & 5 deletions src/CI.hs
Original file line number Diff line number Diff line change
@@ -1,18 +1,26 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}

module CI (Types.CI(..), isCI, getCI) where
module CI
( Types.CI(..)
, isCI
, getCI
) where

import CI.TH (getVendors)
import qualified CI.Types as Types
import Control.Arrow ((***))
import Data.Bool (bool)
import Data.Foldable (find)
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe (isJust)
import qualified Data.Text as T
import System.Environment (getEnvironment)

import CI.TH (getVendors)

import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as T

import qualified CI.Types as Types


vendors :: [Types.Vendor]
vendors = $(getVendors)

Expand Down
8 changes: 6 additions & 2 deletions src/CI/TH.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,14 @@
module CI.TH (getVendors) where
module CI.TH
( getVendors
) where

import qualified CI.Types as Types
import qualified Data.Aeson as Aeson
import qualified Language.Haskell.TH as TH
import qualified Language.Haskell.TH.Syntax as TH

import qualified CI.Types as Types


getVendors :: TH.Q TH.Exp
getVendors = TH.runIO readVendors >>= TH.lift
where
Expand Down
22 changes: 12 additions & 10 deletions src/CI/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,23 +7,25 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}

module CI.Types
( CI(..)
, Vendor(..)
, VendorEnv(..)
, EnvVarName(..)
, EnvVarValue(..)) where
( CI(..)
, Vendor(..)
, VendorEnv(..)
, EnvVarName(..)
, EnvVarValue(..)) where

import Data.Hashable (Hashable)
import Data.HashMap.Strict (HashMap)
import Data.Text (Text)
import Instances.TH.Lift ()

import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Casing as Aeson
import qualified Data.Aeson.TH as Aeson
import Data.Hashable (Hashable)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Text (Text)
import qualified Data.Text as T
import Instances.TH.Lift ()
import qualified Language.Haskell.TH.Syntax as TH


data CI =
CI_APPVEYOR -- http://www.appveyor.com/
| CI_AZURE_PIPELINES -- https://azure.microsoft.com/en-us/services/devops/pipelines/
Expand Down Expand Up @@ -85,7 +87,7 @@ instance Aeson.FromJSON VendorEnv where

instance Aeson.ToJSON VendorEnv where
toJSON val = case val of
VendorEnvString key -> Aeson.toJSON key
VendorEnvString name -> Aeson.toJSON name
VendorEnvList list -> Aeson.toJSON list
VendorEnvObject object -> Aeson.toJSON object

Expand Down

0 comments on commit 09eee77

Please sign in to comment.