{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
module BNFC.Backend.Agda (makeAgda) where
import Prelude hiding ((<>))
import Control.Monad.State hiding (when)
import Data.Bifunctor (second)
import Data.Char
import Data.Function (on)
import qualified Data.List as List
import Data.List.NonEmpty (NonEmpty((:|)))
import qualified Data.List.NonEmpty as List1
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Maybe
import Data.Set (Set)
import qualified Data.Set as Set
import Data.String (IsString)
import BNFC.CF
import BNFC.Backend.Base                 (Backend, mkfile)
import BNFC.Backend.Haskell.HsOpts
import BNFC.Backend.Haskell.CFtoAbstract (DefCfg(..), definedRules')
import BNFC.Backend.Haskell.Utils        (parserName, catToType, comment)
import BNFC.Options                      (SharedOptions, TokenText(..), tokenText, functor)
import BNFC.PrettyPrint
import BNFC.Utils                        (ModuleName, replace, when, table)
data ConstructorStyle
  = UnnamedArg  
  | NamedArg    
data ImportNumeric
  = YesImportNumeric  
  | NoImportNumeric   
  deriving (ImportNumeric -> ImportNumeric -> Bool
(ImportNumeric -> ImportNumeric -> Bool)
-> (ImportNumeric -> ImportNumeric -> Bool) -> Eq ImportNumeric
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImportNumeric -> ImportNumeric -> Bool
== :: ImportNumeric -> ImportNumeric -> Bool
$c/= :: ImportNumeric -> ImportNumeric -> Bool
/= :: ImportNumeric -> ImportNumeric -> Bool
Eq)
makeAgda
  :: String         
  -> SharedOptions  
  -> CF             
  -> Backend
makeAgda :: String -> SharedOptions -> CF -> Backend
makeAgda String
time SharedOptions
opts CF
cf = do
  
  String -> MakeComment -> Doc -> Backend
forall c. FileContent c => String -> MakeComment -> c -> Backend
mkfile (SharedOptions -> String
agdaASTFile SharedOptions
opts) MakeComment
comment (Doc -> Backend) -> Doc -> Backend
forall a b. (a -> b) -> a -> b
$
    String
-> Bool -> TokenText -> String -> String -> String -> CF -> Doc
cf2AgdaAST String
time (SharedOptions -> Bool
functor SharedOptions
opts) (SharedOptions -> TokenText
tokenText SharedOptions
opts) (SharedOptions -> String
agdaASTFileM SharedOptions
opts) (SharedOptions -> String
absFileM SharedOptions
opts) (SharedOptions -> String
printerFileM SharedOptions
opts) CF
cf
  
  String -> MakeComment -> Doc -> Backend
forall c. FileContent c => String -> MakeComment -> c -> Backend
mkfile (SharedOptions -> String
agdaParserFile SharedOptions
opts) MakeComment
comment (Doc -> Backend) -> Doc -> Backend
forall a b. (a -> b) -> a -> b
$
    String
-> TokenText
-> String
-> String
-> String
-> String
-> Maybe String
-> [Cat]
-> Doc
cf2AgdaParser String
time (SharedOptions -> TokenText
tokenText SharedOptions
opts) (SharedOptions -> String
agdaParserFileM SharedOptions
opts) (SharedOptions -> String
agdaASTFileM SharedOptions
opts) (SharedOptions -> String
errFileM SharedOptions
opts) (SharedOptions -> String
happyFileM SharedOptions
opts)
      Maybe String
layoutMod
      [Cat]
parserCats
  
  String -> MakeComment -> Doc -> Backend
forall c. FileContent c => String -> MakeComment -> c -> Backend
mkfile (SharedOptions -> String
agdaLibFile SharedOptions
opts) MakeComment
comment (Doc -> Backend) -> Doc -> Backend
forall a b. (a -> b) -> a -> b
$
    String -> Doc
agdaLibContents (SharedOptions -> String
agdaLibFileM SharedOptions
opts)
  
  String -> MakeComment -> Doc -> Backend
forall c. FileContent c => String -> MakeComment -> c -> Backend
mkfile (SharedOptions -> String
agdaMainFile SharedOptions
opts) MakeComment
comment (Doc -> Backend) -> Doc -> Backend
forall a b. (a -> b) -> a -> b
$
    String -> String -> String -> String -> Bool -> Cat -> Doc
agdaMainContents (SharedOptions -> String
agdaMainFileM SharedOptions
opts) (SharedOptions -> String
agdaLibFileM SharedOptions
opts) (SharedOptions -> String
agdaASTFileM SharedOptions
opts) (SharedOptions -> String
agdaParserFileM SharedOptions
opts)
      (CF -> Bool
hasLayout CF
cf)
      (CF -> Cat
firstEntry CF
cf)
  where
  
  
  parserCats :: [Cat]
  parserCats :: [Cat]
parserCats = NonEmpty Cat -> [Cat]
forall a. NonEmpty a -> [a]
List1.toList (NonEmpty Cat -> [Cat]) -> NonEmpty Cat -> [Cat]
forall a b. (a -> b) -> a -> b
$ CF -> NonEmpty Cat
forall f. CFG f -> NonEmpty Cat
allEntryPoints CF
cf
  
  layoutMod :: Maybe String
  layoutMod :: Maybe String
layoutMod = Bool -> Maybe String -> Maybe String
forall m. Monoid m => Bool -> m -> m
when (CF -> Bool
hasLayout CF
cf) (Maybe String -> Maybe String) -> Maybe String -> Maybe String
forall a b. (a -> b) -> a -> b
$ String -> Maybe String
forall a. a -> Maybe a
Just (SharedOptions -> String
layoutFileM SharedOptions
opts)
cf2AgdaAST
  :: String  
  -> Bool    
  -> TokenText
  -> String  
  -> String  
  -> String  
  -> CF      
  -> Doc
cf2AgdaAST :: String
-> Bool -> TokenText -> String -> String -> String -> CF -> Doc
cf2AgdaAST String
time Bool
havePos TokenText
tokenText String
mod String
amod String
pmod CF
cf = [Doc] -> Doc
vsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$
  [ String -> String -> Doc
preamble String
time String
"abstract syntax data types"
  , [Doc] -> Doc
hsep [ Doc
"module", String -> Doc
text String
mod, Doc
"where" ]
  , ImportNumeric -> Bool -> Bool -> Bool -> Doc
imports ImportNumeric
YesImportNumeric Bool
False Bool
usesPos Bool
havePos
  , Bool -> Doc -> Doc
forall m. Monoid m => Bool -> m -> m
when Bool
usesString (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
hsep [ Doc
"String", Doc
equals, Doc
forall a. IsString a => a
listT, Doc
forall a. IsString a => a
charT ]
  , TokenText -> Bool -> [String] -> Doc
importPragmas TokenText
tokenText Bool
usesPos
      [ [String] -> String
unwords [ String
"qualified", String
amod ]
      , [String] -> String
unwords [ String
pmod, String
"(printTree)" ]
      ]
  , Bool -> Doc -> Doc
forall m. Monoid m => Bool -> m -> m
when Bool
usesPos Doc
defineIntAndPair
  , Bool -> Doc -> Doc
forall m. Monoid m => Bool -> m -> m
when Bool
havePos Doc
defineBNFCPosition
  , [Doc] -> Doc
vsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ ((String, Bool) -> Doc) -> [(String, Bool)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> Bool -> Doc) -> (String, Bool) -> Doc
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((String -> Bool -> Doc) -> (String, Bool) -> Doc)
-> (String -> Bool -> Doc) -> (String, Bool) -> Doc
forall a b. (a -> b) -> a -> b
$ String -> TokenText -> String -> Bool -> Doc
prToken String
amod TokenText
tokenText) [(String, Bool)]
tcats
  , String -> Bool -> ConstructorStyle -> [Data] -> Doc
absyn String
amod Bool
havePos ConstructorStyle
NamedArg [Data]
dats
  , Bool -> CF -> Doc
definedRules Bool
havePos CF
cf
  
  , String -> [Cat] -> Doc
printers String
amod [Cat]
printerCats
  , Doc
empty 
  ]
  where
  
  dats :: [Data]
  dats :: [Data]
dats = CF -> [Data]
cf2data CF
cf
         
  
  tcats :: [(TokenCat, Bool)]
  tcats :: [(String, Bool)]
tcats = (if CF -> Bool
forall f. CFG f -> Bool
hasIdent CF
cf then ((String
catIdent, Bool
False) (String, Bool) -> [(String, Bool)] -> [(String, Bool)]
forall a. a -> [a] -> [a]
:) else [(String, Bool)] -> [(String, Bool)]
forall a. a -> a
id)
    [ (WithPosition String -> String
forall a. WithPosition a -> a
wpThing WithPosition String
name, Bool
b) | TokenReg WithPosition String
name Bool
b Reg
_ <- CF -> [Pragma]
forall function. CFG function -> [Pragma]
cfgPragmas CF
cf ]
  
  printerCats :: [Cat]
  printerCats :: [Cat]
printerCats = [[Cat]] -> [Cat]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    [ (Data -> Cat) -> [Data] -> [Cat]
forall a b. (a -> b) -> [a] -> [b]
map Data -> Cat
forall a b. (a, b) -> a
fst (CF -> [Data]
getAbstractSyntax CF
cf)
    , (String -> Cat) -> [String] -> [Cat]
forall a b. (a -> b) -> [a] -> [b]
map String -> Cat
TokenCat ([String] -> [Cat]) -> [String] -> [Cat]
forall a b. (a -> b) -> a -> b
$ [String] -> [String]
forall a. Eq a => [a] -> [a]
List.nub ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ CF -> [String]
forall function. CFG function -> [String]
cfgLiterals CF
cf [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ ((String, Bool) -> String) -> [(String, Bool)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String, Bool) -> String
forall a b. (a, b) -> a
fst [(String, Bool)]
tcats
    ]
  usesString :: Bool
usesString = String
"String" String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` CF -> [String]
forall function. CFG function -> [String]
cfgLiterals CF
cf
  usesPos :: Bool
usesPos    = Bool
havePos Bool -> Bool -> Bool
|| CF -> Bool
forall f. CFG f -> Bool
hasPositionTokens CF
cf
  defineIntAndPair :: Doc
defineIntAndPair = [Doc] -> Doc
vsep
    [ [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ [[Doc]] -> [Doc]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
      [ [ Doc
"postulate" ]
      , (String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Doc -> Doc
nest Int
2 (Doc -> Doc) -> (String -> Doc) -> String -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Doc
text) ([String] -> [Doc]) -> [String] -> [Doc]
forall a b. (a -> b) -> a -> b
$ String -> [[String]] -> [String]
table String
" "
        [ [ String
forall a. IsString a => a
intT,      String
":", String
"Set" ]
        , [ String
forall a. IsString a => a
intToNatT, String
":", String
forall a. IsString a => a
intT, String
forall a. IsString a => a
uArrow , String
forall a. IsString a => a
natT ]
        , [ String
forall a. IsString a => a
natToIntT, String
":", String
forall a. IsString a => a
natT, String
forall a. IsString a => a
uArrow , String
forall a. IsString a => a
intT ]
        ]
      ]
    , [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (\ String
s -> [Doc] -> Doc
hsep [ Doc
"{-#", Doc
"COMPILE", Doc
"GHC", String -> Doc
text String
s, Doc
"#-}" ]) ([String] -> [Doc]) -> [String] -> [Doc]
forall a b. (a -> b) -> a -> b
$
        String -> [[String]] -> [String]
table String
" = "
        [ [ String
forall a. IsString a => a
intT,      String
"type Prelude.Int"    ]
        , [ String
forall a. IsString a => a
intToNatT, String
"Prelude.toInteger"   ]
        , [ String
forall a. IsString a => a
natToIntT, String
"Prelude.fromInteger" ]
        ]
    , [Doc] -> Doc
vcat
      [ Doc
"data #Pair (A B : Set) : Set where"
      , Int -> Doc -> Doc
nest Int
2 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Doc
"#pair : A → B → #Pair A B"
      ]
    , Doc
"{-# COMPILE GHC #Pair = data (,) ((,)) #-}"
    ]
  defineBNFCPosition :: Doc
defineBNFCPosition =
    [Doc] -> Doc
hsep [ Doc
forall a. IsString a => a
posT, Doc
equals, Doc
forall a. IsString a => a
maybeT, Doc -> Doc
parens Doc
intPairT ]
cf2AgdaParser
  :: String  
  -> TokenText
  -> String  
  -> String  
  -> String  
  -> String  
  -> Maybe String
             
  -> [Cat]   
  -> Doc
cf2AgdaParser :: String
-> TokenText
-> String
-> String
-> String
-> String
-> Maybe String
-> [Cat]
-> Doc
cf2AgdaParser String
time TokenText
tokenText String
mod String
astmod String
emod String
pmod Maybe String
layoutMod [Cat]
cats = [Doc] -> Doc
vsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$
  [ String -> String -> Doc
preamble String
time String
"parsers"
  , [Doc] -> Doc
hsep [ Doc
"module", String -> Doc
text String
mod, Doc
"where" ]
  , ImportNumeric -> Bool -> Bool -> Bool -> Doc
imports ImportNumeric
NoImportNumeric (Maybe String -> Bool
forall a. Maybe a -> Bool
isJust Maybe String
layoutMod) Bool
False Bool
False
  , String -> [String] -> Doc
importCats String
astmod ([String] -> [String]
forall a. Eq a => [a] -> [a]
List.nub [String]
cs)
  , TokenText -> Bool -> [String] -> Doc
importPragmas TokenText
tokenText Bool
False ([String] -> Doc) -> [String] -> Doc
forall a b. (a -> b) -> a -> b
$ [ MakeComment
qual String
emod, String
pmod] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ Maybe String -> [String]
forall a. Maybe a -> [a]
maybeToList (MakeComment
qual MakeComment -> Maybe String -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
layoutMod)
  , Doc
"-- Error monad of BNFC"
  , String -> Doc
prErrM String
emod
  , Doc
"-- Happy parsers"
  , TokenText -> Maybe String -> [Cat] -> Doc
parsers TokenText
tokenText Maybe String
layoutMod [Cat]
cats
  , Doc
empty 
  ]
  where
  cs :: [String]
  cs :: [String]
cs = (Cat -> Maybe String) -> [Cat] -> [String]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Cat -> Maybe String
baseCat [Cat]
cats
  baseCat :: Cat -> Maybe String
  baseCat :: Cat -> Maybe String
baseCat = \case
    Cat String
s         -> String -> Maybe String
forall a. a -> Maybe a
Just String
s
    CoercCat String
s Integer
_  -> String -> Maybe String
forall a. a -> Maybe a
Just String
s
    TokenCat String
"Char" -> Maybe String
forall a. Maybe a
Nothing
    TokenCat String
s    -> String -> Maybe String
forall a. a -> Maybe a
Just String
s
    ListCat Cat
c     -> Cat -> Maybe String
baseCat Cat
c
  qual :: MakeComment
qual String
m = String
"qualified " String -> MakeComment
forall a. [a] -> [a] -> [a]
++ String
m
uArrow, charT, integerT, doubleT, boolT, listT, maybeT, nothingT, justT,
  intT, natT, intToNatT, natToIntT, pairT, posT, stringT, stringFromListT
  :: IsString a => a
uArrow :: forall a. IsString a => a
uArrow           = a
"→"
charT :: forall a. IsString a => a
charT           = a
"Char"     
integerT :: forall a. IsString a => a
integerT        = a
"Integer"  
doubleT :: forall a. IsString a => a
doubleT         = a
"Double"   
boolT :: forall a. IsString a => a
boolT           = a
"#Bool"
listT :: forall a. IsString a => a
listT           = a
"#List"
maybeT :: forall a. IsString a => a
maybeT          = a
"#Maybe"
nothingT :: forall a. IsString a => a
nothingT        = a
"#nothing"
justT :: forall a. IsString a => a
justT           = a
"#just"
intT :: forall a. IsString a => a
intT            = a
"#Int"     
natT :: forall a. IsString a => a
natT            = a
"#Nat"
intToNatT :: forall a. IsString a => a
intToNatT       = a
"#intToNat"
natToIntT :: forall a. IsString a => a
natToIntT       = a
"#natToInt"
pairT :: forall a. IsString a => a
pairT           = a
"#Pair"
posT :: forall a. IsString a => a
posT            = a
"#BNFCPosition"
stringT :: forall a. IsString a => a
stringT         = a
"#String"
stringFromListT :: forall a. IsString a => a
stringFromListT = a
"#stringFromList"
intPairT :: Doc
intPairT :: Doc
intPairT = [Doc] -> Doc
hsep [ Doc
forall a. IsString a => a
pairT, Doc
forall a. IsString a => a
intT, Doc
forall a. IsString a => a
intT ]
preamble
  :: String  
  -> String  
  -> Doc
preamble :: String -> String -> Doc
preamble String
_time String
what = [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$
  [ [Doc] -> Doc
hcat [ Doc
"-- Agda bindings for the Haskell ", String -> Doc
text String
what, Doc
"." ]
  
  
  ]
imports
  :: ImportNumeric 
  -> Bool          
  -> Bool          
  -> Bool          
  -> Doc
imports :: ImportNumeric -> Bool -> Bool -> Bool -> Doc
imports ImportNumeric
numeric Bool
layout Bool
pos Bool
needMaybe = [Doc] -> Doc
vcat ([Doc] -> Doc)
-> ([[(String, [Doc], [(String, Doc)])]] -> [Doc])
-> [[(String, [Doc], [(String, Doc)])]]
-> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String, [Doc], [(String, Doc)]) -> Doc)
-> [(String, [Doc], [(String, Doc)])] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String, [Doc], [(String, Doc)]) -> Doc
prettyImport ([(String, [Doc], [(String, Doc)])] -> [Doc])
-> ([[(String, [Doc], [(String, Doc)])]]
    -> [(String, [Doc], [(String, Doc)])])
-> [[(String, [Doc], [(String, Doc)])]]
-> [Doc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[(String, [Doc], [(String, Doc)])]]
-> [(String, [Doc], [(String, Doc)])]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[(String, [Doc], [(String, Doc)])]] -> Doc)
-> [[(String, [Doc], [(String, Doc)])]] -> Doc
forall a b. (a -> b) -> a -> b
$
  [ Bool
-> [(String, [Doc], [(String, Doc)])]
-> [(String, [Doc], [(String, Doc)])]
forall m. Monoid m => Bool -> m -> m
when Bool
layout
    [ (String
"Agda.Builtin.Bool",   [],            [(String
"Bool", Doc
forall a. IsString a => a
boolT)]) ]
  , [ (String
"Agda.Builtin.Char",   [Doc
forall a. IsString a => a
charT],       []               ) ]
  , Bool
-> [(String, [Doc], [(String, Doc)])]
-> [(String, [Doc], [(String, Doc)])]
forall m. Monoid m => Bool -> m -> m
when (ImportNumeric
numeric ImportNumeric -> ImportNumeric -> Bool
forall a. Eq a => a -> a -> Bool
== ImportNumeric
YesImportNumeric) [(String, [Doc], [(String, Doc)])]
importNumeric
  , [ (String
"Agda.Builtin.List",   [Doc
"[]", Doc
"_∷_"], [(String
"List", Doc
forall a. IsString a => a
listT)]) ]
  , Bool
-> [(String, [Doc], [(String, Doc)])]
-> [(String, [Doc], [(String, Doc)])]
forall m. Monoid m => Bool -> m -> m
when Bool
needMaybe
    [ (String
"Agda.Builtin.Maybe",  [], [(String
"Maybe", Doc
forall a. IsString a => a
maybeT), (String
"nothing", Doc
forall a. IsString a => a
nothingT), (String
"just", Doc
forall a. IsString a => a
justT)]) ]
  , Bool
-> [(String, [Doc], [(String, Doc)])]
-> [(String, [Doc], [(String, Doc)])]
forall m. Monoid m => Bool -> m -> m
when Bool
pos
    [ (String
"Agda.Builtin.Nat",    [],            [(String
"Nat" , Doc
forall a. IsString a => a
natT )]) ]
  , [ (String
"Agda.Builtin.String", [], [(String
"String", Doc
forall a. IsString a => a
stringT), (String
"primStringFromList", Doc
forall a. IsString a => a
stringFromListT) ]) ]
  ]
  where
  importNumeric :: [(String, [Doc], [(String, Doc)])]
  importNumeric :: [(String, [Doc], [(String, Doc)])]
importNumeric =
    [ (String
"Agda.Builtin.Float public", [], [(String
"Float", Doc
forall a. IsString a => a
doubleT)])
    , (String
"Agda.Builtin.Int   public", [], [(String
"Int", Doc
forall a. IsString a => a
integerT)])
    , (String
"Agda.Builtin.Int"         , [], [(String
"pos", Doc
"#pos")])
    ]
  prettyImport :: (String, [Doc], [(String, Doc)]) -> Doc
  prettyImport :: (String, [Doc], [(String, Doc)]) -> Doc
prettyImport (String
m, [Doc]
use, [(String, Doc)]
ren)
    | [(String, Doc)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(String, Doc)]
ren  = Doc
pre
    | Bool
otherwise = Int -> Doc -> Doc -> Doc -> Doc -> [Doc] -> Doc
prettyList Int
2 Doc
pre Doc
lparen Doc
rparen Doc
semi ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$
        ((String, Doc) -> Doc) -> [(String, Doc)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (\ (String
x, Doc
d) -> [Doc] -> Doc
hsep [String -> Doc
text String
x, Doc
"to", Doc
d ]) [(String, Doc)]
ren
    where
    pre :: Doc
pre = [Doc] -> Doc
hsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ [[Doc]] -> [Doc]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
      [ [ Doc
"open", Doc
"import", String -> Doc
text String
m ]
      , [ Doc
"using", Doc -> Doc
parens (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
hcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ Doc -> [Doc] -> [Doc]
punctuate Doc
"; " [Doc]
use ]
      , [ Doc
"renaming" | Bool -> Bool
not ([(String, Doc)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(String, Doc)]
ren) ]
      ]
importCats
  :: String    
  -> [String]  
  -> Doc
importCats :: String -> [String] -> Doc
importCats String
m [String]
cs = Int -> Doc -> Doc -> Doc -> Doc -> [Doc] -> Doc
prettyList Int
2 Doc
pre Doc
lparen Doc
rparen Doc
semi ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map String -> Doc
text [String]
cs
  where
  pre :: Doc
pre = [Doc] -> Doc
hsep [ Doc
"open", Doc
"import", String -> Doc
text String
m, Doc
"using" ]
importPragmas
  :: TokenText
  -> Bool      
  -> [String]  
  -> Doc
importPragmas :: TokenText -> Bool -> [String] -> Doc
importPragmas TokenText
tokenText Bool
pos [String]
mods = [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map String -> Doc
imp ([String] -> [Doc]) -> [String] -> [Doc]
forall a b. (a -> b) -> a -> b
$ [String]
base [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
mods
  where
  imp :: String -> Doc
imp String
s = [Doc] -> Doc
hsep [ Doc
"{-#", Doc
"FOREIGN", Doc
"GHC", Doc
"import", String -> Doc
text String
s, Doc
"#-}" ]
  base :: [String]
base = [[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    [ [ String
"Prelude (" String -> MakeComment
forall a. [a] -> [a] -> [a]
++ String
preludeImports String -> MakeComment
forall a. [a] -> [a] -> [a]
++ String
")" ]
    , Bool -> [String] -> [String]
forall m. Monoid m => Bool -> m -> m
when Bool
pos
      [ String
"qualified Prelude" ]
    , case TokenText
tokenText of
        TokenText
TextToken       -> []
        TokenText
StringToken     -> []
        TokenText
ByteStringToken -> [ String
"qualified Data.ByteString.Char8 as BS" ]
    , [ String
"qualified Data.Text" ]
    ]
  preludeImports :: String
preludeImports = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
List.intercalate String
", " ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    [ [ String
"Bool", String
"Char", String
"Double", String
"Integer", String
"String", String
"(.)" ]
    , Bool -> [String] -> [String]
forall m. Monoid m => Bool -> m -> m
when Bool
pos
      [ String
"error" ] 
    ]
prToken :: ModuleName -> TokenText -> String -> Bool -> Doc
prToken :: String -> TokenText -> String -> Bool -> Doc
prToken String
amod TokenText
tokenText String
t Bool
pos = [Doc] -> Doc
vsep
  [ if Bool
pos then [Doc] -> Doc
vcat
      
      [ [Doc] -> Doc
hsep [ Doc
"data", String -> Doc
text String
t, Doc
":", Doc
"Set", Doc
"where" ]
      , Int -> Doc -> Doc
nest Int
2 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
hsep
          [ String -> Doc
text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ MakeComment
agdaLower String
t
          , Doc
":"
          , Doc
forall a. IsString a => a
pairT
          , Doc -> Doc
parens Doc
intPairT
          , Cat -> Doc
prettyCat Cat
typ
          , Doc
forall a. IsString a => a
uArrow, String -> Doc
text String
t
          ]
      ]
    else ConstructorStyle -> String -> [(String, [Cat])] -> Doc
prettyData ConstructorStyle
UnnamedArg String
t [(MakeComment
agdaLower String
t, [ Cat
typ ])]
  , String -> String -> String -> [(String, [Cat])] -> Doc
pragmaData String
amod String
t String
t [(String
t, [])]
  ]
  where
  typ :: Cat
typ = case TokenText
tokenText of
    TokenText
TextToken       -> String -> Cat
Cat String
"#String"
    TokenText
ByteStringToken -> String -> Cat
Cat String
"#String"
    TokenText
StringToken     -> Cat -> Cat
ListCat (String -> Cat
Cat String
"Char")
absyn :: ModuleName -> Bool -> ConstructorStyle -> [Data] -> Doc
absyn :: String -> Bool -> ConstructorStyle -> [Data] -> Doc
absyn String
_amod Bool
_havePos ConstructorStyle
_style [] = Doc
empty
absyn  String
amod  Bool
havePos  ConstructorStyle
style [Data]
ds = [Doc] -> Doc
vsep ([Doc] -> Doc) -> ([Data] -> [Doc]) -> [Data] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Doc
"mutual" Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
:) ([Doc] -> [Doc]) -> ([Data] -> [Doc]) -> [Data] -> [Doc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Data -> [Doc]) -> [Data] -> [Doc]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((Doc -> Doc) -> [Doc] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Doc -> Doc
nest Int
2) ([Doc] -> [Doc]) -> (Data -> [Doc]) -> Data -> [Doc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Bool -> ConstructorStyle -> Data -> [Doc]
prData String
amod Bool
havePos ConstructorStyle
style) ([Data] -> Doc) -> [Data] -> Doc
forall a b. (a -> b) -> a -> b
$ [Data]
ds
prData :: ModuleName -> Bool -> ConstructorStyle -> Data -> [Doc]
prData :: String -> Bool -> ConstructorStyle -> Data -> [Doc]
prData String
amod Bool
True  ConstructorStyle
style (Cat String
d, [(String, [Cat])]
cs) = [[Doc]] -> [Doc]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    [ [ [Doc] -> Doc
hsep [ String -> Doc
text String
d, Doc
equals, String -> Doc
text (MakeComment
sanitize String
primed), Doc
forall a. IsString a => a
posT ] ]
    , String
-> ConstructorStyle
-> String
-> String
-> [(String, [Cat])]
-> [Doc]
prData' String
amod ConstructorStyle
style (MakeComment
addP String
d) String
primed [(String, [Cat])]
cs'
    ]
  where
  
  sanitize :: MakeComment
sanitize = Char -> Char -> MakeComment
forall a. Eq a => a -> a -> [a] -> [a]
replace Char
'_' Char
'-'
  primed :: String
primed   = String
d String -> MakeComment
forall a. [a] -> [a] -> [a]
++ String
"'"
  param :: String
param    = String
"Pos#"
  addP :: MakeComment
addP String
c   = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [MakeComment
sanitize String
c, String
"' ", String
param]
  cs' :: [(String, [Cat])]
cs'      = ((String, [Cat]) -> (String, [Cat]))
-> [(String, [Cat])] -> [(String, [Cat])]
forall a b. (a -> b) -> [a] -> [b]
map (([Cat] -> [Cat]) -> (String, [Cat]) -> (String, [Cat])
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (([Cat] -> [Cat]) -> (String, [Cat]) -> (String, [Cat]))
-> ([Cat] -> [Cat]) -> (String, [Cat]) -> (String, [Cat])
forall a b. (a -> b) -> a -> b
$ \ [Cat]
cats -> String -> Cat
Cat String
param Cat -> [Cat] -> [Cat]
forall a. a -> [a] -> [a]
: (Cat -> Cat) -> [Cat] -> [Cat]
forall a b. (a -> b) -> [a] -> [b]
map Cat -> Cat
addParam [Cat]
cats) [(String, [Cat])]
cs
  addParam :: Cat -> Cat
  addParam :: Cat -> Cat
addParam = \case
    Cat String
c     -> String -> Cat
Cat (String -> Cat) -> String -> Cat
forall a b. (a -> b) -> a -> b
$ MakeComment
addP String
c
    ListCat Cat
c -> Cat -> Cat
ListCat (Cat -> Cat) -> Cat -> Cat
forall a b. (a -> b) -> a -> b
$ Cat -> Cat
addParam Cat
c
    Cat
c         -> Cat
c
prData String
amod Bool
False ConstructorStyle
style (Cat String
d, [(String, [Cat])]
cs) = String
-> ConstructorStyle
-> String
-> String
-> [(String, [Cat])]
-> [Doc]
prData' String
amod ConstructorStyle
style String
d String
d [(String, [Cat])]
cs
prData String
_    Bool
_     ConstructorStyle
_     (Cat
c    , [(String, [Cat])]
_ ) = String -> [Doc]
forall a. HasCallStack => String -> a
error (String -> [Doc]) -> String -> [Doc]
forall a b. (a -> b) -> a -> b
$ String
"prData: unexpected category " String -> MakeComment
forall a. [a] -> [a] -> [a]
++ Cat -> String
forall a. Pretty a => a -> String
prettyShow Cat
c
prData' :: ModuleName -> ConstructorStyle -> String -> String -> [(Fun, [Cat])] -> [Doc]
prData' :: String
-> ConstructorStyle
-> String
-> String
-> [(String, [Cat])]
-> [Doc]
prData' String
amod ConstructorStyle
style String
d String
haskellDataName [(String, [Cat])]
cs =
  [ ConstructorStyle -> String -> [(String, [Cat])] -> Doc
prettyData ConstructorStyle
style String
d [(String, [Cat])]
cs
  , String -> String -> String -> [(String, [Cat])] -> Doc
pragmaData String
amod ([String] -> String
forall a. HasCallStack => [a] -> a
head ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ String -> [String]
words String
d) String
haskellDataName [(String, [Cat])]
cs
  ]
prErrM :: ModuleName -> Doc
prErrM :: String -> Doc
prErrM String
emod = [Doc] -> Doc
vsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ String
-> ConstructorStyle
-> String
-> String
-> [(String, [Cat])]
-> [Doc]
prData' String
emod ConstructorStyle
UnnamedArg String
"Err A" String
"Err"
  [ (String
"Ok" , [String -> Cat
Cat String
"A"])
  , (String
"Bad", [Cat -> Cat
ListCat (Cat -> Cat) -> Cat -> Cat
forall a b. (a -> b) -> a -> b
$ String -> Cat
Cat String
"Char"])
  ]
prettyData :: ConstructorStyle -> String -> [(Fun, [Cat])] -> Doc
prettyData :: ConstructorStyle -> String -> [(String, [Cat])] -> Doc
prettyData ConstructorStyle
style String
d [(String, [Cat])]
cs = [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ [[Doc]] -> [Doc]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
  [ [ [Doc] -> Doc
hsep [ Doc
"data", String -> Doc
text String
d, Doc
colon, Doc
"Set", Doc
"where" ] ]
  , [(Doc, Doc)] -> [Doc]
mkTSTable ([(Doc, Doc)] -> [Doc]) -> [(Doc, Doc)] -> [Doc]
forall a b. (a -> b) -> a -> b
$ ((String, [Cat]) -> (Doc, Doc))
-> [(String, [Cat])] -> [(Doc, Doc)]
forall a b. (a -> b) -> [a] -> [b]
map (ConstructorStyle -> String -> (String, [Cat]) -> (Doc, Doc)
prettyConstructor ConstructorStyle
style String
d) [(String, [Cat])]
cs
  ]
  where
mkTSTable :: [(Doc,Doc)] -> [Doc]
mkTSTable :: [(Doc, Doc)] -> [Doc]
mkTSTable = (String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Doc -> Doc
nest Int
2 (Doc -> Doc) -> (String -> Doc) -> String -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Doc
text) ([String] -> [Doc])
-> ([(Doc, Doc)] -> [String]) -> [(Doc, Doc)] -> [Doc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[String]] -> [String]
table String
" : " ([[String]] -> [String])
-> ([(Doc, Doc)] -> [[String]]) -> [(Doc, Doc)] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Doc, Doc) -> [String]) -> [(Doc, Doc)] -> [[String]]
forall a b. (a -> b) -> [a] -> [b]
map (Doc, Doc) -> [String]
mkRow
  where
  mkRow :: (Doc, Doc) -> [String]
mkRow (Doc
c,Doc
t) = [ Doc -> String
render Doc
c, Doc -> String
render Doc
t ]
pragmaData :: ModuleName -> String -> String -> [(Fun, [Cat])] -> Doc
pragmaData :: String -> String -> String -> [(String, [Cat])] -> Doc
pragmaData String
amod String
d String
haskellDataName [(String, [Cat])]
cs =
  Int -> Doc -> Doc -> Doc -> Doc -> [Doc] -> Doc
prettyList Int
2 Doc
pre Doc
lparen (Doc
rparen Doc -> Doc -> Doc
<+> Doc
"#-}") Doc
"|" ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$
    ((String, [Cat]) -> Doc) -> [(String, [Cat])] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> Doc
prettyFun String
amod (String -> Doc)
-> ((String, [Cat]) -> String) -> (String, [Cat]) -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, [Cat]) -> String
forall a b. (a, b) -> a
fst) [(String, [Cat])]
cs
  where
  pre :: Doc
pre = [Doc] -> Doc
hsep
    [ Doc
"{-#", Doc
"COMPILE", Doc
"GHC", String -> Doc
text String
d, Doc
equals, Doc
"data"
    , String -> Doc
text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ String
amod, String
".", String
haskellDataName ]
    ]
prettyConstructor :: ConstructorStyle -> String -> (Fun,[Cat]) -> (Doc,Doc)
prettyConstructor :: ConstructorStyle -> String -> (String, [Cat]) -> (Doc, Doc)
prettyConstructor ConstructorStyle
style String
d (String
c, [Cat]
as) = (String -> Doc
prettyCon String
c,) (Doc -> (Doc, Doc)) -> Doc -> (Doc, Doc)
forall a b. (a -> b) -> a -> b
$ if [Cat] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Cat]
as then String -> Doc
text String
d else [Doc] -> Doc
hsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$
  [ ConstructorStyle -> [Cat] -> Doc
prettyConstructorArgs ConstructorStyle
style [Cat]
as
  , Doc
forall a. IsString a => a
uArrow
  , String -> Doc
text String
d
  ]
prettyConstructorArgs :: ConstructorStyle -> [Cat] -> Doc
prettyConstructorArgs :: ConstructorStyle -> [Cat] -> Doc
prettyConstructorArgs ConstructorStyle
style [Cat]
as =
  case ConstructorStyle
style of
    ConstructorStyle
UnnamedArg -> [Doc] -> Doc
hsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
List.intersperse Doc
forall a. IsString a => a
uArrow [Doc]
ts
    ConstructorStyle
NamedArg   -> [Doc] -> Doc
hsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ ((NonEmpty Doc, Doc) -> Doc) -> [(NonEmpty Doc, Doc)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (\ (Doc
x :| [Doc]
xs, Doc
t) -> Doc -> Doc
parens ([Doc] -> Doc
hsep [Doc
x, [Doc] -> Doc
hsep [Doc]
xs, Doc
colon, Doc
t])) [(NonEmpty Doc, Doc)]
tel
  where
  ts :: [Doc]
ts  = (Cat -> Doc) -> [Cat] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Cat -> Doc
prettyCat [Cat]
as
  ns :: [Doc]
ns  = ((Maybe Int, String) -> Doc) -> [(Maybe Int, String)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Doc
text (String -> Doc)
-> ((Maybe Int, String) -> String) -> (Maybe Int, String) -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Int, String) -> String
forall {a}. Show a => (Maybe a, String) -> String
subscript) ([(Maybe Int, String)] -> [Doc]) -> [(Maybe Int, String)] -> [Doc]
forall a b. (a -> b) -> a -> b
$ [String] -> [(Maybe Int, String)]
forall a. Ord a => [a] -> [(Maybe Int, a)]
numberUniquely ([String] -> [(Maybe Int, String)])
-> [String] -> [(Maybe Int, String)]
forall a b. (a -> b) -> a -> b
$ (Cat -> String) -> [Cat] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Cat -> String
nameSuggestion [Cat]
as
  tel :: [(NonEmpty Doc, Doc)]
tel = ((Doc, Doc) -> String) -> [(Doc, Doc)] -> [(NonEmpty Doc, Doc)]
forall c a b. Eq c => ((a, b) -> c) -> [(a, b)] -> [(List1 a, b)]
aggregateOn (Doc -> String
render (Doc -> String) -> ((Doc, Doc) -> Doc) -> (Doc, Doc) -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Doc, Doc) -> Doc
forall a b. (a, b) -> b
snd) ([(Doc, Doc)] -> [(NonEmpty Doc, Doc)])
-> [(Doc, Doc)] -> [(NonEmpty Doc, Doc)]
forall a b. (a -> b) -> a -> b
$ [Doc] -> [Doc] -> [(Doc, Doc)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Doc]
ns [Doc]
ts
  deltaSubscript :: Int
deltaSubscript = Char -> Int
ord Char
'₀' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Char -> Int
ord Char
'0' 
  subscript :: (Maybe a, String) -> String
subscript (Maybe a
m, String
s) = String -> (a -> String) -> Maybe a -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
s (\ a
n -> String
s String -> MakeComment
forall a. [a] -> [a] -> [a]
++ (Char -> Char) -> MakeComment
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Char
chr (Int -> Char) -> (Char -> Int) -> Char -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int
deltaSubscript Int -> Int -> Int
forall a. Num a => a -> a -> a
+) (Int -> Int) -> (Char -> Int) -> Char -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord) (a -> String
forall a. Show a => a -> String
show a
n)) Maybe a
m
  
  aggregateOn :: Eq c => ((a,b) -> c) -> [(a,b)] -> [(List1 a,b)]
  aggregateOn :: forall c a b. Eq c => ((a, b) -> c) -> [(a, b)] -> [(List1 a, b)]
aggregateOn (a, b) -> c
f
    = (NonEmpty (a, b) -> (List1 a, b))
-> [NonEmpty (a, b)] -> [(List1 a, b)]
forall a b. (a -> b) -> [a] -> [b]
map (\ NonEmpty (a, b)
p -> (((a, b) -> a) -> NonEmpty (a, b) -> List1 a
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
List1.map (a, b) -> a
forall a b. (a, b) -> a
fst NonEmpty (a, b)
p, (a, b) -> b
forall a b. (a, b) -> b
snd (NonEmpty (a, b) -> (a, b)
forall a. NonEmpty a -> a
List1.head NonEmpty (a, b)
p)))
    ([NonEmpty (a, b)] -> [(List1 a, b)])
-> ([(a, b)] -> [NonEmpty (a, b)]) -> [(a, b)] -> [(List1 a, b)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b) -> (a, b) -> Bool) -> [(a, b)] -> [NonEmpty (a, b)]
forall (f :: * -> *) a.
Foldable f =>
(a -> a -> Bool) -> f a -> [NonEmpty a]
List1.groupBy (c -> c -> Bool
forall a. Eq a => a -> a -> Bool
(==) (c -> c -> Bool) -> ((a, b) -> c) -> (a, b) -> (a, b) -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (a, b) -> c
f)
    
nameSuggestion :: Cat -> String
nameSuggestion :: Cat -> String
nameSuggestion = \case
  ListCat Cat
c     -> Cat -> String
nameSuggestion Cat
c String -> MakeComment
forall a. [a] -> [a] -> [a]
++ String
"s"
  CoercCat String
d Integer
_  -> MakeComment
nameFor String
d
  Cat String
d         -> MakeComment
nameFor String
d
  TokenCat{}    -> String
"x"
nameFor :: String -> String
nameFor :: MakeComment
nameFor String
d = [ Char -> Char
toLower (Char -> Char) -> Char -> Char
forall a b. (a -> b) -> a -> b
$ String -> Char
forall a. HasCallStack => [a] -> a
head (String -> Char) -> String -> Char
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> MakeComment
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'#') String
d ]
numberUniquely :: forall a. Ord a => [a] -> [(Maybe Int, a)]
numberUniquely :: forall a. Ord a => [a] -> [(Maybe Int, a)]
numberUniquely [a]
as = (a -> StateT (Frequency a) Identity (Maybe Int, a))
-> [a] -> StateT (Frequency a) Identity [(Maybe Int, a)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM a -> StateT (Frequency a) Identity (Maybe Int, a)
step [a]
as StateT (Frequency a) Identity [(Maybe Int, a)]
-> Frequency a -> [(Maybe Int, a)]
forall s a. State s a -> s -> a
`evalState` Frequency a
forall k a. Map k a
Map.empty
  where
  
  counts :: Frequency a
  counts :: Frequency a
counts = (Frequency a -> a -> Frequency a)
-> Frequency a -> [a] -> Frequency a
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl ((a -> Frequency a -> Frequency a)
-> Frequency a -> a -> Frequency a
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> Frequency a -> Frequency a
forall a. Ord a => a -> Frequency a -> Frequency a
incr) Frequency a
forall k a. Map k a
Map.empty [a]
as
  
  step :: a -> State (Frequency a) (Maybe Int, a)
  step :: a -> StateT (Frequency a) Identity (Maybe Int, a)
step a
a = do
    
    let n :: Int
n = Int -> a -> Frequency a -> Int
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault (String -> Int
forall a. HasCallStack => String -> a
error String
"numberUniquelyWith") a
a Frequency a
counts
    if Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 then (Maybe Int, a) -> StateT (Frequency a) Identity (Maybe Int, a)
forall a. a -> StateT (Frequency a) Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Int
forall a. Maybe a
Nothing, a
a) else do
      
      
      (Frequency a -> Frequency a) -> StateT (Frequency a) Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((Frequency a -> Frequency a) -> StateT (Frequency a) Identity ())
-> (Frequency a -> Frequency a) -> StateT (Frequency a) Identity ()
forall a b. (a -> b) -> a -> b
$ a -> Frequency a -> Frequency a
forall a. Ord a => a -> Frequency a -> Frequency a
incr a
a
      (,a
a) (Maybe Int -> (Maybe Int, a))
-> (Frequency a -> Maybe Int) -> Frequency a -> (Maybe Int, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Frequency a -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup a
a (Frequency a -> (Maybe Int, a))
-> StateT (Frequency a) Identity (Frequency a)
-> StateT (Frequency a) Identity (Maybe Int, a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT (Frequency a) Identity (Frequency a)
forall s (m :: * -> *). MonadState s m => m s
get
type Frequency a = Map a Int
incr :: Ord a => a -> Frequency a -> Frequency a
incr :: forall a. Ord a => a -> Frequency a -> Frequency a
incr = (Maybe Int -> Maybe Int) -> a -> Map a Int -> Map a Int
forall k a.
Ord k =>
(Maybe a -> Maybe a) -> k -> Map k a -> Map k a
Map.alter ((Maybe Int -> Maybe Int) -> a -> Map a Int -> Map a Int)
-> (Maybe Int -> Maybe Int) -> a -> Map a Int -> Map a Int
forall a b. (a -> b) -> a -> b
$ Maybe Int -> (Int -> Maybe Int) -> Maybe Int -> Maybe Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1) (Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> (Int -> Int) -> Int -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
forall a. Enum a => a -> a
succ)
agdaDefCfg :: DefCfg
agdaDefCfg :: DefCfg
agdaDefCfg = DefCfg
  { sanitizeName :: MakeComment
sanitizeName = MakeComment
agdaLower
  , hasType :: String
hasType      = String
":"
  , arrow :: String
arrow        = String
forall a. IsString a => a
uArrow
  , lambda :: String
lambda       = String
"λ"
  , cons :: String
cons         = String
"_∷_"
  , convTok :: MakeComment
convTok      = MakeComment
agdaLower
  , convLitInt :: Exp -> Exp
convLitInt   = \ Exp
e -> String -> Type -> [Exp] -> Exp
forall f. f -> Type -> [Exp' f] -> Exp' f
App String
"#pos" Type
dummyType [Exp
e]
  , polymorphism :: [Base] -> [Base]
polymorphism = (String -> Base
forall a. a -> Base' a
BaseT String
"{a : Set}" Base -> [Base] -> [Base]
forall a. a -> [a] -> [a]
:)
  }
definedRules :: Bool -> CF -> Doc
definedRules :: Bool -> CF -> Doc
definedRules Bool
havePos = [Doc] -> Doc
vsep ([Doc] -> Doc) -> (CF -> [Doc]) -> CF -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DefCfg -> Bool -> CF -> [Doc]
definedRules' DefCfg
agdaDefCfg Bool
havePos
printers :: ModuleName -> [Cat] -> Doc
printers :: String -> [Cat] -> Doc
printers String
_amod []   = Doc
empty
printers  String
amod [Cat]
cats = [Doc] -> Doc
vsep
  [ Doc
"-- Binding the pretty printers."
  , [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ Doc
"postulate" Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: [(Doc, Doc)] -> [Doc]
mkTSTable ((Cat -> (Doc, Doc)) -> [Cat] -> [(Doc, Doc)]
forall a b. (a -> b) -> [a] -> [b]
map (Cat -> (Doc, Doc)
prettyTySig) [Cat]
cats)
  , [Doc] -> Doc
vcat ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ (Cat -> Doc) -> [Cat] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Cat -> Doc
pragmaBind [Cat]
cats
  ]
  where
  prettyTySig :: Cat -> (Doc, Doc)
prettyTySig Cat
c = (Cat -> Doc
agdaPrinterName Cat
c, [Doc] -> Doc
hsep [ Cat -> Doc
prettyCat Cat
c, Doc
forall a. IsString a => a
uArrow, Doc
forall a. IsString a => a
stringT ])
  pragmaBind :: Cat -> Doc
pragmaBind  Cat
c = [Doc] -> Doc
hsep
    [ Doc
"{-#", Doc
"COMPILE", Doc
"GHC", Cat -> Doc
agdaPrinterName Cat
c, Doc
equals, Doc
"\\", Doc
y, Doc
"->"
    , Doc
"Data.Text.pack", Doc -> Doc
parens (Doc
"printTree" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (Doc
y Doc -> Doc -> Doc
<+> Doc
"::" Doc -> Doc -> Doc
<+> Doc
t)), Doc
"#-}"
    ]
    where
    y :: Doc
y = String -> Doc
text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ Cat -> String
nameSuggestion Cat
c
    t :: Doc
t = (Doc -> Doc) -> Doc -> Cat -> Doc
catToType ((String -> Doc
text String
amod Doc -> Doc -> Doc
<> String -> Doc
text String
".") Doc -> Doc -> Doc
<>) Doc
empty Cat
c  
parsers
  :: TokenText
  -> Maybe String  
  -> [Cat]         
  -> Doc
parsers :: TokenText -> Maybe String -> [Cat] -> Doc
parsers TokenText
tokenText Maybe String
layoutMod [Cat]
cats =
  [Doc] -> Doc
vcat (Doc
"postulate" Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: (Cat -> Doc) -> [Cat] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Doc -> Doc
nest Int
2 (Doc -> Doc) -> (Cat -> Doc) -> Cat -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cat -> Doc
prettyTySig) [Cat]
cats)
  Doc -> Doc -> Doc
$++$
  [Doc] -> Doc
vcat ((Cat -> Doc) -> [Cat] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Cat -> Doc
pragmaBind [Cat]
cats)
  where
  
  
  
  prettyTySig :: Cat -> Doc
  prettyTySig :: Cat -> Doc
prettyTySig Cat
c = [Doc] -> Doc
hsep ([Doc] -> Doc) -> ([[Doc]] -> [Doc]) -> [[Doc]] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Doc]] -> [Doc]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Doc]] -> Doc) -> [[Doc]] -> Doc
forall a b. (a -> b) -> a -> b
$
   [ [ Cat -> Doc
agdaParserName Cat
c, Doc
colon ]
   , Bool -> [Doc] -> [Doc]
forall m. Monoid m => Bool -> m -> m
when Bool
layout [ Doc
forall a. IsString a => a
boolT, Doc
forall a. IsString a => a
uArrow ]
   , [ Doc
forall a. IsString a => a
stringT, Doc
forall a. IsString a => a
uArrow, Doc
"Err", Cat -> Doc
prettyCatParens Cat
c ]
   ]
  pragmaBind :: Cat -> Doc
  pragmaBind :: Cat -> Doc
pragmaBind Cat
c = [Doc] -> Doc
hsep ([Doc] -> Doc) -> ([[Doc]] -> [Doc]) -> [[Doc]] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Doc]] -> [Doc]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Doc]] -> Doc) -> [[Doc]] -> Doc
forall a b. (a -> b) -> a -> b
$
    [ [ Doc
"{-#", Doc
"COMPILE", Doc
"GHC", Cat -> Doc
agdaParserName Cat
c, Doc
equals ]
    , Bool -> [Doc] -> [Doc]
forall m. Monoid m => Bool -> m -> m
when Bool
layout [ Doc
"\\", Doc
"tl", Doc
"->" ]
    , [ Cat -> Doc
parserName Cat
c, Doc
"." ]
    , Bool -> [Doc] -> [Doc]
forall m. Monoid m => Bool -> m -> m
when Bool
layout [ [Doc] -> Doc
hcat [ String -> Doc
text String
lmod, Doc
".", Doc
"resolveLayout" ], Doc
"tl", Doc
"." ]
    , [ Doc
"myLexer" ]
    , case TokenText
tokenText of
        
        TokenText
TextToken       -> []
        TokenText
StringToken     -> [ Doc
".", Doc
"Data.Text.unpack" ]
        TokenText
ByteStringToken -> [ Doc
".", Doc
"BS.pack", Doc
".", Doc
"Data.Text.unpack" ]
    , [ Doc
"#-}" ]
    ]
  layout :: Bool
  layout :: Bool
layout = Maybe String -> Bool
forall a. Maybe a -> Bool
isJust Maybe String
layoutMod
  lmod :: String
  lmod :: String
lmod = Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust Maybe String
layoutMod
prettyFun :: ModuleName -> Fun -> Doc
prettyFun :: String -> String -> Doc
prettyFun String
amod String
c = String -> Doc
text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ String
amod, String
".", String
c ]
prettyCon :: Fun -> Doc
prettyCon :: String -> Doc
prettyCon = String -> Doc
text (String -> Doc) -> MakeComment -> String -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MakeComment
agdaLower
agdaLower :: String -> String
agdaLower :: MakeComment
agdaLower = MakeComment
avoidKeywords MakeComment -> MakeComment -> MakeComment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Char) -> MakeComment
forall {a}. (a -> a) -> [a] -> [a]
updateHead Char -> Char
toLower MakeComment -> MakeComment -> MakeComment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Char -> MakeComment
forall a. Eq a => a -> a -> [a] -> [a]
replace Char
'_' Char
'-'
  
  where
  updateHead :: (a -> a) -> [a] -> [a]
updateHead a -> a
_f []    = []
  updateHead a -> a
f (a
x:[a]
xs) = a -> a
f a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
xs
  avoidKeywords :: MakeComment
avoidKeywords String
s
    | String
s String -> Set String -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set String
agdaKeywords = String
s String -> MakeComment
forall a. [a] -> [a] -> [a]
++ String
"\'"
    | Bool
otherwise = String
s
agdaKeywords :: Set String
agdaKeywords :: Set String
agdaKeywords = [String] -> Set String
forall a. Ord a => [a] -> Set a
Set.fromList ([String] -> Set String) -> [String] -> Set String
forall a b. (a -> b) -> a -> b
$ String -> [String]
words String
"abstract codata coinductive constructor data do eta-equality field forall hiding import in inductive infix infixl infixr instance let macro module mutual no-eta-equality open overlap pattern postulate primitive private public quote quoteContext quoteGoal quoteTerm record renaming rewrite Set syntax tactic unquote unquoteDecl unquoteDef using variable where with"
agdaParserName :: Cat -> Doc
agdaParserName :: Cat -> Doc
agdaParserName Cat
c = String -> Doc
text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ String
"parse" String -> MakeComment
forall a. [a] -> [a] -> [a]
++ Cat -> String
identCat Cat
c
agdaPrinterName :: Cat -> Doc
agdaPrinterName :: Cat -> Doc
agdaPrinterName Cat
c = String -> Doc
text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ String
"print" String -> MakeComment
forall a. [a] -> [a] -> [a]
++ Cat -> String
identCat (Cat -> Cat
normCat Cat
c)
prettyCat :: Cat -> Doc
prettyCat :: Cat -> Doc
prettyCat = \case
  Cat String
s        -> String -> Doc
text String
s
  TokenCat String
s   -> String -> Doc
text String
s
  CoercCat String
s Integer
_ -> String -> Doc
text String
s
  ListCat Cat
c    -> Doc
forall a. IsString a => a
listT Doc -> Doc -> Doc
<+> Cat -> Doc
prettyCatParens Cat
c
prettyCatParens :: Cat -> Doc
prettyCatParens :: Cat -> Doc
prettyCatParens Cat
c = Bool -> Doc -> Doc
parensIf (Cat -> Bool
compositeCat Cat
c) (Cat -> Doc
prettyCat Cat
c)
compositeCat :: Cat -> Bool
compositeCat :: Cat -> Bool
compositeCat = \case
  Cat String
c     -> (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
isSpace String
c
  ListCat{} -> Bool
True
  Cat
_         -> Bool
False
agdaLibContents
  :: String      
  -> Doc         
agdaLibContents :: String -> Doc
agdaLibContents String
mod = [Doc] -> Doc
vcat
  [ Doc
"-- Basic I/O library."
  , Doc
""
  , Doc
"module" Doc -> Doc -> Doc
<+> String -> Doc
text String
mod Doc -> Doc -> Doc
<+> Doc
"where"
  , Doc
""
  , Doc
"open import Agda.Builtin.IO     public using (IO)"
  , Doc
"open import Agda.Builtin.List   public using (List; []; _∷_)"
  , Doc
"open import Agda.Builtin.String public using (String)"
  , Doc
"  renaming (primStringFromList to stringFromList)"
  , Doc
"open import Agda.Builtin.Unit   public using (⊤)"
  , Doc
""
  , Doc
"-- I/O monad."
  , Doc
""
  , Doc
"postulate"
  , Doc
"  return : ∀ {a} {A : Set a} → A → IO A"
  , Doc
"  _>>=_  : ∀ {a b} {A : Set a} {B : Set b} → IO A → (A → IO B) → IO B"
  , Doc
""
  , Doc
"{-# COMPILE GHC return = \\ _ _ -> return    #-}"
  , Doc
"{-# COMPILE GHC _>>=_  = \\ _ _ _ _ -> (>>=) #-}"
  , Doc
""
  , Doc
"infixl 1 _>>=_ _>>_"
  , Doc
""
  , Doc
"_>>_  : ∀ {b} {B : Set b} → IO ⊤ → IO B → IO B"
  , Doc
"_>>_ = λ m m' → m >>= λ _ → m'"
  , Doc
""
  , Doc
"-- Co-bind and functoriality."
  , Doc
""
  , Doc
"infixr 1 _=<<_ _<$>_"
  , Doc
""
  , Doc
"_=<<_  : ∀ {a b} {A : Set a} {B : Set b} → (A → IO B) → IO A → IO B"
  , Doc
"k =<< m = m >>= k"
  , Doc
""
  , Doc
"_<$>_  : ∀ {a b} {A : Set a} {B : Set b} → (A → B) → IO A → IO B"
  , Doc
"f <$> m = do"
  , Doc
"  a ← m"
  , Doc
"  return (f a)"
  , Doc
""
  , Doc
"-- Binding basic I/O functionality."
  , Doc
""
  , Doc
"{-# FOREIGN GHC import qualified Data.Text #-}"
  , Doc
"{-# FOREIGN GHC import qualified Data.Text.IO #-}"
  , Doc
"{-# FOREIGN GHC import qualified System.Exit #-}"
  , Doc
"{-# FOREIGN GHC import qualified System.Environment #-}"
  , Doc
"{-# FOREIGN GHC import qualified System.IO #-}"
  , Doc
""
  , Doc
"postulate"
  , Doc
"  exitFailure    : ∀{a} {A : Set a} → IO A"
  , Doc
"  getArgs        : IO (List String)"
  , Doc
"  putStrLn       : String → IO ⊤"
  , Doc
"  readFiniteFile : String → IO String"
  , Doc
""
  , Doc
"{-# COMPILE GHC exitFailure    = \\ _ _ -> System.Exit.exitFailure #-}"
  , Doc
"{-# COMPILE GHC getArgs        = fmap (map Data.Text.pack) System.Environment.getArgs #-}"
  , Doc
"{-# COMPILE GHC putStrLn       = System.IO.putStrLn . Data.Text.unpack #-}"
  , Doc
"{-# COMPILE GHC readFiniteFile = Data.Text.IO.readFile . Data.Text.unpack #-}"
  ]
agdaMainContents
  :: String      
  -> String      
  -> String      
  -> String      
  -> Bool        
  -> Cat         
  -> Doc         
agdaMainContents :: String -> String -> String -> String -> Bool -> Cat -> Doc
agdaMainContents String
mod String
lmod String
amod String
pmod Bool
layout Cat
c = [Doc] -> Doc
vcat
  [ Doc
"-- Test for Agda binding of parser.  Requires Agda >= 2.5.4."
  , Doc
""
  , Doc
"module" Doc -> Doc -> Doc
<+> String -> Doc
text String
mod Doc -> Doc -> Doc
<+> Doc
"where"
  , Bool -> Doc -> Doc
forall m. Monoid m => Bool -> m -> m
when Bool
layout Doc
"\nopen import Agda.Builtin.Bool using (true)"
  , Doc
"open import" Doc -> Doc -> Doc
<+> String -> Doc
text String
lmod
  , Doc
"open import" Doc -> Doc -> Doc
<+> String -> Doc
text String
amod Doc -> Doc -> Doc
<+> Doc
"using" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (Doc
printer)
  , Doc
"open import" Doc -> Doc -> Doc
<+> String -> Doc
text String
pmod Doc -> Doc -> Doc
<+> Doc
"using" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (Doc
"Err;" Doc -> Doc -> Doc
<+> Doc
parser)
  , Doc
""
  , Doc
"main : IO ⊤"
  , Doc
"main = do"
  , Doc
"  file ∷ [] ← getArgs where"
  , Doc
"    _ → do"
  , Doc
"      putStrLn \"usage: Main <SourceFile>\""
  , Doc
"      exitFailure"
  , Doc
"  Err.ok result ←" Doc -> Doc -> Doc
<+> Doc
parseFun Doc -> Doc -> Doc
<+> Doc
"<$> readFiniteFile file where"
  , Doc
"    Err.bad msg → do"
  , Doc
"      putStrLn \"PARSE FAILED\\n\""
  , Doc
"      putStrLn (stringFromList msg)"
  , Doc
"      exitFailure"
  , Doc
"  putStrLn \"PARSE SUCCESSFUL\\n\""
  , Doc
"  putStrLn" Doc -> Doc -> Doc
<+> Doc -> Doc
parens (Doc
printer Doc -> Doc -> Doc
<+> Doc
"result")
  ]
  where
  printer :: Doc
printer  = Cat -> Doc
agdaPrinterName Cat
c
  parser :: Doc
parser   = Cat -> Doc
agdaParserName Cat
c
  parseFun :: Doc
parseFun = [Doc] -> Doc
hsep ([Doc] -> Doc) -> ([[Doc]] -> [Doc]) -> [[Doc]] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Doc]] -> [Doc]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Doc]] -> Doc) -> [[Doc]] -> Doc
forall a b. (a -> b) -> a -> b
$ [ [Doc
parser], Bool -> [Doc] -> [Doc]
forall m. Monoid m => Bool -> m -> m
when Bool
layout [Doc
"true"] ]