include module type of Effect
A bad faith preamble
To be beautiful and modern, this project separates the description of the programme from its interpretation. But as the composition is not really to my taste in Preface, I decided to centralize all the effects, like the errors, in one module.
Ugh, that sounds perfectly stupid... it would be like considering that you can only express one family of effects (you could call it ... IO
). Don't panic, the first parameter of type effect
allows you to make a selective choice when defining Freer
. One could say that one takes advantage of the non-surjective aspect of the constructors of a sum (thanks to the GADTs!). Well, I'd be lying if I said I was convinced it was a good approach, but at least it seems viable.
Effects list
Boy, this type sounds like a hell of a lot of trouble to read! don't read it and go a little lower, there are kind of smarts constructors.
Sourcetype (_, 'a) effects = (_, 'a) Effect.effects =
| File_exists : Filepath.t -> (< file_exists : unit.. >, bool) effects
| Target_exists : Filepath.t -> (< target_exists : unit.. >, bool) effects
| Get_modification_time : Filepath.t -> (< get_modification_time : unit.. >,
int Try.t)
effects
| Target_modification_time : Filepath.t -> (< target_modification_time : unit.. >,
int Try.t)
effects
| Read_file : Filepath.t -> (< read_file : unit.. >, string Try.t) effects
| Content_changes : (string * Filepath.t) -> (< content_changes : unit.. >,
(string, unit) Either.t Try.t)
effects
| Write_file : (Filepath.t * string) -> (< write_file : unit.. >, unit Try.t)
effects
| Read_dir : (Filepath.t
* [< `Files | `Directories | `Both ]
* Filepath.t Preface.Predicate.t) -> (< read_dir : unit.. >,
Filepath.t list)
effects
| Command : string -> (< command : unit.. >, int) effects
| Log : (Log.level * string) -> (< log : unit.. >, unit) effects
| Throw : Error.t -> (< throw : unit.. >, 'a) effects
| Raise : exn -> (< raise_ : unit.. >, 'a) effects
Global definition
Complete mechanism for describing programs by description and providing them with handlers (interpreters/runtime) for all effects modelled in type t
. (So absolutely not taking advantage of the slicing capability... It was well worth it!)
Freer monad over effects
All the plumbing for effects description/interpretation resides through a Freer monad (thanks Preface). Although this module is included below, I have taken the liberty of displaying it... for documentation purposes only.
Once described (or/and specialised), the effects must be produced in a programme description. To transform the description of an effect (a value of type Effect.effect
) into the execution of this effect, thus a value of type Effect.t
), the perform
function is used.
Filesystem
In generating a static blog, having control over the file system seems to be a minimum!
file_exists path
should be interpreted as returning true
if the file denoted by the file path path
exists, false
otherwise.
target_exists path
should be interpreted as returning true
if the file denoted by the file path path
exists, false
otherwise.
get_modification_time path
should be interpreted as returning, as an integer, the Unix time (mtime
corresponding to the modification date of the file denoted by the file path path
.
target_modification_time path
should be interpreted as returning, as an integer, the Unix time (mtime
corresponding to the modification date of the file denoted by the file path path
.
read_file path
should be interpreted as trying to read the contents of the file denoted by the file path path
. At the moment I'm using strings mainly out of laziness, and as I'll probably be the only user of this library... it doesn't matter!
Sourceval content_changes :
Filepath.t ->
string ->
(string, unit) Either.t Try.t Freer.t
content_changes content filepath
should be interpreted as trying to check if the content of the file is different from the given content. (In order to reduce the mtime modification)
write_file path content
should be interpreted as trying to write content
to the file denoted by the file path path
. In my understanding of the system, the file will be completely overwritten if it already exists. Once again I am using strings, but this time it is not laziness, it is to be consistent with read_file
.
Get a list of all children of a path.
Get a list of all child files of a path (exclude dirs).
Get a list of all child directories of a path (exclude files).
Same of read_children
but searching through a list of directories.
Same of read_child_files
but searching through a list of directories.
Same of read_child_directories
but searching through a list of directories.
process_files path predicate action
performs sequentially action
on each files which satisfies predicate
.
Sourceval command : string -> int Freer.t
command cmd
performs a shell commands
and returns the exit code.
Logging
Even if it would be possible to limit our feedback with the user to simply returning an integer (El famoso Unix Return)... it would still be more convenient to display feedback to the user on the stage the program is in, right?
log level message
should be interpreted as writing (probably to standard output) a message associated with a log level. To look good, the colour should change according to the log level, it would look more professional!
Sourceval trace : string -> unit Freer.t
trace message
is an alias of log Aliases.Trace
.
Sourceval debug : string -> unit Freer.t
debug message
is an alias of log Aliases.Debug
.
Sourceval info : string -> unit Freer.t
info message
is an alias of log Aliases.Info
.
Sourceval warning : string -> unit Freer.t
warning message
is an alias of log Aliases.Warning
.
Sourceval alert : string -> unit Freer.t
alert message
is an alias of log Aliases.Alert
.
Open bar
When we are in the context of an IO, ahem, effect execution, it's open bar, we can do whatever we want, like throwing exceptions galore!
throw error
should be interpreted as... "fire, fire, what to do using an Error!".
Sourceval raise_ : exn -> 'a Freer.t
raise_ exn
should be interpreted as... "fire, fire, what to do using an exception!".
Effects composition
Sourceval sequence :
'a list Freer.t ->
('a -> 'b -> 'b Freer.t) ->
'b Freer.t ->
'b Freer.t
Collapses sequentially YOCaml program. sequence ps f p
produces a program which performs p
followed by f ps
. A common usage is p |> sequences ps f
.
Included Freer combinators
As mentioned above, the plumbing of program description and program handling is provided through a Freer Monad, a technique that aims to describe a free build over a Left Kan extension. Although the presence of slicing allows for the construction of specialised effects handlers, in the use case of this blog generator, the effects I propagate turn out to be exactly those I have described in my complete effects list. Coicindance, I don't think so!
It therefore seems logical (not to say ergonomic) to introduce the Freer interface in the toplevel of the Effect
module. But as the interface is long and tiring to read, I place it at the end of the module!
include Preface.Specs.FREER_MONAD
with type 'a f = 'a Freer.f
and type 'a t = 'a Freer.t
and module Infix := Freer.Infix
and module Syntax := Freer.Syntax
type !'a t = 'a Freer.t =
| Return : 'b -> 'b t
| Bind : 'c f * ('c -> 'd t) -> 'd t
type (!'a, !'b) handle = ('a -> 'b) -> 'a f -> 'b
val bind : ('a -> 'b t) -> 'a t -> 'b t
val map : ('a -> 'b) -> 'a t -> 'b t
val join : 'a t t -> 'a t
val compose_left_to_right : ('a -> 'b t) -> ('b -> 'c t) -> 'a -> 'c t
val compose_right_to_left : ('b -> 'c t) -> ('a -> 'b t) -> 'a -> 'c t
val lift : ('a -> 'b) -> 'a t -> 'b t
val lift2 : ('a -> 'b -> 'c) -> 'a t -> 'b t -> 'c t
val lift3 : ('a -> 'b -> 'c -> 'd) -> 'a t -> 'b t -> 'c t -> 'd t
val replace : 'a -> 'b t -> 'a t
val void : 'a t -> unit t
include module type of Infix with type 'a t := 'a Freer.t
include Preface.Specs.Applicative.INFIX
with type 'a t := 'a Yocaml__.Effect.Freer.t
val (<*>) :
('a -> 'b) Yocaml__.Effect.Freer.t ->
'a Yocaml__.Effect.Freer.t ->
'b Yocaml__.Effect.Freer.t
val (<**>) :
'a Yocaml__.Effect.Freer.t ->
('a -> 'b) Yocaml__.Effect.Freer.t ->
'b Yocaml__.Effect.Freer.t
val (*>) :
unit Yocaml__.Effect.Freer.t ->
'a Yocaml__.Effect.Freer.t ->
'a Yocaml__.Effect.Freer.t
val (<*) :
'a Yocaml__.Effect.Freer.t ->
unit Yocaml__.Effect.Freer.t ->
'a Yocaml__.Effect.Freer.t
include Preface.Specs.Monad.INFIX with type 'a t := 'a Yocaml__.Effect.Freer.t
val (=|<) :
('a -> 'b) ->
'a Yocaml__.Effect.Freer.t ->
'b Yocaml__.Effect.Freer.t
val (>|=) :
'a Yocaml__.Effect.Freer.t ->
('a -> 'b) ->
'b Yocaml__.Effect.Freer.t
val (>>=) :
'a Yocaml__.Effect.Freer.t ->
('a -> 'b Yocaml__.Effect.Freer.t) ->
'b Yocaml__.Effect.Freer.t
val (=<<) :
('a -> 'b Yocaml__.Effect.Freer.t) ->
'a Yocaml__.Effect.Freer.t ->
'b Yocaml__.Effect.Freer.t
val (>=>) :
('a -> 'b Yocaml__.Effect.Freer.t) ->
('b -> 'c Yocaml__.Effect.Freer.t) ->
'a ->
'c Yocaml__.Effect.Freer.t
val (<=<) :
('b -> 'c Yocaml__.Effect.Freer.t) ->
('a -> 'b Yocaml__.Effect.Freer.t) ->
'a ->
'c Yocaml__.Effect.Freer.t
val (>>) :
unit Yocaml__.Effect.Freer.t ->
'b Yocaml__.Effect.Freer.t ->
'b Yocaml__.Effect.Freer.t
val (<<) :
'a Yocaml__.Effect.Freer.t ->
unit Yocaml__.Effect.Freer.t ->
'a Yocaml__.Effect.Freer.t
val (<$>) :
('a -> 'b) ->
'a Yocaml__.Effect.Freer.t ->
'b Yocaml__.Effect.Freer.t
val (<&>) :
'a Yocaml__.Effect.Freer.t ->
('a -> 'b) ->
'b Yocaml__.Effect.Freer.t
val (<$) : 'a -> 'b Yocaml__.Effect.Freer.t -> 'a Yocaml__.Effect.Freer.t
val ($>) : 'a Yocaml__.Effect.Freer.t -> 'b -> 'b Yocaml__.Effect.Freer.t
include module type of Syntax with type 'a t := 'a Freer.t
include Preface.Specs.Applicative.SYNTAX
with type 'a t := 'a Yocaml__.Effect.Freer.t
val (and+) :
'a Yocaml__.Effect.Freer.t ->
'b Yocaml__.Effect.Freer.t ->
('a * 'b) Yocaml__.Effect.Freer.t
include Preface.Specs.Monad.SYNTAX with type 'a t := 'a Yocaml__.Effect.Freer.t
val (let*) :
'a Yocaml__.Effect.Freer.t ->
('a -> 'b Yocaml__.Effect.Freer.t) ->
'b Yocaml__.Effect.Freer.t
val (let+) :
'a Yocaml__.Effect.Freer.t ->
('a -> 'b) ->
'b Yocaml__.Effect.Freer.t