Skip to content

Commit

Permalink
Add instance IsList (Logic a)
Browse files Browse the repository at this point in the history
  • Loading branch information
Bodigrim committed Aug 8, 2024
1 parent 508af6b commit a25b089
Showing 1 changed file with 18 additions and 1 deletion.
19 changes: 18 additions & 1 deletion Control/Monad/Logic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,9 +23,15 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

#if MIN_VERSION_base(4,17,0)
{-# LANGUAGE Safe #-}
#else
{-# LANGUAGE Trustworthy #-}
#endif

module Control.Monad.Logic (
module Control.Monad.Logic.Class,
-- * The Logic monad
Expand Down Expand Up @@ -74,6 +80,12 @@ import Data.Ord ((<=))
import Data.Semigroup (Semigroup (..))
import qualified Data.Traversable as T

#if MIN_VERSION_base(4,17,0)
import GHC.IsList (IsList(..))
#else
import GHC.Exts (IsList(..))
#endif

import Control.Monad.Logic.Class

-------------------------------------------------------------------------
Expand Down Expand Up @@ -528,3 +540,8 @@ instance MonadCatch m => MonadCatch (LogicT m) where
catch m h = LogicT $ \sk fk -> let
handle r = r `catch` \e -> unLogicT (h e) sk fk
in handle $ unLogicT m (\a -> sk a . handle) fk

instance IsList (Logic a) where
type Item (Logic a) = a
fromList xs = LogicT $ \cons nil -> L.foldr cons nil xs
toList = observeAll

0 comments on commit a25b089

Please sign in to comment.