HsYAML-0.2.1.0: Pure Haskell YAML 1.2 processor

Copyright© Herbert Valerio Riedel 2015-2018
LicenseGPL-2.0-or-later
Safe HaskellSafe
LanguageHaskell2010

Data.YAML.Event

Contents

Description

Event-stream oriented YAML parsing and serializing API

Synopsis

Tutorial

Data.YAML module provides us with API which allow us to interact with YAML data at the cost of some presentation details. In contrast, this module provide us with API which gives us access to a other significant details like ScalarStyles, NodeStyles, Comments, etc.

Parsing YAML Documents

Suppose you want to parse this YAML Document while preserving its format and comments

# Home runs
hr:  65
# Runs Batted In
rbi: 147

then you might want to use the function parseEvents.

The following is a reference implementation of a function using parseEvents. It takes a YAML document as input and prints the parsed YAML Events.

import Data.YAML.Event
import qualified Data.ByteString.Lazy as BS.L

printEvents :: BS.L.ByteString -> IO ()
printEvents input =
  forM_ (parseEvents input) $ ev -> case ev of
    Left _ -> error "Failed to parse"
    Right event -> print (eEvent event)

When we pass the above mentioned YAML document to the function printEvents it outputs the following:

StreamStart
DocumentStart NoDirEndMarker
MappingStart Nothing Nothing Block
Comment " Home runs"
Scalar Nothing Nothing Plain "hr"
Scalar Nothing Nothing Plain "65"
Comment " Runs Batted In"
Scalar Nothing Nothing Plain "rbi"
Scalar Nothing Nothing Plain "147"
MappingEnd
DocumentEnd False
StreamEnd

Notice that now we have all the necessary details in the form of Events.

We can now write simple functions to work with this data without losing any more details.

parseEvents :: ByteString -> EvStream Source #

Parse YAML Events from a lazy ByteString.

The parsed Events allow us to round-trip at the event-level while preserving many features and presentation details like Comments,ScalarStyle,NodeStyle, Anchors, Directives marker along with YAML document version, Chomping Indicator,Indentation Indicator (IndentOfs) ,ordering, etc. It does not preserve non-content white spaces.

The input ByteString is expected to have a YAML 1.2 stream using the UTF-8, UTF-16 (LE or BE), or UTF-32 (LE or BE) encodings (which will be auto-detected).

Serializing Events to YAML Character Stream

Now, suppose we want to generate back the YAML document after playing with the Event-stream, then you might want to use writeEvents.

The following function takes a YAML document as a input and dumps it back to STDOUT after a round-trip.

import Data.YAML.Event
import qualified Data.YAML.Token as YT
import qualified Data.ByteString.Lazy as BS.L

yaml2yaml :: BS.L.ByteString -> IO ()
yaml2yaml input = case sequence $ parseEvents input of
    Left _ -> error "Parsing Failure!"
    Right events -> do
      BS.L.hPutStr stdout (writeEvents YT.UTF8 (map eEvent events))
      hFlush stdout

Let this be the sample document passed to the above function

# This is a Directives Marker
---
# All Comments are preserved
date    : 2019-07-12
bill-to : # Anchor represents a map node
   &id001
    address:
        lines: # This a Block Scalar with Keep chomping Indicator and IndentAuto Indentant indicator
                |+ # Extra Indentation (non-content white space) will not be preserved
                      Vijay
                      IIT Hyderabad


        # Trailing newlines are a preserved here as they are a part of the Scalar node
        country    : India
ship-to  : # This is an Alias
           *id001
# Key is a Scalar and Value is a Sequence
Other Details:
          total: $ 3000
          # Tags are also preserved
          Online Payment: !!bool True
          product:
              - Item1
              # This comment is inside a Sequence
              - Item2
...
# DocumentEnd True
# StreamEnd

This function outputs the following

# This is a Directives Marker
---
# All Comments are preserved
date: 2019-07-12
bill-to: # Anchor represents a map node
  &id001
  address:
    lines: # This a Block Scalar with Keep chomping Indicator and IndentAuto Indentant indicator
      # Extra Indentation (non-content white space) will not be preserved
      |+
      Vijay
      IIT Hyderabad


    # Trailing newlines are a preserved here as they are a part of the Scalar node
    country: India
ship-to: # This is an Alias
  *id001
# Key is a Scalar and Value is a Sequence
Other Details:
  total: $ 3000
  # Tags are also preserved
  Online Payment: !!bool True
  product:
  - Item1
  # This comment is inside a Sequence
  - Item2
...
# DocumentEnd True
# StreamEnd

writeEvents :: Encoding -> [Event] -> ByteString Source #

Serialise Events using specified UTF encoding to a lazy ByteString

NOTE: This function is only well-defined for valid Event streams

Since: 0.2.0.0

writeEventsText :: [Event] -> Text Source #

Serialise Events to lazy Text

NOTE: This function is only well-defined for valid Event streams

Since: 0.2.0.0

How to comment your yaml document for best results

Round-tripping at event-level will preserve all the comments and their relative position in the YAML-document but still, we lose some information like the exact indentation and the position at which the comments were present previously. This information sometimes can be quiet important for human-perception of comments. Below are some guildlines, so that you can avoid ambiguities.

1) Always try to start your comment in a newline. This step will avoid most of the ambiguities.

2) Comments automaticly get indented according to the level in which they are present. For example,

Input YAML-document

# Level 0
- a
# Level 0
- - a
# Level 1
  - a
  - - a
# Level 2
    - a

After a round-trip looks like

# Level 0
- a
# Level 0
- - a
  # Level 1
  - a
  - - a
    # Level 2
    - a

3) Comments immediately after a Scalar node, start from a newline. So avoid commenting just after a scalar ends, as it may lead to some ambiguity. For example,

Input YAML-document

- scalar # After scalar
- random  : scalar # After scalar
  key: 1
# not after scalar
- random  : scalar
  key: 1
- random  : # not after scalar
            scalar
  # not after scalar
  key: 1

After a round-trip looks like

- scalar
# After scalar
- random: scalar
  # After scalar
  key: 1
  # not after scalar
- random: scalar
  key: 1
- random: # not after scalar
    scalar
  # not after scalar
  key: 1

4) Similarly in flow-style, avoid commenting immediately after a comma (,) seperator. Comments immediately after a comma (,) seperator will start from a new line

Input YAML-document

{
    # comment 0
    Name: Vijay # comment 1
    ,
    # comment 2
    age: 19, # comment 3
    # comment 4
    country: India # comment 5
}

After a round-trip looks like

{
  # comment 0
  Name: Vijay,
  # comment 1
  # comment 2
  age: 19,
  # comment 3
  # comment 4
  country: India,
  # comment 5
}

5) Avoid commenting in between syntatical elements. For example,

Input YAML-document

? # Complex key starts
  [
     a,
     b
  ]
 # Complex key ends
: # Complex Value starts
  ? # Complex key starts
    [
       a,
       b
    ]
    # Complex key ends
  : # Simple value
    a
  # Complex value ends

After a round-trip looks like

? # Complex key starts
  [
     a,
     b
 ]
: # Complex key ends
  # Complex Value starts

  ? # Complex key starts
    [
       a,
       b
   ]
  : # Complex key ends
    # Simple value
    a
  # Complex value ends

The above two YAML-documents, after parsing produce the same Event-stream.

So, these are some limitation of this Format-preserving YAML processor.

Event-stream Internals

type EvStream = [Either (Pos, String) EvPos] Source #

Event stream produced by parseEvents

A Left value denotes parsing errors. The event stream ends immediately once a Left value is returned.

data Event Source #

YAML Event Types

The events correspond to the ones from LibYAML

The grammar below defines well-formed streams of Events:

stream   ::= StreamStart document* StreamEnd
document ::= DocumentStart node DocumentEnd
node     ::= Alias
           | Scalar
           | Comment
           | sequence
           | mapping
sequence ::= SequenceStart node* SequenceEnd
mapping  ::= MappingStart (node node)* MappingEnd

Since: 0.2.0

Instances
Eq Event Source # 
Instance details

Defined in Data.YAML.Event.Internal

Methods

(==) :: Event -> Event -> Bool #

(/=) :: Event -> Event -> Bool #

Show Event Source # 
Instance details

Defined in Data.YAML.Event.Internal

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 
Instance details

Defined in Data.YAML.Event.Internal

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

NFData Event Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Event.Internal

Methods

rnf :: Event -> () #

type Rep Event Source # 
Instance details

Defined in Data.YAML.Event.Internal

type Rep Event = D1 (MetaData "Event" "Data.YAML.Event.Internal" "HsYAML-0.2.1.0-3n04Fs6nDN3CMPVb0vyYIF" False) (((C1 (MetaCons "StreamStart" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StreamEnd" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "DocumentStart" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Directives)) :+: (C1 (MetaCons "DocumentEnd" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)) :+: C1 (MetaCons "Comment" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))) :+: ((C1 (MetaCons "Alias" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Anchor)) :+: (C1 (MetaCons "Scalar" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Anchor)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Tag)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ScalarStyle) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) :+: C1 (MetaCons "SequenceStart" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Anchor)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Tag) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 NodeStyle))))) :+: (C1 (MetaCons "SequenceEnd" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MappingStart" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Anchor)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Tag) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 NodeStyle))) :+: C1 (MetaCons "MappingEnd" PrefixI False) (U1 :: Type -> Type)))))

data EvPos Source #

Event with corresponding Pos in YAML stream

Since: 0.2.0

Constructors

EvPos 

Fields

Instances
Eq EvPos Source # 
Instance details

Defined in Data.YAML.Event.Internal

Methods

(==) :: EvPos -> EvPos -> Bool #

(/=) :: EvPos -> EvPos -> Bool #

Show EvPos Source # 
Instance details

Defined in Data.YAML.Event.Internal

Methods

showsPrec :: Int -> EvPos -> ShowS #

show :: EvPos -> String #

showList :: [EvPos] -> ShowS #

Generic EvPos Source # 
Instance details

Defined in Data.YAML.Event.Internal

Associated Types

type Rep EvPos :: Type -> Type #

Methods

from :: EvPos -> Rep EvPos x #

to :: Rep EvPos x -> EvPos #

NFData EvPos Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Event.Internal

Methods

rnf :: EvPos -> () #

type Rep EvPos Source # 
Instance details

Defined in Data.YAML.Event.Internal

type Rep EvPos = D1 (MetaData "EvPos" "Data.YAML.Event.Internal" "HsYAML-0.2.1.0-3n04Fs6nDN3CMPVb0vyYIF" False) (C1 (MetaCons "EvPos" PrefixI True) (S1 (MetaSel (Just "eEvent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Event) :*: S1 (MetaSel (Just "ePos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Pos)))

data Directives Source #

Encodes document %YAML directives and the directives end-marker

Since: 0.2.0

Constructors

NoDirEndMarker

no directives and also no --- marker

DirEndMarkerNoVersion

--- marker present, but no explicit %YAML directive present

DirEndMarkerVersion !Word

--- marker present, as well as a %YAML 1.mi version directive; the minor version mi is stored in the Word field.

Instances
Eq Directives Source # 
Instance details

Defined in Data.YAML.Event.Internal

Show Directives Source # 
Instance details

Defined in Data.YAML.Event.Internal

Generic Directives Source # 
Instance details

Defined in Data.YAML.Event.Internal

Associated Types

type Rep Directives :: Type -> Type #

NFData Directives Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Event.Internal

Methods

rnf :: Directives -> () #

type Rep Directives Source # 
Instance details

Defined in Data.YAML.Event.Internal

type Rep Directives = D1 (MetaData "Directives" "Data.YAML.Event.Internal" "HsYAML-0.2.1.0-3n04Fs6nDN3CMPVb0vyYIF" False) (C1 (MetaCons "NoDirEndMarker" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "DirEndMarkerNoVersion" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DirEndMarkerVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word))))

data ScalarStyle Source #

Scalar-specific node style

This can be considered a more granular superset of NodeStyle. See also scalarNodeStyle.

Since: 0.2.0

Instances
Eq ScalarStyle Source # 
Instance details

Defined in Data.YAML.Event.Internal

Ord ScalarStyle Source # 
Instance details

Defined in Data.YAML.Event.Internal

Show ScalarStyle Source # 
Instance details

Defined in Data.YAML.Event.Internal

Generic ScalarStyle Source # 
Instance details

Defined in Data.YAML.Event.Internal

Associated Types

type Rep ScalarStyle :: Type -> Type #

NFData ScalarStyle Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Event.Internal

Methods

rnf :: ScalarStyle -> () #

type Rep ScalarStyle Source # 
Instance details

Defined in Data.YAML.Event.Internal

data NodeStyle Source #

Node style

Since: 0.2.0

Constructors

Flow 
Block 
Instances
Eq NodeStyle Source # 
Instance details

Defined in Data.YAML.Event.Internal

Ord NodeStyle Source # 
Instance details

Defined in Data.YAML.Event.Internal

Show NodeStyle Source # 
Instance details

Defined in Data.YAML.Event.Internal

Generic NodeStyle Source # 
Instance details

Defined in Data.YAML.Event.Internal

Associated Types

type Rep NodeStyle :: Type -> Type #

NFData NodeStyle Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Event.Internal

Methods

rnf :: NodeStyle -> () #

type Rep NodeStyle Source # 
Instance details

Defined in Data.YAML.Event.Internal

type Rep NodeStyle = D1 (MetaData "NodeStyle" "Data.YAML.Event.Internal" "HsYAML-0.2.1.0-3n04Fs6nDN3CMPVb0vyYIF" False) (C1 (MetaCons "Flow" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Block" PrefixI False) (U1 :: Type -> Type))

data Chomp Source #

Constructors

Strip

Remove all trailing line breaks and shows the presence of - chomping indicator.

Clip

Keep first trailing line break; this also the default behavior used if no explicit chomping indicator is specified.

Keep

Keep all trailing line breaks and shows the presence of + chomping indicator.

Instances
Eq Chomp Source # 
Instance details

Defined in Data.YAML.Event.Internal

Methods

(==) :: Chomp -> Chomp -> Bool #

(/=) :: Chomp -> Chomp -> Bool #

Ord Chomp Source # 
Instance details

Defined in Data.YAML.Event.Internal

Methods

compare :: Chomp -> Chomp -> Ordering #

(<) :: Chomp -> Chomp -> Bool #

(<=) :: Chomp -> Chomp -> Bool #

(>) :: Chomp -> Chomp -> Bool #

(>=) :: Chomp -> Chomp -> Bool #

max :: Chomp -> Chomp -> Chomp #

min :: Chomp -> Chomp -> Chomp #

Show Chomp Source # 
Instance details

Defined in Data.YAML.Event.Internal

Methods

showsPrec :: Int -> Chomp -> ShowS #

show :: Chomp -> String #

showList :: [Chomp] -> ShowS #

Generic Chomp Source # 
Instance details

Defined in Data.YAML.Event.Internal

Associated Types

type Rep Chomp :: Type -> Type #

Methods

from :: Chomp -> Rep Chomp x #

to :: Rep Chomp x -> Chomp #

NFData Chomp Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Event.Internal

Methods

rnf :: Chomp -> () #

type Rep Chomp Source # 
Instance details

Defined in Data.YAML.Event.Internal

type Rep Chomp = D1 (MetaData "Chomp" "Data.YAML.Event.Internal" "HsYAML-0.2.1.0-3n04Fs6nDN3CMPVb0vyYIF" False) (C1 (MetaCons "Strip" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Clip" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Keep" PrefixI False) (U1 :: Type -> Type)))

data IndentOfs Source #

Block Indentation Indicator

IndentAuto is the special case for auto Block Indentation Indicator

Since: 0.2.0

Instances
Enum IndentOfs Source # 
Instance details

Defined in Data.YAML.Event.Internal

Eq IndentOfs Source # 
Instance details

Defined in Data.YAML.Event.Internal

Ord IndentOfs Source # 
Instance details

Defined in Data.YAML.Event.Internal

Show IndentOfs Source # 
Instance details

Defined in Data.YAML.Event.Internal

Generic IndentOfs Source # 
Instance details

Defined in Data.YAML.Event.Internal

Associated Types

type Rep IndentOfs :: Type -> Type #

NFData IndentOfs Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Event.Internal

Methods

rnf :: IndentOfs -> () #

type Rep IndentOfs Source # 
Instance details

Defined in Data.YAML.Event.Internal

type Rep IndentOfs = D1 (MetaData "IndentOfs" "Data.YAML.Event.Internal" "HsYAML-0.2.1.0-3n04Fs6nDN3CMPVb0vyYIF" False) (((C1 (MetaCons "IndentAuto" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IndentOfs1" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "IndentOfs2" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "IndentOfs3" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IndentOfs4" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "IndentOfs5" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IndentOfs6" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "IndentOfs7" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "IndentOfs8" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IndentOfs9" PrefixI False) (U1 :: Type -> Type)))))

data Tag Source #

YAML Tags

Instances
Eq Tag Source # 
Instance details

Defined in Data.YAML.Event.Internal

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Ord Tag Source # 
Instance details

Defined in Data.YAML.Event.Internal

Methods

compare :: Tag -> Tag -> Ordering #

(<) :: Tag -> Tag -> Bool #

(<=) :: Tag -> Tag -> Bool #

(>) :: Tag -> Tag -> Bool #

(>=) :: Tag -> Tag -> Bool #

max :: Tag -> Tag -> Tag #

min :: Tag -> Tag -> Tag #

Show Tag Source # 
Instance details

Defined in Data.YAML.Event.Internal

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 
Instance details

Defined in Data.YAML.Event.Internal

Associated Types

type Rep Tag :: Type -> Type #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

NFData Tag Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Event.Internal

Methods

rnf :: Tag -> () #

type Rep Tag Source # 
Instance details

Defined in Data.YAML.Event.Internal

type Rep Tag = D1 (MetaData "Tag" "Data.YAML.Event.Internal" "HsYAML-0.2.1.0-3n04Fs6nDN3CMPVb0vyYIF" True) (C1 (MetaCons "Tag" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

untagged :: Tag Source #

An "untagged" YAML tag

isUntagged :: Tag -> Bool Source #

Equivalent to (== untagged)

tagToText :: Tag -> Maybe Text Source #

Convert Tag to its string representation

Returns Nothing for untagged

mkTag :: String -> Tag Source #

Construct YAML tag

type Anchor = Text Source #

YAML Anchor identifiers

data Pos Source #

Position in parsed YAML source

See also prettyPosWithSource.

NOTE: if posCharOffset is negative the Pos value doesn't refer to a proper location; this may be emitted in corner cases when no proper location can be inferred.

Constructors

Pos 

Fields

Instances
Eq Pos Source # 
Instance details

Defined in Data.YAML.Pos

Methods

(==) :: Pos -> Pos -> Bool #

(/=) :: Pos -> Pos -> Bool #

Show Pos Source # 
Instance details

Defined in Data.YAML.Pos

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Generic Pos Source # 
Instance details

Defined in Data.YAML.Pos

Associated Types

type Rep Pos :: Type -> Type #

Methods

from :: Pos -> Rep Pos x #

to :: Rep Pos x -> Pos #

NFData Pos Source #

Since: 0.2.0

Instance details

Defined in Data.YAML.Pos

Methods

rnf :: Pos -> () #

type Rep Pos Source # 
Instance details

Defined in Data.YAML.Pos

type Rep Pos = D1 (MetaData "Pos" "Data.YAML.Pos" "HsYAML-0.2.1.0-3n04Fs6nDN3CMPVb0vyYIF" False) (C1 (MetaCons "Pos" PrefixI True) ((S1 (MetaSel (Just "posByteOffset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "posCharOffset") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :*: (S1 (MetaSel (Just "posLine") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "posColumn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))))