module Language.Alloy.Call (
CallAlloyConfig (maxInstances, noOverflow, satSolver, timeout),
SatSolver (..),
defaultCallAlloyConfig,
existsInstance,
getInstances,
getInstancesWith,
module Functions,
module Types,
) where
import Language.Alloy.Functions as Functions
import Language.Alloy.Internal.Call
import Language.Alloy.Parser (parseInstance)
import Language.Alloy.Types as Types
(AlloyInstance, AlloySig, Entries, Object, Signature)
import Control.Monad.Catch (MonadThrow)
import Control.Monad.IO.Class (MonadIO (liftIO))
getInstances
:: (MonadIO m, MonadThrow m)
=> Maybe Integer
-> String
-> m [AlloyInstance]
getInstances :: forall (m :: * -> *).
(MonadIO m, MonadThrow m) =>
Maybe Integer -> String -> m [AlloyInstance]
getInstances Maybe Integer
maxIs = CallAlloyConfig -> String -> m [AlloyInstance]
forall (m :: * -> *).
(MonadIO m, MonadThrow m) =>
CallAlloyConfig -> String -> m [AlloyInstance]
getInstancesWith CallAlloyConfig
defaultCallAlloyConfig {
maxInstances = maxIs
}
getInstancesWith
:: (MonadIO m, MonadThrow m)
=> CallAlloyConfig
-> String
-> m [AlloyInstance]
getInstancesWith :: forall (m :: * -> *).
(MonadIO m, MonadThrow m) =>
CallAlloyConfig -> String -> m [AlloyInstance]
getInstancesWith CallAlloyConfig
config String
content =
IO [ByteString] -> m [ByteString]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (CallAlloyConfig -> String -> IO [ByteString]
getRawInstancesWith CallAlloyConfig
config String
content)
m [ByteString]
-> ([ByteString] -> m [AlloyInstance]) -> m [AlloyInstance]
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ByteString -> m AlloyInstance)
-> [ByteString] -> m [AlloyInstance]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ByteString -> m AlloyInstance
forall (m :: * -> *).
(MonadIO m, MonadThrow m) =>
ByteString -> m AlloyInstance
parseInstance
existsInstance
:: (MonadIO m, MonadThrow m)
=> String
-> m Bool
existsInstance :: forall (m :: * -> *). (MonadIO m, MonadThrow m) => String -> m Bool
existsInstance = ([AlloyInstance] -> Bool) -> m [AlloyInstance] -> m Bool
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Bool -> Bool
not (Bool -> Bool)
-> ([AlloyInstance] -> Bool) -> [AlloyInstance] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [AlloyInstance] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) (m [AlloyInstance] -> m Bool)
-> (String -> m [AlloyInstance]) -> String -> m Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Integer -> String -> m [AlloyInstance]
forall (m :: * -> *).
(MonadIO m, MonadThrow m) =>
Maybe Integer -> String -> m [AlloyInstance]
getInstances (Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
1)