Replies: 8 comments 43 replies
-
? Note that in your version, your are copying the entire file content into In short, by using For your code, note that there is SICStus 4 that produces for a file For information, please read 3. Pure I/O via DCGs of Declarative language extensions for Prolog courses by Neumerkel, Triska, Wielemaker, FDPE 2008. |
Beta Was this translation helpful? Give feedback.
-
|
A sketch for a faster |
Beta Was this translation helpful? Give feedback.
-
🤣🤣🤣 brilliant!!! |
Beta Was this translation helpful? Give feedback.
-
|
Amazing!! This is a result of many comments in the "Meta-DCGs" and "Dcg bug or nuanced behavior?". One of the biggest pain points is that redirecting from a pipe to But this is already a better version of grep with more powerful syntax! With a few command line flags it could be very versatile! $ scryer-prolog -g run dcgrep.pl -- /tmp/words.txt '...,[Last]'.
JiuJitsu is a mousetrap. ...,['.']
The moustrap is not a JiuJitsu mousetrap. ...,['.']
But, when JiuJitsu puts the mouse in the cheese, ...,[',']
JiuJitsu the mousetrap cheese mouse WHATVER LOLLLLL ...,['L']:- use_module(library(format)).
:- use_module(library(pio)).
:- use_module(library(iso_ext)).
:- use_module(library(debug)).
:- use_module(library(lambda)).
:- use_module(library(reif)).
:- use_module(library(dcgs)).
:- use_module(library(lists)).
:- use_module(library(charsio)).
writeln(Line-Term) :- format("~s ~t ~q", [Line,Term]), nl.
run :-
'$toplevel':argv([Fname,DCG|_]),
read_term_from_chars(DCG,DCGTerm, []),
setup_call_cleanup(open(Fname,read,Stream,[]),
( phrase_from_stream(lines(Lines), Stream),
matching_phrases(DCGTerm, Lines, Matching),
maplist(writeln, Matching)
),
close(Stream)
),
halt.
matching_phrases(_Phrase, [], []).
matching_phrases(Phrase, [Line|Lines], Matching) :-
copy_term(Phrase, Phrase1),
if_(phrase_t(Phrase1, Line),
Matching=[Line-Phrase1|Matching0],
Matching=Matching0
),
matching_phrases(Phrase,Lines,Matching0).
phrase_t(Phrase,In,T) :- phrase_t(Phrase,In,[],T).
phrase_t(Phrase,In,Out,T) :-
( phrase(Phrase,In,Out) ->
T=true
; T=false
).
%% https://www.metalevel.at/prolog/dcg
lines([]) --> call(eos), !.
lines([L|Ls]) --> line(L), lines(Ls).
line([]) --> ( "\n" | call(eos) ), !.
line([C|Cs]) --> [C], line(Cs).
eos([], []). |
Beta Was this translation helpful? Give feedback.
-
|
I'm observing developments, just wanted to add my 5 cents. One of the design choices of
If The hardest part is to design a good DSL that will work for all those use cases. If |
Beta Was this translation helpful? Give feedback.
-
I should have mentioned that exactly such discussions happened also in other systems some decades ago. It is just a sink. And, the next step was to support all other encodings... In any case, if we assume that files have to be in UTF-8, be can equally assume that they are normalized.
What is missing here? |
Beta Was this translation helpful? Give feedback.
-
It's the device where it is displayed that actually decides how it is rendered. My Ubuntu terminal makes it different to FF. As I said, a complete sink and waste of time. |
Beta Was this translation helpful? Give feedback.
-
|
Ok so to summarize what I am understanding, it sounds like Scryer Prolog itself should not be in the business of "unicode normalization" but a tool such as |
Beta Was this translation helpful? Give feedback.
Uh oh!
There was an error while loading. Please reload this page.
-
Alright everyone, inspired by some very interesting discussions the past few days regarding subjects related to DCGs, I have been secretly working on...
dcgrep, a DCG-based "grep" tool!It raises so many interesting topics about how to use Prolog and DCGs effectively on numerous threads. Here is my best (but so far not working) effort towards a
dcgrep-like interface:There are many, MANY ways to go with this, I would love to see everyone's great ideas!
Some important considerations:
dcgrepbe? Full text or line by line? Should it offer similar functionality to regex, or be completely different?(..., "something", ...)is tempting, but is not a great technique for matching text because the...consumes more than you probably think it does. Or is it?Beta Was this translation helpful? Give feedback.
All reactions