Browse Source

various backends: don't wrap pretty printed lines at 80

Pat Hickey 9 years ago
parent
commit
dbf4d89c62

+ 1 - 1
src/Gidl/Backend/Cabal.hs

@@ -69,7 +69,7 @@ defaultCabalTest name_ main_ build_depends_ = CabalTest
 
 cabalFileArtifact :: CabalFile -> Artifact
 cabalFileArtifact CabalFile{..} = artifactText (name ++ ".cabal") $
-  prettyLazyText 80 $ stack
+  prettyLazyText 1000 $ stack
     [ text "name:" <+> text name
     , text "version:" <+> text version
     , text "author:" <+> text author

+ 1 - 1
src/Gidl/Backend/Haskell.hs

@@ -50,7 +50,7 @@ haskellBackend iis pkgname namespace_raw =
 
 makefile :: Artifact
 makefile = artifactText "Makefile" $
-  prettyLazyText 80 $ stack
+  prettyLazyText 1000 $ stack
     [ text "default:"
     , text "\tcabal build"
     , empty

+ 1 - 1
src/Gidl/Backend/Haskell/Interface.hs

@@ -17,7 +17,7 @@ interfaceModule :: Bool -> [String] -> Interface -> Artifact
 interfaceModule useAeson modulepath i =
   artifactPath (intercalate "/" modulepath) $
   artifactText ((ifModuleName i) ++ ".hs") $
-  prettyLazyText 80 $
+  prettyLazyText 1000 $
   stack $
     [ text "{-# LANGUAGE DeriveDataTypeable #-}"
     , text "{-# LANGUAGE DeriveGeneric #-}"

+ 1 - 1
src/Gidl/Backend/Haskell/Test.hs

@@ -12,7 +12,7 @@ import Text.PrettyPrint.Mainland
 serializeTestModule :: [String] -> [Interface] -> Artifact
 serializeTestModule modulepath is =
   artifactText "SerializeTest.hs" $
-  prettyLazyText 80 $
+  prettyLazyText 1000 $
   stack
     [ text "{-# LANGUAGE ScopedTypeVariables #-}"
     , empty

+ 1 - 1
src/Gidl/Backend/Haskell/Types.hs

@@ -14,7 +14,7 @@ typeModule :: Bool -> [String] -> Type -> Artifact
 typeModule useAeson modulepath t =
   artifactPath (intercalate "/" modulepath) $
   artifactText ((typeModuleName t) ++ ".hs") $
-  prettyLazyText 80 $
+  prettyLazyText 1000 $
   stack $
     [ text "{-# LANGUAGE RecordWildCards #-}"
     , text "{-# LANGUAGE DeriveDataTypeable #-}"

+ 1 - 1
src/Gidl/Backend/Ivory/Schema.hs

@@ -16,7 +16,7 @@ schemaModule :: [String] -> Interface -> Schema -> Artifact
 schemaModule modulepath ir schema =
   artifactPath (intercalate "/" (modulepath ++ [ifModuleName ir])) $
   artifactText (schemaName ++ ".hs") $
-  prettyLazyText 80 $
+  prettyLazyText 1000 $
   stack
     [ text "{-# LANGUAGE DataKinds #-}"
     , text "{-# LANGUAGE RankNTypes #-}"

+ 1 - 1
src/Gidl/Backend/Ivory/Test.hs

@@ -12,7 +12,7 @@ import Text.PrettyPrint.Mainland
 serializeTestModule :: [String] -> [Interface] -> Artifact
 serializeTestModule modulepath irs =
   artifactText "SerializeTest.hs" $
-  prettyLazyText 80 $
+  prettyLazyText 1000 $
   stack
     [ text "{-# LANGUAGE ScopedTypeVariables #-}"
     , empty

+ 2 - 2
src/Gidl/Backend/Ivory/Types.hs

@@ -12,7 +12,7 @@ typeUmbrella :: [String] -> [Type] -> Artifact
 typeUmbrella modulepath ts =
   artifactPath (intercalate "/" modulepath) $
   artifactText ("Types.hs") $
-  prettyLazyText 80 $
+  prettyLazyText 1000 $
   stack
     [ text "module" <+> typeModulePath modulepath "Types" <+> text "where"
     , empty
@@ -37,7 +37,7 @@ typeModule :: [String] -> Type -> Artifact
 typeModule modulepath t =
   artifactPath (intercalate "/" modulepath) $
   artifactText ((typeModuleName t) ++ ".hs") $
-  prettyLazyText 80 $
+  prettyLazyText 1000 $
   stack
     [ text "{-# LANGUAGE DataKinds #-}"
     , text "{-# LANGUAGE TypeOperators #-}"

+ 1 - 1
src/Gidl/Backend/Rpc.hs

@@ -98,7 +98,7 @@ rpcModule :: [String] -> Interface -> Artifact
 rpcModule ns iface =
   artifactPath (foldr (\ p rest -> p ++ "/" ++ rest) "Rpc" ns) $
   artifactText (ifaceMod ++ ".hs") $
-  prettyLazyText 80 $
+  prettyLazyText 1000 $
   genServer ns iface ifaceMod
   where
   ifaceMod = ifModuleName iface

+ 1 - 1
src/Gidl/Backend/Tower/Schema.hs

@@ -16,7 +16,7 @@ schemaModule :: [String] -> Interface -> Schema -> Artifact
 schemaModule modulepath ir schema =
   artifactPath (intercalate "/" (modulepath ++ [ifModuleName ir])) $
   artifactText (schemaName ++ ".hs") $
-  prettyLazyText 80 $
+  prettyLazyText 1000 $
   stack
     [ text "{-# LANGUAGE DataKinds #-}"
     , text "{-# LANGUAGE RankNTypes #-}"

+ 2 - 2
src/Gidl/Backend/Tower/Server.hs

@@ -16,7 +16,7 @@ umbrellaModule :: [String] -> Interface -> Artifact
 umbrellaModule modulepath i =
   artifactPath (intercalate "/" modulepath) $
   artifactText (ifModuleName i ++ ".hs") $
-  prettyLazyText 80 $
+  prettyLazyText 1000 $
   stack
     [ text "module" <+> mname
     , indent 2 $ encloseStack lparen (rparen <+> text "where") comma
@@ -37,7 +37,7 @@ serverModule :: [String] -> Interface -> Artifact
 serverModule modulepath i =
   artifactPath (intercalate "/" (modulepath ++ [ifModuleName i])) $
   artifactText "Server.hs" $
-  prettyLazyText 80 $
+  prettyLazyText 1000 $
   stack
     [ text "{-# LANGUAGE DataKinds #-}"
     , text "{-# LANGUAGE RankNTypes #-}"