1:- module(tw_reset, [reset_style/1]).    2
    3:- use_module(library(css_write), [write_css/2, css//1]).    4
    5% adapted from https://github.com/green-coder/girouette/blob/master/lib/girouette/src/girouette/tw/preflight.cljc
    6% tailwindcss v2.0.3 | MIT License | https://tailwindcss.com
    7% modern-normalize v1.0.0 | MIT License | https://github.com/sindresorhus/modern-normalize
    8reset_style(Style) :-
    9    write_css(
   10        css(['*, ::before, ::after'('box-sizing'("border-box")),
   11
   12             '.root'(['-moz-tab-size'(4), 'tab-size'(4)]),
   13
   14             'html'('-webkit-text-size-adjust'("100%")),
   15
   16             'body'(margin(0)),
   17
   18             'body'('font-family'("system-ui, apple-system, 'Segoe UI', Roboto, Helvetica, Arial, sans-serif, 'Apple Color Emoji', 'Segoe UI Emoji'")),
   19
   20             hr([height(0), color(inherit), 'border-top-width'("1px")]),
   21
   22             'abbr, [title]'(['-webkit-text-decoration'("underline dotted"),
   23                            'text-decoration'("underline dotted")]),
   24
   25             'b, strong'('font-weight'(bolder)),
   26
   27             'code, kbd, samp, pre'(['font-family'("ui-monospace, SFMono-Regular, Consolas, 'Liberation Mono', Menlo, monospace"),
   28                                     'font-size'("1em")]),
   29
   30             small('font-size'("80%")),
   31
   32             'sub, sup'(['font-size'("75%"),
   33                         'line-height'(0),
   34                         position(relative),
   35                         'vertical-align'(baseline)]),
   36             sub(bottom("-0.25em")),
   37             sup(top("-0.5em")),
   38
   39             table(['text-indent'(0), 'border-color'(inherit)]),
   40
   41             'button, input, optgroup, select, textarea'(
   42                 ['font-family'(inherit),
   43                  'font-size'("100%"),
   44                  'line-height'("1.15"),
   45                  'margin'(0)
   46                 ]),
   47
   48             'button, select'('text-transform'(none)),
   49
   50             'button, [type="button"], [type="reset"], [type="submit"]'(
   51                 '-webkit-appearance'(button)
   52             ),
   53
   54             '::-moz-focus-inner'(['border-style'(none), padding(0)]),
   55
   56             ':-moz-focusring'(outline("1px dotted ButtonText")),
   57
   58             ':-moz-ui-invalid'('box-shadow'(none)),
   59
   60             legend(padding(0)),
   61
   62             progress('vertical-align'(baseline)),
   63
   64             '::-webkit-inner-spin-button, ::-webkit-outer-spin-button'(height(auto)),
   65
   66             '[type="search"]'(['-webkit-appearance'(textfield),
   67                                'outline-offset'("-2px")]),
   68
   69             '::-webkit-file-upload-button'(['-webkit-appearance'(button),
   70                                             font(inherit)]),
   71
   72             summary(display("list-item")),
   73
   74             'blockquote, dl, dd, h1, h2, h3, h4, h5, h6, hr, figure, p, pre'(
   75                 margin(0)
   76             ),
   77
   78             button(['background-color'(transparent), 'background-image'(none)]),
   79
   80             'button:focus'([outline("1px dotted"),
   81                             outline("5px auto -webkit-focus-ring-color")]),
   82
   83             fieldset([margin(0), padding(0)]),
   84
   85             'ol, ul'(['list-style'(none), margin(0), padding(0)]),
   86
   87             % another font change & line-height?
   88
   89             html(['font-family'(inherit), 'line-height'(inherit)]),
   90
   91             '*, ::before, ::after'(['border-width'(0),
   92                                     'border-style'(solid),
   93                                     'border-color'("#e5e7eb")]),
   94
   95             hr('border-top-width'("1px")),
   96
   97             textarea(resize(vertical)),
   98
   99             'input::placeholder, textarea::placeholder'(
  100                 [opacity(1), color("#9ca3af")]
  101             ),
  102
  103             'button, [role="button"]'(cursor(pointer)),
  104
  105             table('border-collapse'(collapse)),
  106
  107             'h1,h2,h3,h4,h5,h6'(['font-size'(inherit), 'font-weight'(inherit)]),
  108
  109             a([color(inherit), 'text-decoration'(inherit)]),
  110
  111             'button, input, optgroup, select, textarea'(
  112                 [padding(0), 'line-height'(inherit), color(inherit)]
  113             ),
  114
  115             'img, video'(['max-width'("100%"), height(auto)])
  116
  117            ]),
  118        Style
  119    )