predicate-typed-0.7.3.0: Predicates, Refinement types and Dsl

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.IO

Description

promoted io functions

Synopsis

Documentation

data ReadFile p Source #

similar to readFile

>>> pz @(ReadFile "LICENSE" >> 'Just Id >> Len > 0) ()
TrueT
>>> pz @(FileExists "xyzzy") ()
FalseT
>>> pl @(FileExists "xxy") ()
False (IsJust)
FalseT
Instances
(PP p x ~ String, P p x) => P (ReadFile p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP (ReadFile p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ReadFile p) -> POpts -> x -> m (TT (PP (ReadFile p) x)) Source #

type PP (ReadFile p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

type PP (ReadFile p :: Type) x = Maybe String

data FileExists p Source #

similar to doesFileExist

Instances
P (FileExistsT p) x => P (FileExists p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP (FileExists p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (FileExists p) -> POpts -> x -> m (TT (PP (FileExists p) x)) Source #

type PP (FileExists p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

type PP (FileExists p :: Type) x

data ReadDir p Source #

similar to listDirectory

Instances
(PP p x ~ String, P p x) => P (ReadDir p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP (ReadDir p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ReadDir p) -> POpts -> x -> m (TT (PP (ReadDir p) x)) Source #

type PP (ReadDir p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

type PP (ReadDir p :: Type) x = Maybe [FilePath]

data DirExists p Source #

similar to doesDirectoryExist

>>> pz @(DirExists ".") ()
TrueT
>>> pl @(DirExists ".") ()
True (IsJust)
TrueT
>>> pl @(DirExists "xxy") ()
False (IsJust)
FalseT
Instances
P (DirExistsT p) x => P (DirExists p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP (DirExists p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (DirExists p) -> POpts -> x -> m (TT (PP (DirExists p) x)) Source #

type PP (DirExists p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

type PP (DirExists p :: Type) x

data ReadEnv p Source #

read an environment variable: similar to getEnv

>>> pz @(ReadEnv "PATH" >> 'Just Id >> 'True) ()
TrueT
Instances
(PP p x ~ String, P p x) => P (ReadEnv p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP (ReadEnv p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ReadEnv p) -> POpts -> x -> m (TT (PP (ReadEnv p) x)) Source #

type PP (ReadEnv p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

type PP (ReadEnv p :: Type) x = Maybe String

data ReadEnvAll Source #

read all the environment variables as key value pairs: similar to getEnvironment

Instances
P ReadEnvAll a Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP ReadEnvAll a :: Type Source #

Methods

eval :: MonadEval m => proxy ReadEnvAll -> POpts -> a -> m (TT (PP ReadEnvAll a)) Source #

type PP ReadEnvAll a Source # 
Instance details

Defined in Predicate.Data.IO

type PP ReadEnvAll a = [(String, String)]

data TimeUtc Source #

get the current time using UTCTime

Instances
P TimeUtc a Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP TimeUtc a :: Type Source #

Methods

eval :: MonadEval m => proxy TimeUtc -> POpts -> a -> m (TT (PP TimeUtc a)) Source #

type PP TimeUtc a Source # 
Instance details

Defined in Predicate.Data.IO

type PP TimeUtc a = UTCTime

data TimeZt Source #

get the current time using ZonedTime

Instances
P TimeZt a Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP TimeZt a :: Type Source #

Methods

eval :: MonadEval m => proxy TimeZt -> POpts -> a -> m (TT (PP TimeZt a)) Source #

type PP TimeZt a Source # 
Instance details

Defined in Predicate.Data.IO

data AppendFile (s :: Symbol) p Source #

append to a file

Instances
P (AppendFileT s p) x => P (AppendFile s p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP (AppendFile s p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (AppendFile s p) -> POpts -> x -> m (TT (PP (AppendFile s p) x)) Source #

type PP (AppendFile s p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

type PP (AppendFile s p :: Type) x

data WriteFile (s :: Symbol) p Source #

write to file, without overwriting

Instances
P (WriteFileT s p) x => P (WriteFile s p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP (WriteFile s p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (WriteFile s p) -> POpts -> x -> m (TT (PP (WriteFile s p) x)) Source #

type PP (WriteFile s p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

type PP (WriteFile s p :: Type) x

data WriteFile' (s :: Symbol) p Source #

write to file, overwriting if needed

Instances
P (WriteFileT' s p) x => P (WriteFile' s p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP (WriteFile' s p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (WriteFile' s p) -> POpts -> x -> m (TT (PP (WriteFile' s p) x)) Source #

type PP (WriteFile' s p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

type PP (WriteFile' s p :: Type) x

data Stdout p Source #

write a string value to stdout

Instances
P (StdoutT p) x => P (Stdout p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP (Stdout p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Stdout p) -> POpts -> x -> m (TT (PP (Stdout p) x)) Source #

type PP (Stdout p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

type PP (Stdout p :: Type) x

data Stderr p Source #

write a string value to stderr

Instances
P (StderrT p) x => P (Stderr p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP (Stderr p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Stderr p) -> POpts -> x -> m (TT (PP (Stderr p) x)) Source #

type PP (Stderr p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

type PP (Stderr p :: Type) x

data Stdin Source #

read a value from stdin

Instances
P Stdin x Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP Stdin x :: Type Source #

Methods

eval :: MonadEval m => proxy Stdin -> POpts -> x -> m (TT (PP Stdin x)) Source #

type PP Stdin x Source # 
Instance details

Defined in Predicate.Data.IO

type PP Stdin x = String

type ReadIO (t :: Type) = ReadIO' t "Enter value" Source #

read in a value of a given type from stdin with a prompt: similar to readIO

type ReadIO' (t :: Type) s = Stdout (s <> ":") >> (Stdin >> ReadP t Id) Source #