Skip to content

Commit

Permalink
Merge pull request #7 from haskell-works/newhoggy/new-ToString-typeclass
Browse files Browse the repository at this point in the history
Adopt some useful modules from `hw-polysemy`
  • Loading branch information
newhoggy authored Nov 18, 2024
2 parents 138d821 + 7f42415 commit 431c708
Show file tree
Hide file tree
Showing 5 changed files with 69 additions and 0 deletions.
4 changes: 4 additions & 0 deletions hw-prelude.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -94,11 +94,15 @@ library
HaskellWorks.Error.Types
HaskellWorks.Error.Types.GenericError
HaskellWorks.Error.Types.TimedOut
HaskellWorks.FilePath
HaskellWorks.IO.Network.NamedPipe
HaskellWorks.IO.Network.Port
HaskellWorks.IO.Network.Socket
HaskellWorks.IO.Process
HaskellWorks.OS
HaskellWorks.Prelude
HaskellWorks.Stack
HaskellWorks.String
HaskellWorks.ToText
HaskellWorks.Unsafe
hs-source-dirs: src
18 changes: 18 additions & 0 deletions src/HaskellWorks/FilePath.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
module HaskellWorks.FilePath
( exeSuffix,
addExeSuffix,
) where

import qualified HaskellWorks.OS as OS

import qualified Data.List as L
import Data.Monoid
import Data.String

exeSuffix :: String
exeSuffix = if OS.isWin32 then ".exe" else ""

addExeSuffix :: String -> String
addExeSuffix s = if ".exe" `L.isSuffixOf` s
then s
else s <> exeSuffix
12 changes: 12 additions & 0 deletions src/HaskellWorks/OS.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
module HaskellWorks.OS
( isWin32,
) where

import Data.Bool
import Data.Eq
import System.Info

-- | Determine if the operating system is Windows.
isWin32 :: Bool
isWin32 = os == "mingw32"
{-# INLINE isWin32 #-}
14 changes: 14 additions & 0 deletions src/HaskellWorks/Stack.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
module HaskellWorks.Stack
( callerModuleName,
) where

import Data.Function
import Data.Maybe (listToMaybe, maybe)
import Data.String
import Data.Tuple
import GHC.Stack (HasCallStack, callStack, getCallStack,
srcLocModule)

-- | Get the module name of the caller.
callerModuleName :: HasCallStack => String
callerModuleName = maybe "<no-module>" (srcLocModule . snd) (listToMaybe (getCallStack callStack))
21 changes: 21 additions & 0 deletions src/HaskellWorks/String.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,21 @@
module HaskellWorks.String
( ToString(..),
) where

import Data.Function
import Data.String
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as LT

class ToString a where
toString :: a -> String

instance ToString String where
toString = id

instance ToString Text where
toString = T.unpack

instance ToString LT.Text where
toString = LT.unpack

0 comments on commit 431c708

Please sign in to comment.