module Language.Alloy.Call (
  CallAlloyConfig (maxInstances, noOverflow, timeout),
  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)
getInstances
  :: Maybe Integer
  
  -> String
  
  -> IO [AlloyInstance]
getInstances :: Maybe Integer -> String -> IO [AlloyInstance]
getInstances Maybe Integer
maxIs = CallAlloyConfig -> String -> IO [AlloyInstance]
getInstancesWith CallAlloyConfig
defaultCallAlloyConfig {
  maxInstances :: Maybe Integer
maxInstances = Maybe Integer
maxIs
  }
getInstancesWith
  :: CallAlloyConfig
  
  -> String
  
  -> IO [AlloyInstance]
getInstancesWith :: CallAlloyConfig -> String -> IO [AlloyInstance]
getInstancesWith CallAlloyConfig
config String
content =
  (ByteString -> AlloyInstance) -> [ByteString] -> [AlloyInstance]
forall a b. (a -> b) -> [a] -> [b]
map ((ErrInfo -> AlloyInstance)
-> (AlloyInstance -> AlloyInstance)
-> Either ErrInfo AlloyInstance
-> AlloyInstance
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> AlloyInstance
forall a. HasCallStack => String -> a
error (String -> AlloyInstance)
-> (ErrInfo -> String) -> ErrInfo -> AlloyInstance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrInfo -> String
forall a. Show a => a -> String
show) AlloyInstance -> AlloyInstance
forall a. a -> a
id (Either ErrInfo AlloyInstance -> AlloyInstance)
-> (ByteString -> Either ErrInfo AlloyInstance)
-> ByteString
-> AlloyInstance
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either ErrInfo AlloyInstance
forall (m :: * -> *).
MonadError ErrInfo m =>
ByteString -> m AlloyInstance
parseInstance)
  ([ByteString] -> [AlloyInstance])
-> IO [ByteString] -> IO [AlloyInstance]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CallAlloyConfig -> String -> IO [ByteString]
getRawInstancesWith CallAlloyConfig
config String
content
existsInstance
  :: String
  
  -> IO Bool
  
existsInstance :: String -> IO Bool
existsInstance = ([AlloyInstance] -> Bool) -> IO [AlloyInstance] -> IO Bool
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 (t :: * -> *) a. Foldable t => t a -> Bool
null) (IO [AlloyInstance] -> IO Bool)
-> (String -> IO [AlloyInstance]) -> String -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Integer -> String -> IO [AlloyInstance]
getInstances (Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
1)