| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Predicate.Data.ReadShow
Description
promoted read, show, and printf functions
read-show
similar to show
>>>pz @(ShowP Id) [4,8,3,9]Val "[4,8,3,9]"
>>>pz @(ShowP Id) 'x'Val "'x'"
>>>pz @(ShowP (42 -% 10)) 'x'Val "(-21) % 5"
data ReadP (t :: Type) p Source #
uses the Read of the given type t and p which points to the content to read
>>>pz @(ReadP Rational Id) "4 % 5"Val (4 % 5)
>>>pz @(Between (ReadP Day "2017-04-11") (ReadP Day "2018-12-30") (ReadP Day Id)) "2018-10-12"Val True
>>>pz @(Between (ReadP Day "2017-04-11") (ReadP Day "2018-12-30") (ReadP Day Id)) "2016-10-12"Val False
>>>pl @(ReadP Rational Id) "123 % 4"Present 123 % 4 (ReadP Ratio Integer 123 % 4) Val (123 % 4)
>>>pl @(ReadP Rational Id) "x123 % 4"Error ReadP Ratio Integer (x123 % 4) ([]) Fail "ReadP Ratio Integer (x123 % 4)"
>>>pl @(ReadP Day Id) "1999-11-30"Present 1999-11-30 (ReadP Day 1999-11-30) Val 1999-11-30
>>>pl @(ReadP Day Id) "1999-02-29"Error ReadP Day (1999-02-29) ([]) Fail "ReadP Day (1999-02-29)"
>>>pl @(ReadP TimeOfDay Id) "14:59:20"Present 14:59:20 (ReadP TimeOfDay 14:59:20) Val 14:59:20
uses the Read of the given type t and p which points to the content to read
data ReadMaybe (t :: Type) p Source #
Read but returns the Maybe of the value and any remaining unparsed string
>>>pz @(ReadMaybe Int Id) "123x"Val (Just (123,"x"))
>>>pz @(ReadMaybe Int Id) "123"Val (Just (123,""))
>>>pz @(ReadMaybe Int Id) "x123"Val Nothing
data ReadMaybe' t p Source #
Instances
| (P p x, PP p x ~ String, Typeable (PP t x), Show (PP t x), Read (PP t x)) => P (ReadMaybe' t p :: Type) x Source # | |
Defined in Predicate.Data.ReadShow Associated Types type PP (ReadMaybe' t p) x Source # Methods eval :: MonadEval m => proxy (ReadMaybe' t p) -> POpts -> x -> m (TT (PP (ReadMaybe' t p) x)) Source # | |
| Show (ReadMaybe' t p) Source # | |
Defined in Predicate.Data.ReadShow Methods showsPrec :: Int -> ReadMaybe' t p -> ShowS # show :: ReadMaybe' t p -> String # showList :: [ReadMaybe' t p] -> ShowS # | |
| type PP (ReadMaybe' t p :: Type) x Source # | |
Defined in Predicate.Data.ReadShow | |
uses PrintF (unsafe) to format output for a single value
>>>pz @(PrintF "value=%03d" Id) 12Val "value=012"
>>>pz @(PrintF "%s" Fst) ("abc",'x')Val "abc"
>>>pz @(PrintF "%d" Fst) ("abc",'x')Fail "PrintF (IO e=printf: bad formatting char 'd')"
>>>pl @(PrintF "someval %d" Id) "!23"Error PrintF (IO e=printf: bad formatting char 'd') ("!23" s=someval %d) Fail "PrintF (IO e=printf: bad formatting char 'd')"
>>>pl @(PrintF "%-6s" Id) 1234Error PrintF (IO e=printf: bad formatting char 's') (1234 s=%-6s) Fail "PrintF (IO e=printf: bad formatting char 's')"
>>>pl @(PrintF "%06x" Id) 1234Present "0004d2" (PrintF [0004d2] | p=1234 | s=%06x) Val "0004d2"
>>>pl @(Msg (PrintF "digits=%d" Len) Head) [1..4]Present 1 (digits=4 Head 1 | [1,2,3,4]) Val 1
>>>pl @(PrintF "ask%%dfas%%kef%05d hey %%" Id) 35Present "ask%dfas%kef00035 hey %" (PrintF [ask%dfas%kef00035 hey %] | p=35 | s=ask%%dfas%%kef%05d hey %%) Val "ask%dfas%kef00035 hey %"
>>>pl @(Fail () (PrintF "someval int=%d" Id)) 45Error someval int=45 Fail "someval int=45"
data PrintL (n :: Nat) s p Source #
print for lists -- use PrintT as it is safer than PrintL
>>>pl @(PrintL 4 "%s %s %s %s" '[W "xyz", ShowP Fst, ShowP Snd, Thd]) (123,'x',"ab")Present "xyz 123 'x' ab" ((>>) "xyz 123 'x' ab" | {PrintI [xyz 123 'x' ab] | s=%s %s %s %s}) Val "xyz 123 'x' ab"
>>>pz @(PrintL 1 "%05d" '[Id]) 123 -- tick is required for a one element lis)Val "00123"
>>>pz @(PrintL 2 "%d %05d" [Fst,Snd]) (29,123)Val "29 00123"
>>>pl @(PrintL 3 "first=%d second=%d third=%d" Id) [10,11,12]Present "first=10 second=11 third=12" ((>>) "first=10 second=11 third=12" | {PrintI [first=10 second=11 third=12] | s=first=%d second=%d third=%d}) Val "first=10 second=11 third=12"
>>>pl @(PrintL 2 "first=%d second=%d third=%d" Id) [10,11,12]Error toITupleListC: expected exactly 2 values (ToITupleList(2) instead found 3) Fail "toITupleListC: expected exactly 2 values"
>>>pl @(PrintL 4 "first=%d second=%d third=%d" Id) [10,11,12]Error toITupleListC: expected exactly 4 values (ToITupleList(4) instead found 3) Fail "toITupleListC: expected exactly 4 values"
>>>pl @(PrintL 4 "%03d.%03d.%03d.%03d" Id) [1,2,3,4]Present "001.002.003.004" ((>>) "001.002.003.004" | {PrintI [001.002.003.004] | s=%03d.%03d.%03d.%03d}) Val "001.002.003.004"
>>>pl @(PrintL 4 "%03d.%03d.%03d.%03d" Id) [1,2,3,4,5]Error toITupleListC: expected exactly 4 values (ToITupleList(4) instead found 5) Fail "toITupleListC: expected exactly 4 values"
>>>pl @(PrintL 4 "%03d.%03d.%03d.%03d" Id) [1,2,3]Error toITupleListC: expected exactly 4 values (ToITupleList(4) instead found 3) Fail "toITupleListC: expected exactly 4 values"
>>>pl @(PrintL 4 "%03d.%03d.%03d.%03d" Id) [1,2,3,4]Present "001.002.003.004" ((>>) "001.002.003.004" | {PrintI [001.002.003.004] | s=%03d.%03d.%03d.%03d}) Val "001.002.003.004"
>>>pl @(PrintL 4 "%d %4d %-d %03d" Id) [1..4]Present "1 2 3 004" ((>>) "1 2 3 004" | {PrintI [1 2 3 004] | s=%d %4d %-d %03d}) Val "1 2 3 004"
print for flat n-tuples of size two or larger
>>>pl @(PrintT "%d %s %s %s" '(Fst, Snd, Snd,Snd)) (10,"Asdf")Present "10 Asdf Asdf Asdf" ((>>) "10 Asdf Asdf Asdf" | {PrintI [10 Asdf Asdf Asdf] | s=%d %s %s %s}) Val "10 Asdf Asdf Asdf"
>>>pl @(PrintT "%c %d %s" Id) ('x', 10,"Asdf")Present "x 10 Asdf" ((>>) "x 10 Asdf" | {PrintI [x 10 Asdf] | s=%c %d %s}) Val "x 10 Asdf"
>>>pz @(PrintT "fst=%s snd=%03d" Id) ("ab",123)Val "fst=ab snd=123"
>>>pz @(PrintT "fst=%s snd=%03d thd=%s" Id) ("ab",123,"xx")Val "fst=ab snd=123 thd=xx"
>>>pl @(PrintT "%s %d %c %s" '(W "xyz", Fst, Snd, Thd)) (123,'x',"ab")Present "xyz 123 x ab" ((>>) "xyz 123 x ab" | {PrintI [xyz 123 x ab] | s=%s %d %c %s}) Val "xyz 123 x ab"
>>>pl @(PrintT "%d %c %s" Id) (123,'x')Error PrintI(IO e=printf: argument list ended prematurely) (PrintI %d %c %s | ('x',(123,()))) Fail "PrintI(IO e=printf: argument list ended prematurely)"
>>>pl @(PrintT "%d %c %s" Id) (123,'x',"abc",11)Error PrintI(IO e=printf: formatting string ended prematurely) (PrintI %d %c %s | (11,("abc",('x',(123,()))))) Fail "PrintI(IO e=printf: formatting string ended prematurely)"
>>>pl @(PrintT "lhs = %d rhs = %s" Id) (123,"asdf")Present "lhs = 123 rhs = asdf" ((>>) "lhs = 123 rhs = asdf" | {PrintI [lhs = 123 rhs = asdf] | s=lhs = %d rhs = %s}) Val "lhs = 123 rhs = asdf"
>>>pl @(PrintT "d=%03d s=%s" Id) (9,"ab")Present "d=009 s=ab" ((>>) "d=009 s=ab" | {PrintI [d=009 s=ab] | s=d=%03d s=%s}) Val "d=009 s=ab"
>>>pl @(PrintT "d=%03d s=%s c=%c f=%4.2f" Id) (9,"ab",'x',1.54)Present "d=009 s=ab c=x f=1.54" ((>>) "d=009 s=ab c=x f=1.54" | {PrintI [d=009 s=ab c=x f=1.54] | s=d=%03d s=%s c=%c f=%4.2f}) Val "d=009 s=ab c=x f=1.54"
>>>pl @(PrintT "d=%03d s=%s" Id) (9, "ab",'x',1.54)Error PrintI(IO e=printf: formatting string ended prematurely) (PrintI d=%03d s=%s | (1.54,('x',("ab",(9,()))))) Fail "PrintI(IO e=printf: formatting string ended prematurely)"
>>>pl @(PrintT "lhs = %d rhs = %s c=%d" Id) (123,"asdf",'x')Present "lhs = 123 rhs = asdf c=120" ((>>) "lhs = 123 rhs = asdf c=120" | {PrintI [lhs = 123 rhs = asdf c=120] | s=lhs = %d rhs = %s c=%d}) Val "lhs = 123 rhs = asdf c=120"
>>>pl @(PrintT "hello d=%d %c %s" '(12, C "z", "someval")) ()Present "hello d=12 z someval" ((>>) "hello d=12 z someval" | {PrintI [hello d=12 z someval] | s=hello d=%d %c %s}) Val "hello d=12 z someval"
>>>pl @(PrintT "ipaddress %03d.%03d.%03d.%03d" '(1,2,3,4)) ()Present "ipaddress 001.002.003.004" ((>>) "ipaddress 001.002.003.004" | {PrintI [ipaddress 001.002.003.004] | s=ipaddress %03d.%03d.%03d.%03d}) Val "ipaddress 001.002.003.004"
prints inductive tuples in reverse order
>>>pz @(PrintI "d=%d s=%s f=%f") (1.73,("abc",(12,())))Val "d=12 s=abc f=1.73"
>>>pz @(PrintI "d=%d s=%s f=%f") ("abc",(12,()))Fail "PrintI(IO e=printf: argument list ended prematurely)"
>>>pz @(PrintI "d=%s s=%d") ("abc",('x',()))Fail "PrintI(IO e=printf: bad formatting char 's')"
>>>pz @(PrintI "%s %s %d") (123,("sss",("bb",())))Val "bb sss 123"