{-# LANGUAGE TypeFamilies, DataKinds, MultiParamTypeClasses, PolyKinds, TypeApplications, ScopedTypeVariables, ConstraintKinds, TypeOperators, GADTs, UndecidableInstances, StandaloneDeriving, IncoherentInstances, AllowAmbiguousTypes, FunctionalDependencies #-} {-| Module: IHP.HaskellSupport Description: Provides helpers to write better haskell code Copyright: (c) digitally induced GmbH, 2020 -} module IHP.HaskellSupport ( (|>) , (|>>) , whenEmpty , whenNonEmpty , get , set , setJust , setMaybe , ifOrEmpty , modify , modifyJust , SetField (..) , UpdateField (..) , incrementField , decrementField , isToday , isToday' , forEach , forEachWithIndex , textToInt , isWeekend , todayIsWeekend , debug , includes , stripTags , symbolToText , symbolToByteString , IsEmpty (..) , copyFields , allEnumValues ) where import ClassyPrelude import qualified Data.Default import qualified Data.UUID as UUID import Data.Proxy import qualified Data.Time import GHC.TypeLits import GHC.OverloadedLabels import qualified GHC.Records as Record import qualified Data.Attoparsec.ByteString.Char8 as Attoparsec import Data.String.Conversions (cs, ConvertibleStrings (..)) import qualified Debug.Trace import qualified Data.Text as Text import qualified Data.Map as Map import qualified Data.ByteString.Char8 as ByteString import qualified Data.Aeson.Key as Aeson --(|>) :: a -> f -> f a infixl 8 |> a |> f = f a {-# INLINE (|>) #-} infixl 8 |>> a |>> b = a <&> b {-# INLINABLE (|>>) #-} -- | Used by 'nonEmpty' and 'isEmptyValue' to check for emptyness class IsEmpty value where -- | Returns True when the value is an empty string, empty list, zero UUID, etc. isEmpty :: value -> Bool instance IsEmpty Text where isEmpty "" = True isEmpty _ = False {-# INLINE isEmpty #-} instance IsEmpty (Maybe value) where isEmpty Nothing = True isEmpty (Just _) = False {-# INLINE isEmpty #-} instance IsEmpty [a] where isEmpty [] = True isEmpty _ = False {-# INLINE isEmpty #-} instance IsEmpty UUID.UUID where isEmpty uuid = UUID.nil == uuid {-# INLINE isEmpty #-} instance IsEmpty (Map a b) where isEmpty = Map.null {-# INLINE isEmpty #-} ifOrEmpty :: (Monoid a) => Bool -> a -> a ifOrEmpty bool a = if bool then a else mempty {-# INLINE ifOrEmpty #-} whenEmpty condition = when (isEmpty condition) {-# INLINE whenEmpty #-} whenNonEmpty :: (IsEmpty a, Applicative f) => a -> f () -> f () whenNonEmpty condition = unless (isEmpty condition) {-# INLINE whenNonEmpty #-} -- Returns 'True' when a value is contained in the given list, array, set, ... -- -- Alias for 'elem', but with a nicer name :) -- -- >>> ["hello", "world"] |> includes "hello" -- True -- -- >>> "Hello" |> includes 'H' -- True includes :: (MonoFoldable container, Eq (Element container)) => Element container -> container -> Bool includes = elem {-# INLINE includes #-} instance Data.Default.Default UUID.UUID where def = UUID.nil {-# INLINE def #-} instance forall name name'. (KnownSymbol name, name' ~ name) => IsLabel name (Proxy name') where fromLabel = Proxy @name' {-# INLINE fromLabel #-} -- | Returns the field value for a field name -- -- __Example:__ -- -- > data Project = Project { name :: Text, isPublic :: Bool } -- > -- > let project = Project { name = "Hello World", isPublic = False } -- -- >>> project.name -- "Hello World" -- -- >>> project.isPublic -- False get :: forall model name value. (KnownSymbol name, Record.HasField name model value) => Proxy name -> model -> value get _ record = Record.getField @name record {-# INLINE get #-} -- | Sets a field of a record and returns the new record. -- -- __Example:__ -- -- > data Project = Project { name :: Text, isPublic :: Bool } -- > -- > let project = Project { name = "Hello World", isPublic = False } -- -- >>> set #name "New Name" project -- Project { name = "New Name", isPublic = False } -- -- >>> set #isPublic True project -- Project { name = "Hello World", isPublic = True } set :: forall model name value. (KnownSymbol name, SetField name model value) => Proxy name -> value -> model -> model set name value record = setField @name value record {-# INLINE set #-} -- | Like 'set' but doesn't set the value if it's 'Nothing'. Useful when you update NULL values -- | e.g. via a cron job and don't want to lose that work on subsequent updates. -- -- __Example:__ -- -- > data Project = Project { name :: Maybe Text } -- > -- > let project = Project { name = Nothing } -- -- >>> setMaybe #name (Just "New Name") project -- Project { name = Just "New Name" } -- -- >>> setMaybe #name Nothing project -- Project { name = Just "New Name" } -- previous value is kept -- setMaybe :: forall model name value. (KnownSymbol name, SetField name model (Maybe value)) => Proxy name -> Maybe value -> model -> model setMaybe name value record = case value of Just value -> setField @name (Just value) record Nothing -> record {-# INLINE setMaybe #-} -- | Like 'set' but wraps the value with a 'Just'. Useful when you want to set a 'Maybe' field -- -- __Example:__ -- -- > data Project = Project { name :: Maybe Text } -- > -- > let project = Project { name = Nothing } -- -- >>> setJust #name "New Name" project -- Project { name = Just "New Name" } -- setJust :: forall model name value. (KnownSymbol name, SetField name model (Maybe value)) => Proxy name -> value -> model -> model setJust name value record = setField @name (Just value) record {-# INLINE setJust #-} modify :: forall model name value. (KnownSymbol name, Record.HasField name model value, SetField name model value) => Proxy name -> (value -> value) -> model -> model modify _ updateFunction model = let value = Record.getField @name model in setField @name (updateFunction value) model {-# INLINE modify #-} -- Like 'modify', but only modifies the value if it's not Nothing. -- -- __Example:__ -- -- > let pauseDuration = now `diffUTCTime` pausedAt -- > -- > floorTimer <- floorTimer -- > |> modifyJust #startedAt (addUTCTime pauseDuration) -- > |> updateRecord -- modifyJust :: forall model name value. (KnownSymbol name, Record.HasField name model (Maybe value), SetField name model (Maybe value)) => Proxy name -> (value -> value) -> model -> model modifyJust _ updateFunction model = case Record.getField @name model of Just value -> setField @name (Just (updateFunction value)) model Nothing -> model {-# INLINE modifyJust #-} -- | Plus @1@ on record field. -- -- __Example:__ -- -- > data Project = Project { name :: Text, followersCount :: Int } -- > -- > let project = Project { name = "Hello World", followersCount = 0 } -- -- >>> project |> incrementField #followersCount -- Project { name = "Hello World", followersCount = 1 } incrementField :: forall model name value. (KnownSymbol name, Record.HasField name model value, SetField name model value, Num value) => Proxy name -> model -> model incrementField _ model = let value = Record.getField @name model in setField @name (value + 1) model {-# INLINE incrementField #-} -- | Minus @1@ on a record field. -- -- __Example:__ -- -- > data Project = Project { name :: Text, followersCount :: Int } -- > -- > let project = Project { name = "Hello World", followersCount = 1337 } -- -- >>> project |> decrementField #followersCount -- Project { name = "Hello World", followersCount = 1336 } decrementField :: forall model name value. (KnownSymbol name, Record.HasField name model value, SetField name model value, Num value) => Proxy name -> model -> model decrementField _ model = let value = Record.getField @name model in setField @name (value - 1) model {-# INLINE decrementField #-} class SetField (field :: GHC.TypeLits.Symbol) model value | field model -> value where setField :: value -> model -> model class Record.HasField field model value => UpdateField (field :: GHC.TypeLits.Symbol) model model' value value' | model model' value' -> value where updateField :: value' -> model -> model' utcTimeToYearMonthDay :: UTCTime -> (Integer, Int, Int) utcTimeToYearMonthDay = toGregorian . utctDay -- (year,month,day) isToday :: UTCTime -> IO Bool isToday timestamp = do now <- getCurrentTime pure (isToday' now timestamp) isToday' :: UTCTime -> UTCTime -> Bool isToday' currentTime timestamp = utcTimeToYearMonthDay currentTime == utcTimeToYearMonthDay timestamp -- | Allows `Just "someThing"` to be written as `"someThing"` instance IsString string => IsString (Maybe string) where fromString string = Just (fromString string) {-# INLINE fromString #-} -- | Example: -- -- > forEach users \user -> putStrLn (tshow user) -- -- __Example:__ Within HSX -- -- > renderUser :: User -> Html -- > renderUser user = [hsx|